TreeMig Code
Loading...
Searching...
No Matches
SpecImmigration.f90
Go to the documentation of this file.
1!==============================================================================
2!
3! Name : SpecImmigration
4!
5! Purpose: determines the immigration of seedlings
6!
7! Remarks: contains the SUBROUTINE
8!
9! SpecImmigration (<LocalDynOneTimeStep<LocalDynOneTimeStep<
10! DistrLocalDynThisTime<TimeLoop<TreeMig)
11!
12!==============================================================================
13! design : H. Lischke, N. Zimmermann
14! author(s) : H. Lischke, N. Zimmermann
15! implementation : H. Lischke, N. Zimmermann
16! cleaner : T.J. Loeffler
17! copyright : (c) 1999, 03 by H. Lischke
18!==============================================================================
19!=====================================================================
50!===============================================================
51
52SUBROUTINE specimmigration(nspc, year, doDispersal, thiscell)
53
54 ! <CALL modules for TYPE definitions and +- fixed variables>---------------------------------------------------------------
55 use all_par, only: potbirth, pltsiz, &
56 maxlat, maxlon, &
59 ! Use control, species and stand parameters
60 IMPLICIT NONE
61
62 ! <Passed variables>--------------------------------------------------------------------------------
63 INTEGER, INTENT(in) :: nspc, year ! number of species [=spec]
64 Logical, INTENT(in) :: doDispersal
65
66 ! <Local variables>---------------------------------------------------------------------------------
67 INTEGER :: immilatcoord, immiloncoord, & ! looping variable for species and light
68 iimm, i
69 TYPE(currstateincell), INTENT(inout) :: thiscell
70
71 ! <Here the SUBROUTINE starts>**********************************************************************
72 byspecies: do i = 1, nspc
73 if (dodispersal) then
74 if (immigration) then
75 !----- Immigration (sapling inflow) at certain times and cells
76 do iimm = 1, spec(i)%immi%n
77 !----- the relative immigration coords are converted to coords (0 to maxlat, 0 to maxlon)
78 immilatcoord = int(max(1.0, maxlat*spec(i)%immi%dat(iimm)%relLat))
79 immiloncoord = int(max(1.0, maxlon*spec(i)%immi%dat(iimm)%relLon))
80 !----- if current year and coords fall into the immigration period and are an immigration point,
81 !----- the saplings number is increased
82 if ((thiscell%lat == immilatcoord) .and. &
83 (thiscell%lon == immiloncoord) .and. &
84 (year >= spec(i)%immi%dat(iimm)%year - immiperiod) .and. &
85 (year < spec(i)%immi%dat(iimm)%year + immiperiod)) then
86 thiscell%sp(i)%numin(0) = thiscell%sp(i)%numin(0) + 1000.0*pltsiz/833.0
87 end if
88 end do !----- iimm
89 end if !----- immigration
90 else !----- not doDispersal
91 if (immigration) then
92 if (year >= spec(i)%immi%dat(1)%year) then
93 spec(i)%birth = potbirth
94 else
95 spec(i)%birth = 0
96 end if
97 else !----- not immigration
98 spec(i)%birth = potbirth
99 end if !----- IF immigration
100 end if !----- immigration
101 end do byspecies
102
103end SUBROUTINE specimmigration
104!done
subroutine specimmigration(nspc, year, dodispersal, thiscell)
SpecImmigration
real pltsiz
Definition All_par.f90:125
type(specproperties), dimension(maxspc) spec
Definition All_par.f90:345
integer immiperiod
Definition All_par.f90:85
integer maxlon
Definition All_par.f90:46
real, parameter potbirth
Definition All_par.f90:126
integer, allocatable, parameter immigration
Definition All_par.f90:37
integer, parameter max
Definition All_par.f90:98
integer maxlat
Definition All_par.f90:45