TreeMig Code
Loading...
Searching...
No Matches
TimeLoop.f90
Go to the documentation of this file.
1!==============================================================================
34!===============================================================
35SUBROUTINE timeloop(yearStart, yearEnd, &
36 latStart, latEnd, lonStart, lonEnd, &
37 currLatStart, currLatEnd, currLonStart, currLonEnd, &
38 facvar, &
39 nspc, doDispersal, ncallSpatSimu, doParallel, doFFT)
40
41 ! <CALL modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
43! use TMMPITypes, only: master
45 IMPLICIT NONE
46
47 ! <Passed variables>--------------------------------------------------------------------------------
48 INTEGER, INTENT(in) :: yearStart, yearEnd, & ! start and end of simulated period
49 latStart, latEnd, lonStart, lonEnd, & ! start and end of simulated areaINTEGER :: nspc
50 currLatStart, currLatEnd, currLonStart, currLonEnd, & ! part of total simulation area currently simulated, e.g. for spin-up. Is not subarea!
51 nspc, ncallSpatSimu ! number of species involved [=spec]
52 REAL, INTENT(in) :: facvar
53 LOGICAL, INTENT(in) :: doDispersal, doParallel, doFFT ! flag: simulate dispersal?
54
55 ! <Local variables>--------------------------------------------------------------------------------
56 INTEGER :: year ! looping variable for simulated year
57
58 ! <Here the SUBROUTINE starts>**********************************************************************
59
60 looptime: do year = yearstart, yearend
61 write (logmessage, "(A10,I8,A7,L)") " Year: ", year, " doDispersal: ", dodispersal
63!---- Reads the bioclimate if necessary. In the current version bioclimate is read in each year.
65!---- Run the model for this time step
66 if (doparallel) then
67! #ifdef WITHMPI
68! call MastersParallelWorkForDistributedAndDispersalSimus( &
69! year, &
70! latStart, latEnd, lonStart, lonEnd, &
71! currLatStart, currLatEnd, currLonStart, currLonEnd, &
72! facvar, &
73! nspc, doDispersal)
74! #endif
75 else
76 call spatialdynonetimestep(year, &
77 currlatstart, currlatend, currlonstart, currlonend, &
78 nspc, dodispersal, dofft)
79 end if
80!---- Write out the current state to the statefile if wished at this year
81 if (((mod(year, stateoutputdist) == 0) &
82 .or. any((year + simustartyear) == stateoutputyears) &
83 .or. (year == numyrs-1)) &
84 .and. (year > 0))&
85 call writestate(year, latstart, latend, lonstart, lonend, nspc) ! Store intermediate results all 400 years
86 end do looptime
87
88! #ifdef WITHMPI
89! if (doParallel) call BCastTimeLoopIsReady(ncallSpatSimu, thisyear) ! Comment out if run without MPI
90! #endif
91 ! call measuretime(master,20) ! Comment out if run without MPI
92
93end SUBROUTINE timeloop
94!done
95
subroutine readnewbioclimifnecessary(year)
ReadNewBioClimIfNecessary.
subroutine spatialdynonetimestep(year, currlatstart, currlatend, currlonstart, currlonend, nspc, dodispersal, dofft)
SpatialDynOneTimeStep, spatial dynamics in one time step.
subroutine timeloop(yearstart, yearend, latstart, latend, lonstart, lonend, currlatstart, currlatend, currlonstart, currlonend, facvar, nspc, dodispersal, ncallspatsimu, doparallel, dofft)
TimeLoop.
Definition TimeLoop.f90:40
subroutine writestate(year, latstart, latend, lonstart, lonend, nspc)
WriteState.
integer stateoutputdist
Definition All_par.f90:31
integer simustartyear
Definition All_par.f90:27
integer numyrs
Definition All_par.f90:26
integer, dimension(10) stateoutputyears
Definition All_par.f90:32
LoggerModule.
subroutine loginfo(msg)
LogInfo
character(len=1024) logmessage