TreeMig Code
Loading...
Searching...
No Matches
ReadImmigrationData.f90
Go to the documentation of this file.
1!==============================================================================
25!===============================================================
26SUBROUTINE readimmigrationdata(nspc)
27 use loggermodule
29 ! CALL modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
30 use all_par, only: simustartyear, &
31 spec, &
33
34 IMPLICIT NONE
35
36 ! Passed variables>--------------------------------------------------------------------------------
37 INTEGER, INTENT(in) :: nspc ! number of species [=spec]
38
39 ! Local variables>---------------------------------------------------------------------------------
40 INTEGER :: i, j, & ! looping variable for species and immigration dates
41 err, &
42 imdat(maxImmigrationsPerSpec)
43 character(27) :: text1
44
45 ! Here the SUBROUTINE starts>**********************************************************************
46 !-----<Check for file (opening) errors>
47 if (immigration) then
48 call loginfo("Reading immigration data")
49 call openfiler(immigration_file, err) ! closed (this l. 85)
50 if (err /= 0) then
51 call logerror("Could not open file with immigration data: "//immigration_file%path)
52 error stop
53 end if
54 call openfiler(immigrationout_file, err) ! closed (this l. 86)
55 !----- Read immigration period
56 read (immigration_file%unit, "(A)") ! skip first line
57 read (immigration_file%unit, *) immiperiod ! read the immigration period, i.e. the length of immigration event
58
59 !----- Skip first
60 read (immigration_file%unit, "(A)")
61 read_specimmi: do i = 1, nspc ! for each species ...
62 read (immigration_file%unit, *, iostat=err) text1, spec(i)%immi%n, & ! read the number of immigration events...
63 (imdat(j), spec(i)%immi%dat(j)%relLat, spec(i)%immi%dat(j)%relLon, j=1, spec(i)%immi%n) ! ... and for each event year (in real years), relLat and relLon; the coordinates are relative values (between 0 and 1)
64
65 if (spec(i)%immi%n .gt. maximmigrationsperspec) then
66 write (logmessage, *) 'more immigration events ', spec(i)%immi%n, ' than allowed ', maximmigrationsperspec
68 error stop
69 end if
70
71 !----- If EOF, then exit the read loop
72 exit_loop1: if (err /= 0) then
73 exit read_specimmi
74 end if exit_loop1
75
76 do j = 1, spec(i)%immi%n ! transform immigration year to relative years (years since simulation start)
77 spec(i)%immi%dat(j)%year = -simustartyear + imdat(j)
78 end do
79
80 write (immigrationout_file%unit, *) &
81 spec(i)%immi%n, (spec(i)%immi%dat(j)%year, &
82 spec(i)%immi%dat(j)%relLat, spec(i)%immi%dat(j)%relLon, j=1, spec(i)%immi%n)
83 end do read_specimmi
84
85 call closefile(immigration_file)
86 call closefile(immigrationout_file)
87 else !----- no immigration, initialize at least first year
88 spec%immi%n = 0
89 spec%immi%dat(1)%year = 0
90
91 end if !----- immigration
92end SUBROUTINE readimmigrationdata
93!done
subroutine readimmigrationdata(nspc)
ReadImmigrationData
integer simustartyear
Definition All_par.f90:27
type(specproperties), dimension(maxspc) spec
Definition All_par.f90:345
integer immiperiod
Definition All_par.f90:85
integer, parameter maximmigrationsperspec
Definition All_par.f90:37
integer, allocatable, parameter immigration
Definition All_par.f90:37
type(file) immigrationout_file
type(file) immigration_file
LoggerModule.
subroutine loginfo(msg)
LogInfo
character(len=1024) logmessage
subroutine logerror(msg)
LogError