TreeMig Code
Loading...
Searching...
No Matches
SelfRegulation.f90
Go to the documentation of this file.
1!=====================================================================
33!===============================================================
34SUBROUTINE selfregulation(nspc, doDispersal, thiscell)
35
36 ! <CALL modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
37 use all_par, only: pltsiz, &
42 ! Use control, species and stand parameters
43 IMPLICIT NONE
44
45 ! <Passed variables>--------------------------------------------------------------------------------
46 INTEGER, INTENT(in) :: nspc ! number of species [=spec]
47 Logical, INTENT(in) :: doDispersal
48
49 ! <Local variables>---------------------------------------------------------------------------------
50 INTEGER :: i ! looping variable for species and light
51 REAL :: seedBankUngrazed, grazing, grazersOld, sharePerGrazer, amountPerGrazer, &
52 ratio, exporatio
53 TYPE(currstateincell), INTENT(inout):: thiscell
54
55 ! <Here the SUBROUTINE starts>**********************************************************************
56 byspecies: do i = 1, nspc
57 if (dodispersal) then ! only if dispersal, because otherwise no seed bank
58 !----- if wished antagonists eat seeds from seedBank and grow
59 if (withseedantagonists) then
60 grazersold = thiscell%sp(i)%antagonist
61 seedbankungrazed = thiscell%sp(i)%seedBank + thiscell%sp(i)%newSeeds
62 sharepergrazer = 1/(grazersold + 0.5/seedantagraz)
63 amountpergrazer = seedbankungrazed*sharepergrazer
64 grazing = grazersold*amountpergrazer
65
66 !----- they can eat only as much as is there
67 thiscell%sp(i)%seedBank = seedbankungrazed - grazing
68 thiscell%sp(i)%antagonist = (grazersold + grazing*seedantaeff)*(1.-seedantamort) + &
70 end if !----- withseedAntagonists
71
72 !----- more abstract: the antagonist dynamics is formulated by a simple carrying capacity
73 !----- This is assumed to work continuously during each year. That means the dynamics is a solved logistic equation
74 if (withseedcarrcap) then
75 ratio = min(thiscell%sp(i)%newSeeds/seedcarrcap, 20.0) ! it is 0 anyway with values smaller exp(-20)
76 exporatio = exp(-ratio)
77 thiscell%sp(i)%seedBank = seedcarrcap + (thiscell%sp(i)%seedBank - seedcarrcap)*exporatio
78 !----- technical trick to avoid 0 trees with very little influx
79 if ((ratio > 0.0) .AND. (thiscell%sp(i)%seedBank == 0.0)) thiscell%sp(i)%seedBank = thiscell%sp(i)%newSeeds
80 end if !----- withSeedCarrCap
81
82 if ((.not. withseedcarrcap) .and. (.not. withseedantagonists)) then ! ----- this case happens only in reprotest
83 thiscell%sp(i)%seedBank = thiscell%sp(i)%seedBank + thiscell%sp(i)%newSeeds
84 end if
85
86 thiscell%sp(i)%sb = thiscell%sp(i)%seedBank !-----
87 thiscell%sp(i)%newSeeds = 0.0;
88 end if !----- doDispersal
89
90 end do byspecies
91
92end SUBROUTINE selfregulation
93!done
subroutine selfregulation(nspc, dodispersal, thiscell)
SelfRegulation
real pltsiz
Definition All_par.f90:125
real seedantamort
Definition All_par.f90:80
real seedantaeff
Definition All_par.f90:79
real seedantarain
Definition All_par.f90:81
logical withseedantagonists
Definition All_par.f90:77
logical withseedcarrcap
Definition All_par.f90:82
real seedantagraz
Definition All_par.f90:78
real seedcarrcap
Definition All_par.f90:83