TreeMig Code
Loading...
Searching...
No Matches
SpatialDynOneTimeStep.f90
Go to the documentation of this file.
1!==============================================================================
2!
3! Name : SpatialDynOneTimeSteo
4!
5! Remarks: contains the SUBROUTINEs
6!
7! SpatialDynOneTimeStep (<TimeLoop<TreeMig)
8! LocalDynOneTimeStep (<SpatialDynOneTimeStep<TimeLoop<TreeMig)
9!
10!==============================================================================
11! design : H. Lischke, N. Zimmermann
12! author(s) : H. Lischke, N. Zimmermann
13! implementation : H. Lischke, N. Zimmermann
14! cleaner : T.J. Loeffler
15! copyright : (c) 1999, 03 by H. Lischke
16!==============================================================================
17
18!=================== For non parallel (i.e.) standard TreeMig======================================================
45!===============================================================
46SUBROUTINE spatialdynonetimestep(year, &
47 currLatStart, currLatEnd, currLonStart, currLonEnd, &
48 nspc, doDispersal, doFFT)
49 ! <CALL modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
50 IMPLICIT NONE
51 ! <Passed variables>--------------------------------------------------------------------------------
52 INTEGER, INTENT(in) :: year, & ! current year
53 currLatStart, currLatEnd, currLonStart, currLonEnd, & ! start and end of simulated areaINTEGER :: nspc
54 nspc ! number of species involved [=spec]
55
56 LOGICAL, INTENT(in) :: doDispersal, doFFT ! dispersal or not?
57
58 ! <Local variables>--------------------------------------------------------------------------------
59 INTEGER :: lat, & ! looping variable for latitude [=..]
60 lon, & ! looping variable for longitude
61 iam ! processor or slave number
62 REAL:: ddegs, wtemp, drstr, avnit, brwpr, disturb, germDrought
63 ! <Here the SUBROUTINE starts>**********************************************************************
64! print *, "begin localwork ", year, "currLatStart, currLatEnd,currLonStart, currLonEnd ",&
65! currLatStart, currLatEnd,currLonStart, currLonEnd
66 !---- Dynamics in cells
67 looplatlocadyn: do lat = currlatstart, currlatend
68 looplonlocadyn: do lon = currlonstart, currlonend
69 !---- Get the current environment for this cell
70 call getenvfactors(year, lat, lon, ddegs, wtemp, drstr, avnit, brwpr, disturb, germdrought )
71 !---- Local dynamics in this cell
72 call localdynonetimestep(year, lat, lon, nspc, &
73 ddegs, wtemp, drstr, avnit, brwpr, disturb, germdrought, dodispersal, dofft)
74 end do looplonlocadyn
75 end do looplatlocadyn
76 !---- write the results to netcdf file if wished
77 call reportnetcdf(year, nspc)
78 !---- Seed dynamics
79 !---- do seed dispersal by fft is wished
80 if (dodispersal .and. dofft) &
81 call seedrainbyfft(nspc, year, currlatstart, currlatend, currlonstart, currlonend)
82 !---- update the new seeds ending up in this simulation area
83 call updatenewseeds(nspc, iam, dodispersal, year, currlatstart, currlatend, currlonstart, currlonend) !For compatibility with parallel version ! In Interact.f90
84 !---- Get seeds from outside the simulation region
85 call seedsfromoutssimregion(nspc, dodispersal, year, currlatstart, currlatend, currlonstart, currlonend) ! In Interact.f90
86end SUBROUTINE spatialdynonetimestep
87!****<Here the SUBROUTINE ends>********************************************************************
88!=================== For non parallel (i.e.) standard TreeMig======================================================
126!===============================================================
127
128!========================= For parallel and sequential ===============================
129SUBROUTINE localdynonetimestep(year, lat, lon, nspc, ddegs, wtemp, drstr, avnit, brwpr, disturb, germDrought, doDispersal, doFFT)
130
132 use loggermodule
133 IMPLICIT NONE
134
135 INTEGER, INTENT(in) :: year, nspc, lat, lon ! number of species involved [=spec]
136 LOGICAL, INTENT(in) :: doDispersal, doFFT ! dispersal or not?
137 REAL, INTENT(in) :: ddegs, wtemp, drstr, avnit, brwpr, disturb, germDrought
138
139 TYPE(currstateincell):: thiscell
140
141
142 ! check whether cell is in allowed area
143 if ((lat > maxlat) .or. (lat < 1) .or. (lon > maxlon) .or. (lon < 1)) then
144 call logerror("Wrong coordinates in SUBROUTINE LocalDynOneTimeStep")
145 write (logmessage, "(4A15)") "lon", "lat", "maxlon", "maxlat"
146 call logerror(logmessage)
147 write (logmessage, "(4I15)") lon, lat, maxlon, maxlat
148 call logerror(logmessage)
149 error stop
150 end if
151 ! if not stockable, shown by a negative value of ddegs...
152 if (ddegs < 0.0 .and. stockability(lat, lon) > 0.0) then
153 call killalltreesandseeds(nspc, thiscell) ! set all trees and seeds to zero
154 call storethiscellspecstatestocell(lat, lon, nspc, thiscell) ! store the actual structure thiscell back to the cell, ! In StoringBackAndForth.f90
155 stockability(lat, lon) = 0.0 ! set the stockability to zero
156 end if
157!print *," in localwork", year,lat, lon , stockability(lat, lon), ddegs
158
159 if (stockability(lat, lon) > 1.e-20) then ! if cell is stockable, do the local dynamics
160 call calccurrentdepfunctsincell(nspc, ddegs, wtemp, drstr, avnit, brwpr, germdrought) ! calculate dep functions
161 call storecellstatetothiscell(lat, lon, nspc, ddegs, wtemp, drstr, avnit, brwpr, disturb, germdrought, thiscell) ! store the actual cell to the structure thiscell ! In StoringBackAndForth.f90
162 call localforestdynamics(nspc, year, dodispersal, thiscell) ! do the local forest dynamics
163 call storethiscellspecstatestocell(lat, lon, nspc, thiscell) ! store the actual structure thiscell back to the cell, ! In StoringBackAndForth.f90
164
165 if (dodispersal .and. (.not. dofft)) call seedsdispersedfromthiscell(nspc, lat, lon) !!! calculate the seed dispersal from this cell, ! In Interact.f90
166! else
167! call StoreCellStateToThisCell(lat, lon, nspc, ddegs, wtemp, drstr, avnit, brwpr, disturb, germDrought, thiscell) ! store the actual cell to the structure thiscell ! In StoringBackAndForth.f90
168! call KillAllTrees(nspc, year, thiscell)
169! call StoreThisCellSpecStatesToCell(lat, lon, nspc, thiscell) ! store the actual structure thiscell back to the cell, ! In StoringBackAndForth.f90
170 end if !stockability(lat, lon) > 1.E-20
171
172 call report(nspc, year, lat, lon)
173 ! call EvaluateResults (nspc, year, lat, lon)
174 end SUBROUTINE localdynonetimestep
175
176!========================= Setting all trees and seeds to zero when cell becomes unstockable ===============================
177!****<Here the SUBROUTINE ends>********************************************************************
178!=================== For non parallel (i.e.) standard TreeMig======================================================
192!===============================================================
193 SUBROUTINE killalltreesandseeds(nspc, thiscell)
194 use all_par, only: currstateincell
195 IMPLICIT NONE
196 TYPE(currstateincell), INTENT(inout):: thiscell
197 INTEGER, INTENT(in) :: nspc
198 INTEGER :: ispec
199
200 do ispec = 1, nspc
201 thiscell%sp(ispec)%numin = 0.0
202 thiscell%sp(ispec)%sb = 0.0
203 thiscell%sp(ispec)%seedBank = 0.0
204 end do
205 end SUBROUTINE killalltreesandseeds
206!done
subroutine calccurrentdepfunctsincell(nspc, ddegs, wtemp, drstr, avnit, brwpr, germdrought)
CalcCurrentDepFunctsInCell
subroutine seedrainbyfft(nspc, year)
SeedRainByFFT
subroutine getenvfactors(year, lat, lon, ddegs, wtemp, drstr, avnit, brwpr, disturb, germdrought)
GetEnvFactors.
subroutine updatenewseeds(nspc, iam, dodispersal, year, lats, late, lons, lone)
UpdateNewSeeds.
Definition Interact.f90:159
subroutine seedsfromoutssimregion(nspc, dodispersal, year, lats, late, lons, lone)
SeedsFromOutsSimRegion.
Definition Interact.f90:218
subroutine seedsdispersedfromthiscell(nspc, lat, lon)
SeedsDispersedFromThisCell: Does the explicit seed dispersal for all species.
Definition Interact.f90:30
subroutine localforestdynamics(nspc, year, dodispersal, thiscell)
LocalForestDynamics.
subroutine reportnetcdf(year, nspc)
ReportNETCDF.
subroutine killalltreesandseeds(nspc, thiscell)
KillAllTreesAndSeeds, local dynamics in one time step and one cell.
subroutine localdynonetimestep(year, lat, lon, nspc, ddegs, wtemp, drstr, avnit, brwpr, disturb, germdrought, dodispersal, dofft)
LocalDynOneTimeStep, local dynamics in one time step and one cell.
subroutine spatialdynonetimestep(year, currlatstart, currlatend, currlonstart, currlonend, nspc, dodispersal, dofft)
SpatialDynOneTimeStep, spatial dynamics in one time step.
subroutine storecellstatetothiscell(lat, lon, nsp, ddegs, wtemp, drstr, avnit, brwpr, disturb, germdrought, thiscell)
StoreCellStateToThisCell.
subroutine storethiscellspecstatestocell(lat, lon, nspc, thiscell)
StoreThisCellSpecStatesToCell.
real, dimension(:, :), allocatable stockability
Definition All_par.f90:53
character(len=:), allocatable e
Definition All_par.f90:93
integer maxlon
Definition All_par.f90:46
integer, dimension(10, 3) report
Definition All_par.f90:29
integer maxlat
Definition All_par.f90:45
LoggerModule.
character(len=1024) logmessage
subroutine logerror(msg)
LogError