TreeMig Code
Loading...
Searching...
No Matches
TreeMig.f90
Go to the documentation of this file.
1!==============================================================================
42
43!==============================================================================
44
45SUBROUTINE treemig(doParallel)
48 ! USE modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
49 use all_par, only: numyrs, maxlat, maxlon, &
53 use loggermodule
54 IMPLICIT NONE
55
56 LOGICAL, INTENT(in):: doParallel
57 ! Passed on variables>--------------------------------------------------------------------------------
58 INTEGER :: nspc, & ! number of species [=spec]
59 yearStartEqRun, yearEndEqRun, & ! year of calculation for initial run into equilibrium [=..]
60 yearStart, yearEnd, & ! year of calculation [=..]
61 stateYear, & ! year of stored state
62 currLatStart, currLatEnd, & ! looping variable for latitude [=..]
63 currLonStart, currLonEnd ! looping variable for longitude [=..]
64 LOGICAL :: doDispersal
65
66
67
68!! This is all MASTER-WORK
70
71!----- Preparation of simulation, reading in of settings and parameters ----------------------------------
72 ! call startmeasuretime(0,17) ! Comment out if run without MPI
73 call readcontrolparsandinitfiles() ! Initialises all kinds of output files, reads in the control parameters
74
75 call allocateareas() ! Allocates all kinds of arrays for the simulation
76 call getspc(nspc, dofft) ! reads in the species parameters, and calculates further constant variables from them
77
78! Preparation of outputs
79 call preparenetcdfoutput(nspc) ! prepares the output in NetCDF format
80 call prepareoutput(nspc) ! prepares the output
81! Setting of variables for stand
82 call initandsetconstheightclprops(nspc) ! sets cell-specific constant variables
83 call preparebiocliminput() ! prepares the reading in of the bioclimate
84
85! For parallel computing transfer of initial information to slaves
86 if (doparallel) then
87 currlatstart = 1; currlatend = startlatend
88 currlonstart = 1; currlonend = startlonend
89! call startmeasuretime(0,26) ! Comment out if run without MPI
90!#ifdef WITHMPI
91! call BroadcastConstantValues(nspc, 0)
92! call SendInitValuesToSlaves(0, startlatStart, startlatEnd, startlonStart, startlonEnd, facvar, nspc, doDispersal)
93!#endif
94 ! call measuretime(0,26) ! Comment out if run without MPI
95 end if !doParallel
96
97!----- Inoculation simulation, i.e. simulation with constant seed pool and no dispersal. -------------------------
98 dodispersal = .false.
99
100 yearstarteqrun = 0
101 yearendeqrun = inoculationtime + yearstarteqrun
102
103 if ((yearstarteqrun < yearendeqrun)) then ! run only if an inoculation period longer than 0 is defined
104 currlatstart = startlatstart; currlatend = startlatend ! run only in the inoculation area
105 currlonstart = startlonstart; currlonend = startlonend
107 write(logmessage,"(A,I6,A,I6)") "Starting inoculation from year", yearstarteqrun, " to ", yearendeqrun
108 call loginfo(logmessage)
109 write(logmessage,"(4(A10))") "latStart", "latEnd", "lonStart", "lonEnd"; call loginfo(logmessage)
110 write(logmessage,"(4(I10))") currlatstart, currlatend, currlonstart, currlonend; call loginfo(logmessage)
111
112 call timeloop(yearstarteqrun, yearendeqrun, & ! This is the simulation
113 1, maxlat, 1, maxlon, currlatstart, currlatend, currlonstart, currlonend, &
114 facvar, nspc, dodispersal, 1, doparallel, dofft)
115 end if
116
117!----- Now the simulation with migration starts. ---------------------------------------------------------------------------
118 dodispersal = .true.
119
120 currlatstart = 1; currlatend = maxlat ! run in the full simulation domain
121 currlonstart = 1; currlonend = maxlon
122
123 if (readstatefile) then ! if simulation is to be started from a statefile...
124 call loginfo("Reading state file...")
125 call readstate(stateyear, currlatstart, currlatend, currlonstart, currlonend, nspc) ! read this statefile
126 yearstart = stateyear ! simulation starts at year of statefile
127 yearend = numyrs + yearstarteqrun - 1
128 else
129 call loginfo("Read state file disabled. Skip reading state file...")
130 yearstart = yearendeqrun + 1 ! simulation starts in the year after the inoculation period
131 yearend = numyrs + yearstarteqrun - 1
132 end if
133
134 !call OpenStateFileForWrite()
135
136 write(logmessage,"(A,I6,A,I6)") "Starting migration simulation from year", yearstart, " to ", yearend
137 call loginfo(logmessage)
138 write(logmessage,"(4(A10))") "latStart", "latEnd", "lonStart", "lonEnd"
139 call loginfo(logmessage)
140 write(logmessage,"(4(I10))") currlatstart, currlatend, currlonstart, currlonend
141 call loginfo(logmessage)
142
144 call timeloop(yearstart, yearend, & ! This is the simulation
145 1, maxlat, 1, maxlon, currlatstart, currlatend, currlonstart, currlonend, &
146 facvar, nspc, dodispersal, 2, doparallel, dofft)
147
148!----- Finally some cleaning up ---------------------------------------------------------------------------
149
150! #ifdef WITHMPI
151! if (doParallel) then
152! ! receive end signals
153! call WaitUntilSlavesAreCompletelyReady
154! call PasteResultFilesTogether(nspc, currLatStart, currLatEnd)
155! ! call PasteStateFilesTogether(nspc, currLatStart, currLatEnd,currLonStart, currLonEnd)
156! end if
157! #endif
158
159 call closeoutputfiles()
160 call closefile(bioclimate_file)
161 call stoplogger()
162end SUBROUTINE treemig
subroutine allocateareas
AllocateAreas.
subroutine getspc(nspc, dofft)
GetSpc
Definition GetSpc.f90:38
subroutine initandsetconstheightclprops(nspc)
InitAndSetConstHeightClProps.
subroutine preparebiocliminput()
PrepareBioclimInput
subroutine closeoutputfiles
CloseOutputFiles
subroutine prepareoutput(nspc)
PrepareOutput
subroutine readstate(stateyear, latstart, latend, lonstart, lonend, nspc)
ReadState.
Definition ReadState.f90:32
subroutine timeloop(yearstart, yearend, latstart, latend, lonstart, lonend, currlatstart, currlatend, currlonstart, currlonend, facvar, nspc, dodispersal, ncallspatsimu, doparallel, dofft)
TimeLoop.
Definition TimeLoop.f90:40
subroutine treemig(doparallel)
TreeMig (TREE MIGration simulator)
Definition TreeMig.f90:46
integer startlatend
Definition All_par.f90:52
logical readstatefile
Definition All_par.f90:56
integer startlonend
Definition All_par.f90:52
integer numyrs
Definition All_par.f90:26
type(wroutp) true
Definition All_par.f90:143
real fcvardyn
Definition All_par.f90:124
integer maxlon
Definition All_par.f90:46
integer startlatstart
Definition All_par.f90:52
logical dofft
Definition All_par.f90:73
real facvar
Definition All_par.f90:122
type(wroutp) false
Definition All_par.f90:143
integer inoculationtime
Definition All_par.f90:55
real fcvarinit
Definition All_par.f90:123
integer startlonstart
Definition All_par.f90:52
integer maxlat
Definition All_par.f90:45
subroutine readcontrolparsandinitfiles()
ReadControlParsAndInitFiles
type(file) bioclimate_file
LoggerModule.
subroutine loginfo(msg)
LogInfo
character(len=1024) logmessage
subroutine stoplogger()
StopLogger
subroutine preparenetcdfoutput(nspc)
PrepareNetcdfOutput