source: branches/publications/ORCHIDEE_GLUC_r6545/src_sticslai/Stics_Calcul_LAI.f90 @ 6737

Last change on this file since 6737 was 3751, checked in by albert.jornet, 8 years ago

New: CROP module. Done by Xuhui.

File size: 35.5 KB
Line 
1!    *****************************
2!     calcul de l'indice foliaire
3!           N.Brisson, R. Roche
4!    *****************************
5! *-----------------------------------------------------------------------------------------------------------------------------------------------------------* c!
6!> calculation of the LAI
7!> - Stics book paragraphe 3.1.1, page 40-44
8!>
9!! In STICS, leaf area growth is driven by phasic development, temperature and stresses. An empirical plant density-dependent function represents inter-plant
10!! competition. For indeterminate plants, trophic competition is taken into account through a trophic stress index, while for determinate plants a maximal
11!! expansion rate threshold is calculated to avoid unrealistic leaf expansion.
12!! The calculation of leaf growth rate (deltai in m2m-2 d-1) is broken down: a first calculation of the LAI growth rate (in m2 plant-1 degree-day-1) describes
13!! a logistic curve, related to the ILEV, IAMF and ILAX phenological stages. This value is then multiplied by the effective crop temperature, the plant density
14!! combined with a density factor, supposed to stand for inter-plant competition, that is characteristic for the variety, and the water and nitrogen stress indices.
15!!
16!! The phasic development function is comparable to that of the model PUTU (Singels and Jagger, 1991), i.e. a logistic function with dlaimaxbrut as asymptote
17!! and pentlaimax as the slope at the inflection point. It is driven by a normalized leaf development unit (ULAI) equal to 1 at ILEV and 3 at ILAX.
18!! At the end of the juvenile stage (IAMF), it is equal to vlaimax when the inflection of the dynamics (point of maximal rate) also occurs.
19!! Between the stages ILEV, IAMF and ILAX, the model performs linear interpolation based on development units (upvt) which include all the environmental effects
20!! on phasic development. As the ILAX stage approaches, it is possible to introduce a gradual decline in growth rate using the udlaimax parameter
21!!- the ULAI value beyond which there is a decline in the leaf growth rate. If udlaimax=3 it has no effect and the leaf stops growing at once at ILAX.
22!!
23!! The thermal function relies on crop temperature and cardinal temperatures (tcmin and tcmax) which differ from the ones used for the phasic development.
24!! The extreme threshold tcxstop is the same as for development.
25!!
26!! The density function is active solely after a given LAI threshold occurs (laicomp parameter) if the plant density (densite in plant m-2 possibly decreased
27!! by early frost) is greater than the bdens threshold, below which plant leaf area is assumed independent of density.  Beyond this density value, leaf area
28!! per plant decreases exponentially.  The adens parameter represents the ability of a plant to withstand increasing densities.  It depends on the species
29!! and may depend on the variety.  For branching or tillering plants, adens represents the plant’s branching or tillering ability (e. g. wheat or pea).
30!! For single-stem plants, adens represents competition between plant leaves within a given stand (e.g. maize or sunflower).
31!!
32!! Water and nitrogen affect leaf growth as limiting factors, i.e. stress indices whose values vary between 0 and 1. Water (turfac) and nitrogen deficits (innlai)
33!! are assumed to interact, justifying the use of the more severe of the two stresses. Meanwhile at the whole plant level the water-logging stress index is assumed
34!! to act independently
35!!
36!!
37!!
38!> -    Features of determinate crops
39!!   Failure to account for trophic aspects in the calculation of leaf growth may cause problems when the radiation intercepted by the crop is insufficient to
40!!   ensure leaf expansion (e.g. for crops under a tree canopy or crops growing in winter).  Consequently, from the IAMF stage, we have introduced a trophic effect
41!!  to calculate the definitive LAI growth rate in the form of a maximum threshold for leaf expansion (deltaimaxi in m2m-2d-1) using the notion of the maximum
42!!   leaf expansion allowed per unit of biomass accumulated in the plant (sbvmax in cm2 g-1) and the daily biomass accumulation (dltams in t.ha-1day-1 possibly
43!!   complemented by remobilized reserve remobilj). sbvmax is calculated using the slamax and tigefeuil parameters.
44!!
45!> -    Features of indeterminate crops
46!!   It has been possible to test the robustness of the above formalisation on a variety of crops, including crops where there is an overlap between the
47!!   vegetative phase and the reproductive phase (soybean and flax for example).  However, when trophic competition between leaves and fruits is a driving force
48!!   for the production and management of the crop (for example tomato, sugarbeet), this formalisation is unsuitable.  We therefore calculate the deltai variable
49!!   so as to take trophic monitoring into consideration in the case of crops described as ‘indeterminate’, by introducing a trophic stress index (splai).
50!!   As a consequence, the LAI can decrease markedly during the theoretical growth phase if the crop is experiencing severe stresses during the harvested
51!!   organs filling phase.
52! *-----------------------------------------------------------------------------------------------------------------------------------------------------------* c
53
54
55
56subroutine calai_(turfac,                                                                     & ! IN
57                  udevair,udevcult,n,                                                         & ! IN
58                  nplt,nlev,namf,nlax,ndrp,nrec,upvt,upvtutil,somcour,somcourutp,             & ! IN
59                  densite,tcult,                                                              & ! IN
60                  fstressgel,dltamsen,sla,                                                    & ! IN
61                  dltams, densiteequiv, bsenlai,                                              & ! IN
62                  pdlaisen, lai, pdlai, pdulai, somfeuille, nbfeuille, nsen, nlan,            & ! INOUT
63                  reajust,  ulai, vmax,                                                       & ! INOUT
64                  dltaisenat, laisen, dltaisen, R_stsenlan,                                   & ! INOUT
65                  tustress, efdensite, nstopfeuille, deltai, R_stlaxsen, tempeff, &
66                  histgrowth, hist_sencour, hist_latest, doyhistst) !, &
67!                  nbox, boxulai, boxndays, boxlai, boxlairem,boxtdev, &
68!                  boxbiom,boxbiomrem, boxdurage, boxsomsenbase)
69
70USE Stics
71USE Besoins_en_froid
72implicit none
73
74! 0 DECLARATION
75
76! 0.1 INPUTS
77
78!integer, intent(IN)    :: nbjmax !> la taille des tableaux journaliers 
79!integer, intent(IN)    :: P_codeinnact  !> // PARAMETER // code activating  nitrogen stress effect on the crop: yes (1), no (2) // code 1/2 // PARAM // 0
80!integer, intent(IN)    :: P_codeh2oact  !> // PARAMETER // code to activate  water stress effect on the crop: yes (1), no (2) // code 1/2 // PARAM // 0
81!integer, intent(IN)    :: P_codehypo  !> // PARAMETER // option of simulation of a  phase of hypocotyl growth (1) or planting of plantlets (2) // code 1/2 // PARPLT // 0
82!integer, intent(IN)    :: P_codegermin  !> // PARAMETER // option of simulation of a germination phase or a delay at the beginning of the crop (1) or  direct starting (2) // code 1/2 // PARPLT // 0
83!integer, intent(IN)    :: P_codcueille  !> // PARAMETER // way how to harvest // code 1/2 // PARTEC // 0
84!integer, intent(IN)    :: P_codlainet  !> // PARAMETER // option of calculation of the LAI (1 : direct LAInet; 2 : LAInet = gross LAI - senescent LAI) // code 1/2 // PARPLT // 0
85!integer, intent(IN)    :: codeulaivernal  !>// the value is either 0 (there is not a vernalization) or 1 (there is an effect of vernalization).
86!integer, intent(IN)    :: P_codeindetermin  !> // PARAMETER // option of  simulation of the leaf growth and fruit growth : indeterminate (2) or determinate (1) // code 1/2 // PARPLT // 0
87!integer, intent(IN)    :: P_codeinitprec  !> // PARAMETER // reinitializing initial status in case of chaining simulations : yes (1), no (2) // code 1/2 // PARAM // 0
88!integer, intent(IN)    :: P_codeperenne  !> // PARAMETER // option defining the annual (1) or perenial (2) character of the plant // code 1/2 // PARPLT // 0
89!integer, intent(IN)    :: P_codetemp  !> // PARAMETER // option calculation mode of heat time for the plant : with air temperature (1)  or crop temperature (2) // code 1/2 // PARPLT // 0
90real,    intent(IN)    :: turfac   !> // OUTPUT // Index of turgescence water stress  // 0-1
91!real,    intent(IN)    :: innlai   !> // OUTPUT // Index of nitrogen stress active on leaf growth // P_innmin à 1
92!real,    intent(IN)    :: P_laiplantule  !> // PARAMETER // Plantlet Leaf index at the plantation // m2 leaf  m-2 soil // PARPLT // 1
93!real,    intent(IN)    :: P_phyllotherme  !> // PARAMETER // thermal duration between the apparition of two successive leaves on the main stem // degree C day // PARPLT // 1
94real,    intent(IN)    :: udevair   !> // OUTPUT // Effective temperature for the development, computed with TAIR // degree.days
95real,    intent(IN)    :: udevcult   !> // OUTPUT // Effective temperature for the development, computed with TCULT // degree.days
96!real,    intent(IN)    :: P_dlaimaxbrut  !> // PARAMETER // Maximum rate of the setting up of LAI // m2 leaf plant-1 degree d-1 // PARPLT // 1
97!real,    intent(IN)    :: P_udlaimax  !> // PARAMETER // ulai from which the rate of leaf growth decreases  // SD // PARPLT // 1
98integer, intent(IN)    :: n 
99!integer, intent(IN)    :: numcult 
100integer, intent(IN)    :: nplt 
101integer, intent(IN)    :: nlev 
102integer, intent(IN)    :: namf 
103integer, intent(IN)    :: nlax 
104integer, intent(IN)    :: ndrp 
105integer, intent(IN)    :: nrec 
106real,    intent(IN)    :: upvt   !> // OUTPUT // Daily development unit  // degree.days (calculated in stics_diverse.f90)
107real,    intent(IN)    :: upvtutil  ! (calculated in stics_develop.f90)
108!real,    intent(IN)    :: P_vlaimax  !> // PARAMETER // ULAI  at inflection point of the function DELTAI=f(ULAI) // SD // PARPLT // 1
109!real,    intent(IN)    :: P_laicomp  !> // PARAMETER // LAI from which starts competition inbetween plants // m2 m-2 // PARPLT // 1
110real,    intent(IN)    :: somcour   !> // OUTPUT // Cumulated units of development between two stages // degree.days
111real,    intent(IN)    :: somcourutp 
112!real,    intent(IN)    :: P_stlevamf  !> // PARAMETER // Sum of development units between the stages LEV and AMF // degree.days // PARPLT // 1
113!real,    intent(IN)    :: P_stamflax  !> // PARAMETER // Sum of development units between the stages AMF and LAX // degree.days // PARPLT // 1
114real,    intent(IN)    :: densite   !> // OUTPUT // Actual sowing density // plants.m-2
115!real,    intent(IN)    :: P_adens  !> // PARAMETER // Interplant competition parameter // SD // PARPLT // 1
116!real,    intent(IN)    :: P_bdens  !> // PARAMETER // minimal density from which interplant competition starts // plants m-2 // PARPLT // 1
117!real,    intent(IN)    :: P_tcxstop  !> // PARAMETER // threshold temperature beyond which the foliar growth stops // degree C // PARPLT // 1
118real,    intent(IN)    :: tcult   !> // OUTPUT // Crop surface temperature (daily average) // degree C
119!real,    intent(IN)    :: P_tcmin  !> // PARAMETER // Minimum temperature of growth // degree C // PARPLT // 1
120!real,    intent(IN)    :: P_tcmax  !> // PARAMETER // Maximum temperature of growth // degree C // PARPLT // 1
121!real,    intent(IN)    :: P_pentlaimax  !> // PARAMETER // parameter of the logistic curve of LAI growth  // SD // PARPLT // 1
122!real,    intent(IN)    :: P_dlaimin  !> // PARAMETER // accelerating parameter for the lai growth rate // SD // PARAMV6/PLT // 1
123!real,    intent(IN)    :: exolai   !> // OUTPUT // Index for excess water active on growth in biomass // 0-1   ! at this moment, we do not consider the effects of water logging on LAI
124!real,    intent(IN)    :: P_splaimin  !> // PARAMETER // Minimal value of ratio sources/sinks for the leaf growth  // between 0 and 1 // PARPLT // 1
125!real,    intent(IN)    :: P_splaimax  !> // PARAMETER // maximal sources/sinks value allowing the trophic stress calculation for leaf growing // SD // PARPLT // 1
126!real,    intent(IN)    :: P_slamin  !> // PARAMETER // minimal SLA of green leaves // cm2 g-1 // PARPLT // 1
127!real,    intent(IN)    :: P_slamax  !> // PARAMETER // maximal SLA of green leaves // cm2 g-1 // PARPLT // 1
128!real,    intent(IN)    :: P_tigefeuil  !> // PARAMETER // stem (structural part)/leaf proportion // SD // PARPLT // 1
129!real,    intent(IN)    :: P_tustressmin  !> // PARAMETER //  threshold stress (min(turfac,inns)) under which there is an effect on the LAI (supplementary senescence by ratio at the natural senescence)
130real,    intent(IN)    :: fstressgel   !> // OUTPUT // Frost index on the LAI // 0-1
131real,    intent(IN)    :: dltamsen   !> // OUTPUT // Senescence rate // t ha-1 j-1
132real,    intent(IN)    :: sla   !> // OUTPUT // Specific surface area // cm2 g-1
133real,    intent(IN)    :: dltams                ! (n-1)    // OUTPUT // Growth rate of the plant  // t ha-1.j-1
134real,    intent(IN)    :: densiteequiv  !densite equivalente calculée chaque jour
135real,    intent(IN)    :: bsenlai      ! lai value at date nsen, when the sen begin
136
137! 0.2 INOUT
138
139real,    intent(INOUT) :: pdlaisen          ! senescence leaf area index of the previous day // Leaf area index (table) // m2 leafs  m-2 soil//
140real,    intent(INOUT) :: lai            ! (n), (n-1), (nsen), (nlan)    // OUTPUT // Leaf area index (table) // m2 leafs  m-2 soil// in this version, there is no time dimension
141real,    intent(INOUT) :: pdlai          ! leaf area index of the previous day // Leaf area index (table) // m2 leafs  m-2 soil//
142real,    intent(INOUT) :: pdulai          ! leaf area index of the previous day // Leaf area index (table) // m2 leafs  m-2 soil//
143real,    intent(INOUT) :: somfeuille 
144integer, intent(INOUT) :: nbfeuille   !> // OUTPUT // Number of leaves on main stem // SD
145integer, intent(INOUT) :: nsen 
146integer, intent(INOUT) :: nlan 
147!real,    intent(INOUT) :: P_dlaimax  !> // PARAMETER // Maximum rate of the setting up of LAI // m2 leaf plant-1 degree d-1 // PARPLT // 1
148real,    intent(INOUT) :: reajust 
149real,    intent(INOUT) :: ulai         !> // Daily relative development unit for LAI // 0-3
150real,    intent(INOUT) :: vmax 
151real,    intent(INOUT) :: dltaisenat 
152real,    intent(INOUT) :: laisen        ! (n), (n-1)    // OUTPUT // Leaf area index of senescent leaves // m2 leafs  m-2 soil
153real,    intent(INOUT) :: dltaisen   !> // OUTPUT // Daily increase of the senescent leaf index // m2.m-2 sol.j-1
154real,    intent(INOUT) :: R_stsenlan  !> // PARAMETER // Sum of development units between the stages SEN et LAN // degree.days // PARPLT // 1
155
156  real, dimension(300,5), intent(INOUT) :: histgrowth
157  integer, intent(INOUT)                :: hist_sencour
158  integer, intent(INOUT)                :: hist_latest
159  integer, intent(INOUT)                :: doyhistst
160
161! 0.3 OUT
162
163real,    intent(OUT)   :: tustress   !> // OUTPUT // Stress index active on leaf growth (= minimum(turfac,innlai))  // 0-1
164real,    intent(OUT)   :: efdensite 
165integer, intent(OUT)   :: nstopfeuille 
166real,    intent(OUT)   :: deltai                ! (n)    --(0:nbjmax)    // OUTPUT // Daily increase of the green leaf index // m2 leafs.m-2 soil
167!real,    intent(OUT)   :: splai   !> // OUTPUT // Pool/sink ratio applied to leaves // 0-1
168!real,    intent(OUT)   :: fpv   !> // OUTPUT // Sink strength of developing leaves // g.j-1.m-2
169real,    intent(OUT)   :: R_stlaxsen  !> // PARAMETER // Sum of development units between the stages LAX and SEN // degree.days // PARPLT // 1
170real,    intent(OUT)   :: tempeff   !> // OUTPUT // Efficient temperature for growth // degree C
171
172! 0.4 LOCAL VARIABLES
173real :: deltaimaxi 
174real :: sbvmin 
175real :: sbvmax 
176
177real :: tdevelop 
178!integer :: ii
179
180!: 0. Assignments of the historical variables
181!---------------------------------------------------------------
182   
183    ! assignment of the historical variables
184    pdlai = lai
185    pdulai = ulai
186    pdlaisen = laisen
187
188
189!: 1. CALCULATION THE STRESS FACTOR (no problem)
190!--------------------------------------
191
192    if (P_codeinnact == 1 .and. P_codeh2oact == 1) then
193      tustress = min(turfac,P_innlai)
194    endif
195    if (P_codeinnact == 2 .and. P_codeh2oact == 1) then
196      tustress = min(turfac,1.0)
197    endif
198    if (P_codeinnact == 1 .and. P_codeh2oact == 2) then
199      tustress = min(1.0,P_innlai)
200    endif
201    if (P_codeinnact == 2 .and. P_codeh2oact == 2) then
202      tustress = 1.
203    endif
204
205!print *, 'wu: in calai process the tustress is', tustress
206
207!: 2. INITIALIZATIONS OF SOME VARIABLES BEFORE EMERGENCE (done)
208!-------------------------------------------------
209
210!: Dans le cas des cultures annuelles (P_codeperenne=1), trois cas:
211!
212!- a) pour les cultures qui se plantent (P_codehypo=2) et admettent un
213!-    temps de latence avant le demarrage de la croissance (P_codegermin=1):
214!-    initialisation du lai a P_laiplantule a partir de la plantation;
215!-    et calcul de QNPlante par courbe de dilution
216!-
217!- b) pour les cultures qui se sement (P_codehypo=1):
218!-    initialisation du lai a 0 a partir du semis
219!-
220!- c) pour les cultures qui se plantent (P_codehypo=2) et demarrent directement (P_codegermin=2):
221!-    initialisation du lai a P_laiplantule a partir de la levee qui est aussi la plantation
222!-------------------------------------------------
223! in the case of annual crop, 3 cases:
224!
225! a) for crops that are planted (P_codehypo = 2) and admit a latency before startup growth (P_codegermin = 1):
226!    initialization lai P_laiplantule from planting; and calculating by dilution curve QNPlante
227!
228! b) for crops that are sowed  (P_codehypo = 1): initialization lai 0 from sowing
229!
230! c) for crops that are planted (P_codehypo = 2) and been booted directly (P_codegermin = 2):
231!    initialization lai P_laiplantule from the levee
232!------------------------------------------------
233
234
235!    print *, 'dltams before calculate the lai is', dltams
236!    print *, 'in calai the nsen is,', nsen
237
238    if (nlev == 0) then
239
240      if (P_codeperenne == 1 .and. n >= nplt) then  !- NPLT étant non nul dès le depart de la simulation, on test n>=nplt
241        if (P_codehypo == 2 .and. P_codegermin == 1) then ! a)
242          !lai(n) = P_laiplantule
243          lai = P_laiplantule
244          return
245        else ! b)
246          lai = 0.
247          !lai(n) = 0.
248          return
249        endif
250      else
251        !lai(n) = 0.0
252        lai = 0.0
253        return
254        !: TODO - le somfeuille=0 après le return est inutile, il n'est jamais exécuté. BUG ?
255        somfeuille = 0.
256      endif
257    endif
258
259    ! le jour de la levée, si plantation par plantule, on force le lai du jour précédent
260    if (n == nlev .and. P_codehypo == 2 .and. namf == 0) then
261      !lai(n-1) = P_laiplantule
262      pdlai = P_laiplantule   ! // pdlai lai of previous day
263    endif
264
265    !: à la récolte (nrec+1)
266    !:
267    if (nrec > 0 .and. n > nrec) then
268      ! En cas de moisson, on enlève les feuilles.
269      if (P_codcueille == 1) then ! havest the whole plant (1) or only the fruit (2)
270        !lai(n) = 0.
271        lai = 0.
272        somfeuille = 0.
273        return
274      endif
275    endif
276
277    !: Calcul du nombre de feuilles
278    !: calculation of number of leaves
279    if (P_codetemp == 2) then ! p_codetemp == 2 indicate that we use the crop temperature
280      call CalculNombreDeFeuilles(nlax,udevcult,somfeuille,nbfeuille)
281    else
282      call CalculNombreDeFeuilles(nlax,udevair,somfeuille,nbfeuille)
283    endif
284
285!    print *, 'wu: in calai process the nlev, ndrp, nlax, nsen are', nlev, ndrp, nlax, nsen
286!    print *, 'wu: in calai process the nbfeuille is', nbfeuille
287
288    !: si option LAI brut+ sénescence
289    !if (P_codlainet == 2) P_dlaimax = P_dlaimaxbrut
290
291    !: 2a) calcul de reajust : distance de développement pour réajuster
292    !-     les parcours observés
293
294    ! reinitialization of the sum of upvt
295    if (n == nlev) reajust = 0.0
296    if (n == namf) reajust = 0.0
297    if (n == nlax) reajust = 0.0
298    if (n == nsen) reajust = 0.0
299    if (n == nlan) reajust = 0.0
300
301    reajust = reajust + upvt - upvtutil 
302   
303!    print *, 'wu: in calai process the reajust is', reajust
304   
305
306    !: 2b) lai de départ non nul pour les cultures qui se plantent
307    !--      if (n == nlev .and. P_codehypo == 2 .and. namf == 0) then
308    !--        lai(n-1) = P_laiplantule
309    !--!: NB - le 21/04 - sbv remplacé par slavert
310    !--        ms(n-1) = lai(n-1)/P_slamin*100.0
311    !--!: NB - ajout de P_QNplante0 - le 21/04
312    !--        QNplante = (P_adilmax * ms(n-1) * 10) + P_QNplante0
313    !--        QNplantetot = QNplante
314    !--        inns =  1.0
315    !--        inn  =  1.0
316    !--        innlai  =  1.0
317    !--      endif
318
319
320!: 3. CALCUL DE ULAI
321!-------------------
322    !: 3a) calcul de ulai entre lev et amf
323    !- domi - 29/03 la vernalisation ne joue pas sur ulai si codeulaivernal = 1
324    if (nlev > 0 .and. namf == 0) then
325      if (codeulaivernal == 1) then
326        !ulai(n) = 1 + (P_vlaimax - 1) * (somcour + reajust) / (P_stlevamf + reajust)
327        ulai = 1 + (P_vlaimax - 1) * (somcour + reajust) / (P_stlevamf + reajust)
328      else
329        if (somcourutp <= P_stlevamf) then
330!          print *, 'in lai the somcourutp is,', somcourutp
331          !ulai(n) = 1 + (P_vlaimax - 1) * (somcourutp + reajust) / (P_stlevamf + reajust)
332          ulai = 1 + (P_vlaimax - 1) * (somcourutp + reajust) / (P_stlevamf + reajust)
333        else
334          !ulai(n) = ulai(n-1)
335          ulai = pdulai
336        endif
337      endif
338    endif
339 
340
341!    print *, 'wu: in calai process the ulai is', ulai
342
343    !: 3b) calcul de ulai entre amf et lax
344   
345    if (namf > 0 .and. nlax == 0) then
346     
347      if (codeulaivernal == 1) then
348        !ulai(n) = P_vlaimax + (3 - P_vlaimax) * (somcour + reajust) / (P_stamflax + reajust)
349        ulai = P_vlaimax + (3 - P_vlaimax) * (somcour + reajust) / (P_stamflax + reajust)
350      else
351        if (somcourutp <= P_stamflax) then
352          !ulai(n) = P_vlaimax + (3 - P_vlaimax) * (somcourutp + reajust) / (P_stamflax + reajust)
353          ulai = P_vlaimax + (3 - P_vlaimax) * (somcourutp + reajust) / (P_stamflax + reajust)         
354 
355        else
356          !ulai(n) = ulai(n-1)
357          ulai = pdulai
358
359        endif
360      endif
361
362    endif
363
364!    print *, 'wu: in calai process the ulai is', ulai
365
366    !: 3c) ulai maximal atteint à drp pour les indéterminées
367    if (P_codeindetermin == 2 .and. ndrp > 0) then
368      !ulai(n) = P_udlaimax
369      ulai = P_udlaimax
370    else
371      if (nlax > 0) ulai = P_udlaimax     !ulai(n) = P_udlaimax
372    endif
373
374   
375
376!: 4. CALCUL du DELTAI BRUT
377!--------------------------
378
379    !: 4a) calcul du facteur densité efdensite actif à partir de P_laicomp
380    !- calcul de l'effet densité sur la mise en place du LAI pour les stics-plante
381
382    !: calculation of the effective density, to address the density effects on LAI development
383
384    efdensite = 1.
385    !if (ulai(n) > 1.) then
386    if (ulai > 1.) then 
387      !if (lai(n-1) < P_laicomp) then
388      if (pdlai < P_laicomp) then
389        efdensite = 1.
390      else
391        if (densite == 0) then
392          efdensite = 0.0
393        else
394          ! domi - 02/07/2002 - pb si gel total densite  = 0 et pb de log(0)
395          ! efdensite = min(1.0,(exp(P_adens * (log(densite / P_bdens)))))
396          ! DR 12/09/2012 on prend la densite equivalente pour calculer l'effet densite et uniquement pour ca !
397          efdensite = min(1.0,(exp(P_adens * (log(densiteequiv / P_bdens)))))
398        endif
399      endif
400    else
401      ! domi - 02/07/2002 - pb si gel total densite  = 0 et pb de log(0)
402      if (densite == 0) then
403        efdensite = 0.0
404      else
405        !efdensite = min(1.0,(exp(P_adens * log(densite / P_bdens))))
406        !DR 12/09/2012 on prend la densite equivalente pour calculer l'effet densite et uniquement pour ca !
407        efdensite = min(1.0,(exp(P_adens * log(densiteequiv / P_bdens))))
408      endif
409    endif
410
411    !if (ulai(n) == 1.0) efdensite = 1
412    if (ulai == 1.0) efdensite = 1.
413
414!    print *, 'wu: in calai process the efdensite is', efdensite
415
416    ! ** 4b) température efficace de croissance: limitation par P_tcmax
417    ! NB le 13/06/06
418    ! introduction d'une température maximale d'arrêt de croissance
419    ! foliaire P_Tcxstop à l'occasion étude Françoise sur fourrages méditerranéens
420    !      P_tcxstop = 30.0
421
422    !: addressing the effective temperature
423
424
425    if (P_tcxstop >= 100.0) then
426      if (tcult > P_tcmax) then
427        tempeff = max(0.,(P_tcmax - P_tcmin))
428      else
429        tempeff = max(0.,(tcult - P_tcmin))
430      endif
431    else
432      if (tcult > P_tcmax) then
433        tempeff = (P_tcmax - P_tcmin) / (-P_tcxstop + P_tcmax) * (tcult - P_tcxstop)
434        tempeff = max(0.,tempeff)
435      else
436        tempeff = max(0.,(tcult - P_tcmin))
437      endif
438    endif
439
440!    print *, 'wu: in calai process the tempeff is', tempeff
441
442    !: 4c) calcul du deltai
443    !- quelle que soit l'option LAI choisie, LAI net ou LAI brut :
444    !-  * la croissance s'arrête à LAX pour les déterminées
445    !-  * la croissance s'arrête à SEN pour les indéterminées
446    if (P_codeindetermin == 1) nstopfeuille = nlax
447    if (P_codeindetermin == 2) nstopfeuille = nsen
448
449    if (P_codlainet == 2) nstopfeuille = nlax
450    if (P_codlainet == 3) nstopfeuille = nlax
451
452!    print *, 'wu: in calai process the nstopfeuille is', nstopfeuille
453!    print *, 'wu: in calai process the densite is', densite
454    if ( nstopfeuille .eq. 0 ) then
455 
456!    print *, 'wu: in calai process, do we go in? if so the ulai is', ulai
457
458      !: modif le 23/07/01
459      !- entre ulai = 1 et ulai = P_udlaimax, la vitesse est croissante
460      !- NB - le 13/12
461
462      !if (ulai(n) <= P_udlaimax .or. P_udlaimax == 3.0) then
463      if (ulai <= P_udlaimax .or. P_udlaimax == 3.0) then
464
465        ! DR 07/03/08 integration des modifs du 28/02/07 P_dlaimax n'etait actif
466        ! et introduction de P_codedlaimin
467        ! NB et FR le 28/02/07
468        ! introduction d'une ordonnée à l'origine pour la croissance des feuilles
469        ! DR on vire le P_codedlaimin et on met P_dlaimin dans le fichier plante
470 
471        deltai = P_dlaimax * efdensite * densite &
472                  * (P_dlaimin + (1.0 - P_dlaimin) / (1 + exp(P_pentlaimax * (P_vlaimax - ulai))))
473        vmax = deltai
474      else
475        !: entre P_udlaimax = 1 et ulai = 3(lax), la vitesse est décroissante
476        !- sauf pour les indéterminées
477        ! DR 24/01/2011 on a un pb dans l'equation la puissance multiplie tout (eq 3.2 bouquin)
478
479        !deltai = vmax * (1 - (ulai(n) - P_udlaimax) / (3.0 - P_udlaimax))**2
480        deltai = vmax * (1 - (ulai - P_udlaimax) / (3.0 - P_udlaimax))**2
481
482      endif
483
484
485
486
487      !: NB - le 28/05 - on lève toujours
488      !- 10/01 - ajout d'un test sur l'enchainement des perennes
489      ! TODO: voir si on pourrait remplacer ce test par un booléen qui dirait si la plante a levé ou pas. ex: *if (isLevee) then*
490
491      !if (n > nlev .or. (P_codeperenne == 2 .and. P_codeinitprec == 2 .and. numcult > 1)) then
492      if (nlev > 0 .or. (P_codeperenne == 2 .and. P_codeinitprec == 2)) then
493
494        !: NB le 07/06 introduction de exolai
495        !: At this moment, we do not consider the limiting effects of exolai--xcwu
496 
497        deltai = deltai * tempeff * tustress * exolai
498
499      endif
500
501      !: la croissance foliaire des plantes indéterminées dépend
502      !- du rapport source/puits des organes végétatifs
503
504      ! At this moment, we do not consider the perennial crop or indeterminant crops---xcw
505
506      !if (P_codeindetermin == 2) then
507
508      !  splai = (sourcepuits - P_splaimin) / (P_splaimax - P_splaimin)
509
510      !  splai = max(splai,0.0)
511      !  splai = min(splai,1.0)
512
513      !  ! NB le 21/04 recalcul d'un sbv approprié
514      !  sbvmin = P_slamin / (1.0 + P_tigefeuil)
515      !  fpv = deltai * splai * 1e4 / sbvmin
516      !  deltai  =  deltai*splai
517
518      !else
519     
520      if (P_codeindetermin == 1) then       ! determinant crop case
521 
522        !: limitation si le rayonnement est vraiment insuffisant
523        !- après AMF (cas des cultures associées)
524        !- NB le 21/04 recalcul d'un sbv approprié
525        !- NB le 15/05/02 calcul de fpv pour les pérennes
526
527        sbvmin = P_slamin / (1.0 + P_tigefeuil)
528        !fpv = deltai * 1e4 / sbvmin
529        sbvmax = P_slamax / (1.0 + P_tigefeuil)
530
531        !: ajout des remobilisations possible pour faire redémarrer le
532        !- lai en cas de couvert complètement sec
533        !- NB le 13/06/06
534        !- NB le 27/06/06 attention delatremobil était déjà compté dans dltams
535       
536        ! at this moment, we do not consider the remobilization,
537        ! we adjust the process
538        ! original process as following:
539        ! deltaimaxi = (dltams + remobilj) * sbvmax / 100.
540        ! adjusted processes as following:
541
542        deltaimaxi = dltams * sbvmax / 100. ! unit in m2 m-2
543   
544!        print *, 'in calai the dltams and sbvmax and deltaimaxi is:', dltams, sbvmax, deltaimaxi
545!        print *, 'in calai the dltams and sbvmin and deltaimini is:', dltams * sbvmin / 100.   
546        if (namf > 0) then
547          deltai = min(deltai,deltaimaxi)
548          !deltai = deltai   ! test
549        endif
550      endif
551      ! fin nstopfeuille = 0
552    else
553      deltai = 0.0
554    endif
555
556
557!    print *, 'xuhui: n ', n
558!    print *, 'xuhui: nlev ', nlev
559! xuhui: record the historical growth of lai for calculation of senescence
560    if (P_codlainet==2) then
561        if (nlev > 0) then ! leaf growth have initiated
562            if (doyhistst == 0 .and. hist_sencour == 0) then ! history has not been intialized
563                doyhistst = n
564                hist_sencour = 1
565                hist_latest = 1
566!                print *, 'xuhui: histgrowth initiated'
567            else  ! history already initialized
568                hist_latest = hist_latest + 1
569!                print *, 'xuhui: histlatest: ',hist_latest
570            endif
571    !        histgrowth(hist_latest,6) = n
572            histgrowth(hist_latest,1) = deltai
573            if (hist_latest>1) then
574                histgrowth(hist_latest-1,2) = dltams  !! dltams in this routin is from yesterday
575            endif
576            if (P_codetemp == 2) then
577                tdevelop = 2.0 ** (udevcult / 10.)
578            else
579                tdevelop = 2.0 ** (udevair / 10.)
580            endif
581            ! according to STICS book, tdevelop should be 2.0 **
582            ! (udevcult*(stressdev*min(turfac, innlai) + 1 - stressdev)/10.)
583            ! however, the code of v6.0 did not have this process, considering
584            ! adding it into the calculation
585            histgrowth(hist_latest,3) = tdevelop
586            histgrowth(hist_latest,4) = ulai
587            ! histgrowth(:,5) is durvie, added in the senescence subroutine
588!            print *, 'xuhui: histgrowth in ',hist_latest, ': ', histgrowth(hist_latest,:)
589        endif
590    elseif (P_codlainet==3) then
591!        if (ulai < 1 .or. ulai > 3) then
592!            write(*,*) 'xuhui: ulai: ', ulai, ', likely a bug'
593!        else
594!            ii = nbox
595!            do while (ulai < ulaibox(ii))
596!                ii = ii - 1
597!            enddo
598!            if (ii < 1) then
599!                write(*,*) 'xuhui: bug: ii<1'
600!                ii = 1
601!            endif
602!            boxndays(ii) = boxndays(ii) + 1
603!            boxlai(ii) = boxlai(ii) + deltai
604!            boxlairem(ii) = boxlairem(ii) + deltai
605!            boxbiom(ii) = boxbiom(ii) + dltams
606!            boxbiomrem(ii) = boxbiomrem(ii) + dltams
607!            if (P_codetemp == 2) then
608!                tdevelop = 2.0 ** (udevcult / 10.)
609!            else
610!                tdevelop = 2.0 ** (udevair / 10.)
611!            endif
612!            boxtdev(ii) = boxtdev(ii) + tdevelop
613!        endif
614    endif
615! end xuhui
616
617!: 5. PHASE DE PLATEAU  (si option lainet et culture determinée)
618!---------------------------------------------------------------
619
620    if (P_codlainet == 1 .and. P_codeindetermin == 1) then
621      if (nlax > 0 .and. nsen == 0) deltai = 0.0
622    endif
623
624!: 6. Calcul de la senescence rapide par ajustement a la récolte
625!- entre sen et lan  pour les options 1 et 2
626!: calculation the lai according to two options
627!---------------------------------------------------------------
628
629    if (P_codlainet <= 1) then ! the P_codlainet is either 1 or 2, so here it is the direct calculation of LAI
630
631          !lai(n) =  lai(n-1) + deltai - dltaisenat  ! the calculation of dltaisenat is shown below
632          lai = pdlai + deltai - dltaisenat
633   
634
635          !if (n == nsen) lai(n) = lai(n-1)
636          if (n == nsen) lai = pdlai    ! in this date, the senescence is 0
637 
638          if (nsen > 0 .and. nlan == 0.) then
639
640            !lai(n) = lai(nsen) * (1 - ((somcour+reajust) / (R_stsenlan+reajust)))  !
641            lai = bsenlai * (1 - ((somcour+reajust) / (R_stsenlan+reajust + 80.0)))     ! there is decreasing lai, 80 is an offset
642           
643 
644            !dltaisenat = lai(n-1) - lai(n)
645            dltaisenat = pdlai - lai
646            !if (lai(n) <= 0.0 .and. nlan == 0)  nlan = n
647            if (lai <= 0.0 .and. nlan == 0) nlan = n
648            !if (n == nlan) lai(nlan) = 0.0
649            if (n == nlan) lai = 0.0    ! if n == nlan, lai(nlan) is the same as lai(n) , so lai = 0.0
650
651          endif
652     else
653          !: option LAI brut la sénescence (dltaisen) est calculé dans le spg senescen
654          !lai(n) = lai(n-1) + deltai - dltaisen  ! we do not consider the net calculation, so...
655          lai = pdlai + deltai - dltaisen
656     endif
657
658    !if (lai(n) < 0.) then
659    if (lai < 0.0) then
660      !lai(n) = 0.
661      lai = 0.0
662
663      ! DR 06/09/06 y'a un soucis car alors laisen ne prend pas en compte la derniere valeur de lai
664      !--dltaisen = 0.0
665    endif
666
667    ! NB - le 22/04 - à cause précisison dans les soustractions
668    !if (lai(n) <= 1e-4 .and. nstopfeuille > 0) then
669    !  lai(n) = 0.
670    !endif
671
672    if (lai <= 1e-4 .and. nstopfeuille > 0) then
673       lai = 0.0
674    endif
675
676!: 7. senescence foliaire due à des stress  pour l'option LAInet
677!: Addressing the senescence of lai, see senescen.f90
678!---------------------------------------------------------------
679
680    !if (P_codlainet == 1 .and. lai(n) > 0.0) then
681    if (P_codlainet == 1 .and. lai > 0.0) then
682   
683      if (tustress < P_tustressmin .or. tcult < P_tcmin .or. fstressgel < 1.0) then    ! there seems to be an additional part of senescence for LAI, representing by dltamsen/100*sla
684        ! bug dans l'opération NB le 08/05
685
686        dltaisen = dltamsen * sla * 100.   ! unit in m2 m-2
687       
688
689        ! how can we calculate the sla, it is calculated in biomass allocation processes; ---repartir.f90
690        ! the calculation of sla is determined by the tursla.
691
692        !lai(n) = lai(n) - dltaisen
693        lai = lai - dltaisen
694        dltaisen = dltaisen + dltaisenat
695        lai = max(lai, 0.0)
696 
697      else
698        dltaisen = dltaisenat
699      endif
700    endif
701
702    !laisen(n) = laisen(n-1) + dltaisen
703    laisen = pdlaisen + dltaisen 
704
705
706    !: NB le 22/04: calcul du stade lan pour P_codlainet = 2
707    !if (lai(n) <= 0 .and. nlan == 0 .and. nlax > 0) then
708    if (lai <= 0.0 .and. nlan == 0 .and. nlax > 0) then
709      if (nsen == 0) then
710        nsen = n
711        R_stlaxsen = somcour
712
713      endif
714      nlan = n
715      R_stsenlan = somcour
716      !lai(n) = 0.0      ! 07/06
717      lai = 0.0
718      dltaisen = 0.0
719      dltaisenat = 0.0 ! NB le 11/06
720    endif
721   
722
723return
724end subroutine calai_
Note: See TracBrowser for help on using the repository browser.