source: branches/publications/ORCHIDEE-PEAT_r5488/src_stomate/stomate_phenology.f90 @ 5491

Last change on this file since 5491 was 4806, checked in by chunjing.qiu, 7 years ago

orchi-peat based on r4229

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 98.4 KB
Line 
1! =================================================================================================================================
2! MODULE        : stomate_phenology
3!
4! CONTACT       : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE       : IPSL (2006). This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8!>\BRIEF        This module manages the beginning of the growing season (leaf onset).
9!!     
10!!\n DESCRIPTION: None
11!!
12!! RECENT CHANGE(S): None
13!!
14!! SVN          :
15!! $HeadURL$
16!! $Date$
17!! $Revision$
18!! \n
19!_ =================================================================================================================================
20
21MODULE stomate_phenology
22
23  ! modules used:
24  USE xios_orchidee
25  USE ioipsl_para
26  USE stomate_data
27  USE constantes
28  USE pft_parameters
29
30  IMPLICIT NONE
31
32  ! private & public routines
33
34  PRIVATE
35  PUBLIC phenology,phenology_clear
36
37  ! first call
38  LOGICAL, SAVE                                              :: firstcall_all_phenology = .TRUE.
39!$OMP THREADPRIVATE(firstcall_all_phenology)
40  LOGICAL, SAVE                                              :: firstcall_hum = .TRUE.
41!$OMP THREADPRIVATE(firstcall_hum)
42  LOGICAL, SAVE                                              :: firstcall_moi = .TRUE.
43!$OMP THREADPRIVATE(firstcall_moi)
44  LOGICAL, SAVE                                              :: firstcall_humgdd = .TRUE.
45!$OMP THREADPRIVATE(firstcall_humgdd)
46  LOGICAL, SAVE                                              :: firstcall_moigdd = .TRUE.
47  LOGICAL, SAVE                                              :: firstcall_moi_C4 = .TRUE.
48!$OMP THREADPRIVATE(firstcall_moigdd)
49!!!qcj++ peatland
50  LOGICAL, SAVE                                              :: firstcall_siggdd= .TRUE.
51
52CONTAINS
53
54
55!! ================================================================================================================================
56!! SUBROUTINE   : phenology_clear
57!!
58!>\BRIEF          Flags setting   
59!!
60!! DESCRIPTION  : This subroutine sets flags
61!!                ::firstcall_all_phenology, ::firstcall_hum, ::firstcall_moi, ::firstcall_humgdd,
62!!                ::firstcall_moigdd to .TRUE., and therefore activates section 1.1 of each
63!!                subroutine which writes messages to the output. \n
64!!                This subroutine is called at the beginning of ::stomateLpj_clear in the
65!!                ::stomate_lpj module.
66!!
67!! RECENT CHANGE(S): None
68!!
69!! MAIN OUTPUT VARIABLE(S): ::firstcall_all_phenology, ::firstcall_hum, ::firstcall_moi, ::firstcall_humgdd,
70!!                ::firstcall_moigdd
71!!
72!! REFERENCE(S)  : None
73!!
74!! FLOWCHART     : None
75!! \n
76!_ ================================================================================================================================
77
78  SUBROUTINE phenology_clear
79    firstcall_all_phenology=.TRUE.
80    firstcall_hum=.TRUE.
81    firstcall_moi = .TRUE.
82    firstcall_humgdd = .TRUE.
83    firstcall_moigdd = .TRUE.
84    firstcall_moi_C4 = .TRUE.
85    firstcall_siggdd= .TRUE.
86  END SUBROUTINE phenology_clear
87
88
89!! ================================================================================================================================
90!! SUBROUTINE   : phenology
91!!
92!>\BRIEF          This subroutine controls the detection of the beginning of the growing season
93!!                (if dormancy has been long enough), leaf onset, given favourable biometeorological
94!!                conditions, and leaf growth and biomass allocation when leaf biomass is low (i.e.
95!!                at the start of the growing season.
96!!
97!! DESCRIPTION  : This subroutine is called by the module ::stomate_lpj and deals with the beginning of the 
98!!                growing season. First it is established whether the beginning of the growing season is
99!!                allowed. This occurs if the dormance period has been long enough (i.e. greater
100!!                than a minimum PFT-dependent threshold, specified by ::lowgpp_time),
101!!                AND if the last beginning of the growing season was a sufficiently long time ago
102!!                (i.e. when the growing season length is greater than a minimum threshold, specified
103!!                by ::min_growthinit_time, which is defined in this module to be 300 days. \n
104!!                The dormancy time-length is represented by the variable
105!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
106!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
107!!                it is set to zero. \n
108!!                ::lowgpp_time is set for each PFT in ::stomate_data from a table of all
109!!                PFT values (::lowgpp_time_tab), which is defined in ::stomate_constants. \n
110!!                The growing season length is given by ::when_growthinit, which increases
111!!                by the stomate time-step at each call to this phenology module, except for when
112!!                leaf onset is detected, when it is set to 0. \n
113!!                If these two conditions are met, leaf onset occurs if the biometeorological
114!!                conditions are also met. This is determined by the leaf onset models, which are
115!!                biome-specific. Each PFT is looped over (ignoring bare soil).
116!!                The onset phenology model is selected, (according to the parameter
117!!                ::pheno_model, which is initialised in stomate_data), and called. \n
118!!                There are six leaf onset phenology models currently being used by ORCHIDEE.
119!!                These are: 'hum' and 'moi', which are based exclusively on moisture conditions,
120!!                'humgdd' and 'moigdd', which are based on both temperature and moisture conditions,
121!!                'ncdgdd', which is based on a "chilling" requirement for leaf onset, and
122!!                'ngd', which is based on the number of growing days since the temperature was
123!!                above a certain threshold, to account for the end of soil frost.
124!!                Those models which are based mostly on temperature conditions are used for
125!!                temperate and boreal biomes, and those which include a moisture condition are used
126!!                for tropical biomes. More detail on the biometeorological conditions is provided
127!!                in the sections on the individual onset models. \n
128!!                The moisture conditions are based on the concept of plant "moisture availability".
129!!                This is based on the soil humidity (relative soil moisture), but is moderated by
130!!                the root density profile, as per the equation:
131!!                \latexonly
132!!                \input{phenology_moiavail_eqn1.tex}
133!!                \endlatexonly
134!!                \n
135!!                Although some studies have shown that the length of the photoperiod is important
136!!                in determining onset (and senescence) dates, this is not considered in the current
137!!                versions of the onset models (Krinner et al., 2005). \n
138!!                If conditions are favourable, leaf onset occurs (::begin_leaves is set to TRUE),
139!!                ::when_growthinit is set to 0.0, and the growing season has begun. \n
140!!                Following the detection of leaf onset, biomass is allocated from the carbohydrate
141!!                reserves equally to the leaves and roots IF the leaf biomass is lower than a minimum
142!!                threshold, which is calculated in this subroutine from the parameter
143!!                ::lai_initmin, divided by the specific leaf area (both of which are
144!!                PFT-dependent and set in ::stomate_constants). \n
145!!                Finally, if biomass is required to be allocated from the carbohydrate reserve
146!!                because the leaf biomass is too low, the leaf age and leaf age distribution is
147!!                re-set. In this case the youngest age class fraction is set to 1 and all other   
148!!                leaf age class fractions are set to 0. All leaf ages are set to 0. If there is
149!!                no biomass in the carbohydrate reserve, leaf onset will not occur and the PFT
150!!                will disappear from the grid cell (Krinner et al., 2005). \n
151!!                This subrouting is called in ::stomate_lpj.
152!!
153!! RECENT CHANGE(S): None
154!!
155!! MAIN OUTPUT VARIABLE(S): ::biomass,
156!!                        ::when_growthinit,
157!!                        ::leaf age distribution
158!!                        ::leaf fraction
159!!
160!! REFERENCE(S) :
161!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
162!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
163!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
164!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
165!!
166!! FLOWCHART    :
167!! \latexonly
168!! \includegraphics[scale = 1]{phenology_flowchart.png}
169!! \endlatexonly
170!! \n
171!_ ================================================================================================================================
172
173  SUBROUTINE phenology (npts, dt, PFTpresent, &
174       veget_max, &
175       t2m_longterm, t2m_month, t2m_week, gpp, &
176       maxmoiavail_lastyear, minmoiavail_lastyear, &
177       moiavail_month, moiavail_week, &
178       gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
179       senescence, time_hum_min, &
180       biomass, leaf_frac, leaf_age, &
181       when_growthinit, co2_to_bm, &
182       pdlai, slai, deltai, ssla, & !added for crops, xuhui
183       begin_leaves, &!)
184!gmjc
185       sla_calc)
186!end gmjc
187
188    !
189    !! 0. Variable and parameter declaration
190    !
191
192    !
193    !! 0.1 Input variables
194    !
195    INTEGER(i_std), INTENT(in)                                          :: npts                 !! Domain size - number of grid
196                                                                                                !! cells (unitless)
197    REAL(r_std), INTENT(in)                                             :: dt                   !! time step (dt_days)
198    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                            :: PFTpresent           !! PFT exists (true/false)
199    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: veget_max            !! "maximal" coverage fraction of a
200                                                                                                !! PFT (LAI -> infinity) on ground
201                                                                                                !! (0-1, unitless)
202    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: t2m_longterm         !! "long term" 2 meter reference
203                                                                                                !! temperatures (K)
204    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: t2m_month            !! "monthly" 2-meter temperatures
205                                                                                                !! (K)
206    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: t2m_week             !! "weekly" 2-meter temperatures (K)
207    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: gpp                  !! daily gross primary productivity
208                                                                                                !! @tex ($gC m^{-2} of
209                                                                                                !! ground/day$) @endtex
210    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: maxmoiavail_lastyear !! last year's maximum moisture
211                                                                                                !! availability (0-1, unitless)
212    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: minmoiavail_lastyear !! last year's minimum moisture
213                                                                                                !! availability (0-1, unitless)
214    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: moiavail_month       !! "monthly" moisture availability
215                                                                                                !! (0-1, unitless)
216    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: moiavail_week        !! "weekly" moisture availability
217                                                                                                !! (0-1, unitless)
218    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: gdd_m5_dormance      !! growing degree days above a
219                                                                                                !! threshold of -5 deg C (C)
220    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                     :: gdd_midwinter        !! growing degree days, since
221                                                                                                !! midwinter (C)
222    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: ncd_dormance         !! number of chilling days since
223                                                                                                !! leaves were lost (days)
224    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: ngd_minus5           !! number of growing days above a
225                                                                                                !! threshold of -5 deg C (days)
226    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                            :: senescence           !! is the plant senescent? (only
227                                                                                                !! for deciduous trees -
228                                                                                                !! carbohydrate reserve)
229                                                                                                !! (true/false)
230    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: time_hum_min         !! time elapsed since strongest
231                                                                                                !! moisture availability (days)
232    !!!! added for crops
233    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: pdlai
234    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: slai
235    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: deltai
236    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: ssla
237    !!! end crops, xuhui
238    !
239    !! 0.2 Ouput variables
240    !
241
242    !
243    !! 0.3 Modified variables
244    !
245    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout)    :: biomass              !! biomass @tex ($gC m^{-2} of
246                                                                                                !! ground$) @endtex
247    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)           :: leaf_frac            !! fraction of leaves in leaf age
248                                                                                                !! class (0-1, unitless)
249    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)           :: leaf_age             !! leaf age (days)
250    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                     :: when_growthinit      !! how many days since the
251                                                                                                !! beginning of the growing season
252                                                                                                !! (days)
253    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                     :: co2_to_bm            !! co2 taken up by carbohydrate
254                                                                                                !! reserve at the beginning of the
255                                                                                                !! growing season @tex ($gC m^{-2}
256                                                                                                !! of total ground/day$) @endtex
257                                                                                                ! NV passge 2D
258    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                         :: begin_leaves         !! signal to start putting leaves
259!gmjc
260    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: sla_calc
261!end gmjc                                                                                                !! on (true/false)
262    !
263    !! 0.4 Local variables
264    !
265    LOGICAL, DIMENSION(npts,nvm)                                        :: allow_initpheno      !! are we allowed to decalre the
266                                                                                                !! beginning of the growing
267                                                                                                !! season? (true/false)
268    REAL(r_std), DIMENSION(npts)                                        :: bm_wanted            !! biomass we would like to have
269                                                                                                !! @tex ($gC m^{-2} of ground$)
270                                                                                                !! @endtex
271    REAL(r_std), DIMENSION(npts)                                        :: bm_use               !! biomass we use (from
272                                                                                                !! carbohydrate reserve or from
273                                                                                                !! atmosphere) @tex ($gC m^{-2} of
274                                                                                                !! ground$) @endtex
275    REAL(r_std), DIMENSION(npts)                                        :: lm_min               !! minimum leaf mass @tex ($gC
276                                                                                                !! m^{-2} of ground$) @endtex
277    LOGICAL(r_std), DIMENSION(npts)                                     :: age_reset            !! does the leaf age distribution
278                                                                                                !! have to be reset? (true/false)
279    INTEGER(i_std)                                                      :: i,j,m                !! indices (unitless)
280    REAL(r_std), DIMENSION(npts,nvm)                                    :: histvar              !! controls the history output
281                                                                                                !! level - 0: nothing is written;
282                                                                                                !! 10: everything is written
283                                                                                                !! (0-10, unitless)
284
285!_ ================================================================================================================================
286
287    IF (printlev>=3) WRITE(numout,*) 'Entering phenology'
288
289    !
290    !! 1. first call - output message giving the setting of the ::always_init
291    !!    and ::min_growthinit_time parameters.
292    !
293
294    IF ( firstcall_all_phenology ) THEN
295
296       WRITE(numout,*) 'phenology:'
297
298       WRITE(numout,*) '   > take carbon from atmosphere if carbohydrate' // &
299            ' reserve too small (::always_init): ', always_init
300
301       WRITE(numout,*) '   > minimum time since last beginning of a growing' // &
302            ' season (d) (::min_growthinit_time): ', min_growthinit_time
303
304       firstcall_all_phenology = .FALSE.
305
306    ENDIF
307
308    !
309    !! 2. Detection of the beginning of the growing season.
310    !
311
312    !
313    !! 2.1 allow detection of the beginning of the growing season if dormance was
314    !!     long enough (i.e. when ::time_lowgpp, which is calculated in ::stomate_season,
315    !!     is above a certain PFT-dependent threshold, ::lowgpp_time,
316    !!     which is given in ::stomate_constants),
317    !!     AND the last beginning of growing season was a sufficiently long time ago
318    !!     (i.e. when ::when_growthinit, which is calculated in this module,
319    !!     is greater than ::min_growthinit_time, which is declared at the beginning of this module).
320    !!     If these conditions are met, allow_initpheno is set to TRUE. Each PFT is looped over.
321    !
322
323    allow_initpheno(:,1) = .FALSE.
324    DO j = 2,nvm
325
326       WHERE ( when_growthinit(:,j) .GT. min_growthinit_time )
327          allow_initpheno(:,j) = .TRUE.
328       ELSEWHERE
329          allow_initpheno(:,j) = .FALSE.
330       ENDWHERE
331
332    ENDDO
333
334    WHERE(allow_initpheno)
335       histvar=un
336    ELSEWHERE
337       histvar=zero
338    ENDWHERE
339
340    CALL xios_orchidee_send_field("ALLOW_INITPHENO",histvar)
341
342    CALL histwrite_p (hist_id_stomate, 'ALLOW_INITPHENO', itime, histvar, npts*nvm, horipft_index)
343
344    !
345    !! 2.2 increase the ::when_growthinit counter, which gives the number of days since the beginning of the growing season.
346    !!     Needed for allocation and for the detection of the beginning of the growing season.
347    !
348
349    when_growthinit(:,:) = when_growthinit(:,:) + dt
350
351    !
352    !! 3. Leaf onset.
353    !!    Check biometeorological conditions using the onset phenological models,
354    !!    which are different for each PFT group (i.e. grass versus tropical etc.
355    !!    See below for more detail on the different models and which PFTs use each model).
356    !
357
358    !! - By default: phenology does not start (::begin_leaves set to FALSE).
359    begin_leaves(:,:) = .FALSE.
360
361    !! - The onset phenology model is selected, (according to the parameter ::pheno_model,
362    !! which is initialised in stomate_data), and called.
363    !! Each PFT is looped over (ignoring bare soil).
364    !! If conditions are favourable, begin_leaves is set to TRUE.
365   
366    ! parameter used in all the differents models of phenology
367    t_always = ZeroCelsius + t_always_add
368
369    DO j = 2,nvm ! Loop over # PFTs
370
371       SELECT CASE ( pheno_model(j) )
372
373       CASE ( 'hum' )
374
375          CALL pheno_hum (npts, j, PFTpresent, allow_initpheno, &
376               moiavail_month, moiavail_week, &
377               maxmoiavail_lastyear, minmoiavail_lastyear, &
378               begin_leaves)
379
380       CASE ( 'moi' )
381
382          CALL pheno_moi (npts, j, PFTpresent, allow_initpheno, &
383               time_hum_min, &
384               moiavail_month, moiavail_week, &
385               begin_leaves)
386
387
388       CASE ( 'ncdgdd' )
389
390          CALL pheno_ncdgdd (npts, j, PFTpresent, allow_initpheno, &
391               ncd_dormance, gdd_midwinter, &
392               t2m_month, t2m_week, begin_leaves)
393
394       CASE ( 'ngd' )
395
396          CALL pheno_ngd (npts, j, PFTpresent, allow_initpheno, ngd_minus5, &
397               t2m_month, t2m_week, begin_leaves)
398
399       CASE ( 'humgdd' )
400
401          CALL pheno_humgdd (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
402               maxmoiavail_lastyear, minmoiavail_lastyear, &
403               t2m_longterm, t2m_month, t2m_week, &
404               moiavail_week, moiavail_month, &
405               begin_leaves)
406
407       CASE ( 'moigdd' )
408
409          CALL pheno_moigdd (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
410               time_hum_min, &
411               t2m_longterm, t2m_month, t2m_week, &
412               moiavail_week, moiavail_month, &
413               begin_leaves, pdlai, slai)
414!!!qcj++ peatland
415       CASE ( 'siggdd' )
416
417          CALL pheno_siggdd (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
418               time_hum_min, &
419               t2m_longterm, t2m_month, t2m_week, &
420               moiavail_week, moiavail_month, &
421               begin_leaves)
422
423
424       CASE ( 'moi_C4' )
425
426          CALL pheno_moi_C4 (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
427               time_hum_min, &
428               t2m_longterm, t2m_month, t2m_week, &
429               moiavail_week, moiavail_month, &
430               begin_leaves)
431
432       CASE ( 'none' )
433
434          ! no action
435
436       CASE default
437
438          WRITE(numout,*) 'phenology: don''t know how to treat this PFT.'
439          WRITE(numout,*) '  number: (::j)',j
440          WRITE(numout,*) '  phenology model (::pheno_model(j)) : ',pheno_model(j)
441          CALL ipslerr_p(3,'stomate phenology','Cannot treat this PFT','','')
442
443       END SELECT
444
445    ENDDO
446
447    WHERE(begin_leaves)
448       histvar=un
449    ELSEWHERE
450       histvar=zero
451    ENDWHERE
452
453    CALL xios_orchidee_send_field("BEGIN_LEAVES",histvar)
454
455    CALL histwrite_p (hist_id_stomate, 'BEGIN_LEAVES', itime, histvar, npts*nvm, horipft_index)
456
457    !
458    !! 4. Leaf growth and biomass allocation when leaf biomass is low.
459    !!   Leaves start to grow if biometeorological conditions are favourable (::begin_leaves == TRUE) and if
460    !!   leaf growth is allowed (::allow_initpheno == TRUE).
461    !!   PFTs and then grid cells are looped over.
462    !
463
464    DO j = 2,nvm ! Loop over # PFTs
465
466       age_reset(:) = .FALSE.
467
468       DO i = 1, npts
469
470          IF ( begin_leaves(i,j) ) THEN
471            IF ( .NOT. ok_LAIdev(j) ) THEN
472
473                 !! 4.1 First minimum biomass is calculated using the following equation:
474                 !!     \latexonly
475                 !!     \input{phenology_lm_min_eqn2.tex}
476                 !!     \endlatexonly
477                 !!     \n
478    !JCMODIF
479    !             lm_min(i) = lai_initmin(j) / sla(j)
480                 lm_min(i) = lai_initmin(j) / sla_calc(i,j)
481    !ENDJCMODIF
482                 !! 4.2 If leaf biomass is lower than the minimum biomass then biomass must be allocated from the carbohydrate
483                 !!     reserves to leaves and roots.
484   
485                 IF ( biomass(i,j,ileaf,icarbon) .LT. lm_min(i) ) THEN
486   
487                    !
488                    !! 4.2.1 Determine how much biomass is available to use
489                    !!       First calculate how much biomass is wanted/required
490                    !!       (::bm_wanted = 2 x the minimum leaf biomass).
491                    !
492   
493                    bm_wanted(i) = 2. * lm_min(i)
494   
495                    !! 4.2.2 If the biomass in the carbohydrate reserves is less than the required biomass
496                    !!       take the required amount of carbon from the atmosphere and put it into the
497                    !!       carbohydrate reserve. This only occurs if the parameter ::always_init
498                    !!       (set at beginning of this ::subroutine) is TRUE. Default is FALSE.
499   
500                    IF ( always_init .AND. ( biomass(i,j,icarbres,icarbon) .LT. bm_wanted(i) ) ) THEN
501                       !NV passage 2D
502                       co2_to_bm(i,j) = co2_to_bm(i,j) + ( bm_wanted(i) - biomass(i,j,icarbres,icarbon) ) / dt
503   
504                       biomass(i,j,icarbres,icarbon) = bm_wanted(i)
505   
506                    ENDIF
507                   
508                    !! 4.2.3 The biomass available to use is set to be the minimum of the biomass of the carbohydrate reservoir (if
509                    !! carbon not taken from the atmosphere), and the wanted biomass.
510                    bm_use(i) = MIN( biomass(i,j,icarbres,icarbon), bm_wanted(i) )
511   
512                    !
513                    !! 4.2.4 divide the biomass which is available to use equally between the leaves and roots.
514                    !
515   
516                    biomass(i,j,ileaf,icarbon) = biomass(i,j,ileaf,icarbon) + bm_use(i) / 2.
517   
518                    biomass(i,j,iroot,icarbon) = biomass(i,j,iroot,icarbon) + bm_use(i) / 2.
519   
520                    !
521                    !! 4.2.5 decrease carbohydrate reservoir biomass by the amount that's been allocated to the leaves and roots
522                    !
523   
524                    biomass(i,j,icarbres,icarbon) = biomass(i,j,icarbres,icarbon) - bm_use(i)
525   
526                    !
527                    !! 4.2.6 set reset leaf age distribution (::age_reset) flag. Default is TRUE.
528                    !     (done later for better vectorization)
529                    !
530   
531                    age_reset(i) = .TRUE.
532   
533                 ENDIF  ! leaf mass is very low
534            ELSE ! crop STICS
535                 !! bm_use(i) = MIN( biomass(i,j,icarbres,icarbon), deltai(i,
536                 !j)/ssla(i, j)*10000. ) ! available carbon pools
537                 ! problem is that although the growth of biomass is reduced,
538                 ! but the lai growth continues and sla does not change. So
539                 ! there is a decoupling of the two, xuhui
540                 bm_use(i) = deltai(i, j)/ssla(i, j)*2*10000.  ! forcibly giving the lai at the begining of the growing season
541                 biomass(i,j,ileaf,icarbon) = biomass(i,j,ileaf,icarbon) + bm_use(i) / 2.   ! this is the first day for leave growth
542                 biomass(i,j,iroot,icarbon) = biomass(i,j,iroot,icarbon) + bm_use(i) / 2.
543                 biomass(i,j,icarbres,icarbon) = biomass(i,j,icarbres,icarbon) - bm_use(i)
544                 age_reset(i) = .TRUE.
545                 IF (printlev>=4) THEN
546                     WRITE(numout,*) 'in phenology, the bm_use and biomass is:', bm_use
547!                     WRITE(numout,*) 'in phenology, the reserve is:', biomass(:,12:14, icarbres,icarbon)
548!                     WRITE(numout,*) 'in phenology, the deltai is:', deltai(:,12:14)
549                 ENDIF
550            ENDIF ! if no crop
551
552             !
553             !! 4.3 reset when_growthinit counter: start of the growing season
554             !
555
556             when_growthinit(i,j) = zero
557
558          ENDIF    ! start of the growing season
559
560       ENDDO      ! loop over grid points
561
562       !
563       !! 4.4 reset leaf age distribution where necessary (i.e. when age_reset is TRUE)
564       !!     simply say that everything is in the youngest age class
565       !
566
567       !! 4.4.1 fractions - set the youngest age class fraction to 1 and all other leaf age class fractions to 0.
568
569       WHERE ( age_reset(:) )
570          leaf_frac(:,j,1) = un
571       ENDWHERE
572       DO m = 2, nleafages
573          WHERE ( age_reset(:) )
574             leaf_frac(:,j,m) = zero
575          ENDWHERE
576       ENDDO
577
578       !! 4.4.2 ages - set all leaf ages to 0.
579
580       DO m = 1, nleafages
581          WHERE ( age_reset(:) )
582             leaf_age(:,j,m) = zero
583          ENDWHERE
584       ENDDO
585
586    ENDDO        ! loop over # PFTs
587
588
589    IF (printlev>=3) WRITE(numout,*) 'Leaving phenology'
590
591  END SUBROUTINE phenology
592
593
594!! ================================================================================================================================
595!! SUBROUTINE   : pheno_hum
596!!
597!>\BRIEF          The 'hum' onset model initiate leaf onset based exclusively on moisture
598!!                availability criteria.
599!!                Currently no PFTs are assigned to this onset model.
600!!
601!! DESCRIPTION  : This model is for tropical biomes, where temperatures are high but moisture
602!!                might be a limiting factor on growth. It is based on leaf onset model 4a in
603!!                Botta et al. (2000), which adopts the approach of Le Roux (1995). \n
604!!                Leaf onset occurs if the monthly moisture availability is still quite
605!!                low (i.e. lower than the weekly availability), but the weekly availability is
606!!                higher than the critical threshold ::availability_crit (as it reacts faster),
607!!                which indicates the weekly moisture availability is increasing.
608!!                OR if the monthly moisture availability is high enough (i.e. above the
609!!                threshold value ::moiavail_always), leaf onset is initiated if this has not
610!!                already happened. This allows vegetation in arid areas to respond to rapidly
611!!                changing soil moisture conditions (Krinner et al., 2005). \n
612!!                The critical weekly moisture availability threshold (::availability_crit), is
613!!                calculated in this subroutine, and is a function of last year's maximum and
614!!                minimum moisture availability and the PFT-dependent parameter
615!!                ::hum_frac, which specifies how much of last year's available
616!!                moisture is required for leaf onset, as per the equation:
617!!                \latexonly
618!!                \input{phenology_moi_availcrit_eqn3.tex}
619!!                \endlatexonly
620!!                \n
621!!                ::hum_frac is set for each PFT in ::stomate_data from a table
622!!                which contains all the PFT values (::hum_frac_tab) in ::stomate_constants. \n
623!!                Last year's maximum and minimum moisture availability and the monthly and
624!!                weekly moisture availability are 
625!!                The ::pheno_hum subroutine is called in the subroutine ::phenology.
626!!
627!! RECENT CHANGE(S): None
628!!
629!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start.
630!!
631!! REFERENCE(S) :
632!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
633!! A global prognostic scheme of leaf onset using satellite data,
634!! Global Change Biology, 207, 337-347.
635!! - Le Roux, X. (1995), Etude et modelisation des echanges d'eau et d'energie
636!! sol-vegetation-atmosphere dans une savane humide, PhD Thesis, University
637!! Pierre et Marie Curie, Paris, France.
638!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
639!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
640!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
641!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
642!!
643!! FLOWCHART    :
644!! \latexonly
645!! \includegraphics[scale = 1]{pheno_hum.png}
646!! \endlatexonly
647!! \n             
648!_ ================================================================================================================================
649
650  SUBROUTINE pheno_hum (npts, j, PFTpresent, allow_initpheno, &
651       moiavail_month, moiavail_week, &
652       maxmoiavail_lastyear, minmoiavail_lastyear, &
653       begin_leaves)
654
655    !
656    !! 0. Variable and parameter declarations
657    !
658
659    !
660    !! 0.1 Input variables
661    !
662    INTEGER(i_std), INTENT(in)                                             :: npts                  !! Domain size - number of
663                                                                                                    !! grid cells (unitless)
664    INTEGER(i_std), INTENT(in)                                             :: j                     !! PFT index (unitless)
665    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                               :: PFTpresent            !! PFT exists (true/false)
666    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                               :: allow_initpheno       !! are we allowed to
667                                                                                                    !! declare the beginning of
668                                                                                                    !! the growing season?
669                                                                                                    !! (true/false)
670    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: moiavail_month        !! "monthly" moisture
671                                                                                                    !! availability (0-1, unitless)
672    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: moiavail_week         !! "weekly" moisture
673                                                                                                    !! availability (0-1, unitless)
674    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: maxmoiavail_lastyear  !! last year's maximum
675                                                                                                    !! moisture availability
676                                                                                                    !! (0-1, unitless)
677    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: minmoiavail_lastyear  !! last year's minimum
678                                                                                                    !! moisture availability
679                                                                                                    !! (0-1, unitless)
680
681    !
682    !! 0.2 Output variables
683    !
684
685    !
686    !! 0.3 Modified variables
687    !
688    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                            :: begin_leaves          !! signal to start putting
689                                                                                                    !! leaves on (true/false)
690
691    !
692    !! 0.4 Local variables
693    !
694    REAL(r_std)                                                            :: moiavail_always       !! critical monthly
695                                                                                                    !! moisture availability - set
696                                                                                                    !! for tree or grass
697                                                                                                    !! (0-1, unitless)
698    REAL(r_std), DIMENSION(npts)                                           :: availability_crit     !! critical weekly moisture
699                                                                                                    !! availability (0-1, unitless)
700    INTEGER(i_std)                                                         :: i                     !! index (unitless)
701
702!_ ================================================================================================================================
703
704    IF (printlev>=3) WRITE(numout,*) 'Entering hum'
705
706    !
707    !! 1. Initializations
708    !
709
710    !
711    !! 1.1 first call - outputs the name of onset model and the moisture availability
712    !!     parameters for tree and grass
713    !
714
715    IF ( firstcall_hum ) THEN
716
717       WRITE(numout,*) 'pheno_hum:'
718       WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
719       WRITE(numout,*) '         trees (::moiavail_always_tree): ', moiavail_always_tree
720       WRITE(numout,*) '         grasses (::moiavail_always_grass):', moiavail_always_grass
721
722       firstcall_hum = .FALSE.
723
724    ENDIF
725
726    !
727    !! 1.2 initialize output
728    !
729
730    begin_leaves(:,j) = .FALSE.
731
732    !
733    !! 1.3 check the critical value ::hum_frac is defined. If not, stop.
734    !
735
736    IF ( hum_frac(j) .EQ. undef ) THEN
737
738       WRITE(numout,*) 'hum: hum_frac is undefined for PFT (::j)',j
739       CALL ipslerr_p(3,'stomate phenology','hum_frac is undefined for this PFT','','')
740
741    ENDIF
742
743    !
744    !! 1.4 set the critical monthly moisture availability above which we always detect the beginning of the
745    !!     growing season - set as the moisture availability for trees or grass.
746    !
747
748    IF ( is_tree(j) ) THEN
749       moiavail_always = moiavail_always_tree
750    ELSE
751       moiavail_always = moiavail_always_grass
752    ENDIF
753
754    !
755    !! 2. Check if biometeorological conditions are favourable for leaf growth.
756    !! The PFT has to be there and start of growing season must be allowed
757    !
758
759    DO i = 1, npts
760
761       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
762
763          !! 2.1 Calculate the critical weekly moisture availability: depends linearly on the last year
764          !! minimum and maximum moisture availabilities, and on the parameter ::hum_frac.
765
766          availability_crit(i) = minmoiavail_lastyear(i,j) + hum_frac(j) * &
767               ( maxmoiavail_lastyear(i,j) - minmoiavail_lastyear(i,j) )
768
769          !! 2.2 Determine if growing season should start (if so, ::begin_leaves set to TRUE).
770          !!     Leaf onset occurs if the monthly moisture availability is still quite
771          !!     low (i.e. lower than the weekly availability), but the weekly availability is
772          !!     already higher than the critical threshold ::availability_crit (as it reacts faster),
773          !!     which indicates the weekly moisture availability is increasing.
774          !!     OR if the monthly moisture availability is high enough (i.e. above the threshold value
775          !!     ::moiavail_always), leaf onset is initiated if this has not already happened.
776
777          IF ( ( ( moiavail_week(i,j)  .GE. availability_crit(i) ) .AND. &
778               ( moiavail_month(i,j) .LT. moiavail_week(i,j) )   ) .OR. &
779               ( moiavail_month(i,j) .GE. moiavail_always )                ) THEN
780             begin_leaves(i,j) = .TRUE.
781          ENDIF
782
783       ENDIF        ! PFT there and start of growing season allowed
784
785    ENDDO ! end loop over grid points
786
787    IF (printlev>=4) WRITE(numout,*) 'Leaving hum'
788
789  END SUBROUTINE pheno_hum
790
791
792!! ================================================================================================================================
793!! SUBROUTINE   : pheno_moi
794!!
795!>\BRIEF          The 'moi' onset model (::pheno_moi) initiates leaf onset based exclusively
796!!                on moisture availability criteria.
797!!                It is very similar to the 'hum' onset model but instead of the weekly moisture
798!!                availability being higher than a constant threshold, the condition is that the
799!!                moisture minimum happened a sufficiently long time ago.
800!!                Currently PFT 3 (Tropical Broad-leaved Raingreen) is assigned to this model.
801!!
802!! DESCRIPTION  : This model is for tropical biomes, where temperatures are high but moisture
803!!                might be a limiting factor on growth. It is based on leaf onset model 4b in
804!!                Botta et al. (2000).
805!!                Leaf onset begins if the plant moisture availability minimum was a sufficiently 
806!!                time ago, as specified by the PFT-dependent parameter ::hum_min_time
807!!                AND if the "monthly" moisture availability is lower than the "weekly"
808!!                availability (indicating that soil moisture is increasing).
809!!                OR if the monthly moisture availability is high enough (i.e. above the threshold
810!!                value ::moiavail_always), leaf onset is initiated if this has not already
811!!                happened. \n
812!!                ::hum_min_time is set for each PFT in ::stomate_data, and is
813!!                defined in the table ::hum_min_time_tab in ::stomate_constants. \n
814!!                ::moiavail_always is defined for both tree and grass in this subroutine
815!!                (set to 1. and 0.6 respectively). \n
816!!                The ::pheno_moi subroutine is called in the subroutine ::phenology.
817!!
818!! RECENT CHANGE(S): None
819!!       
820!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start.
821!!
822!! REFERENCE(S) :
823!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
824!! A global prognostic scheme of leaf onset using satellite data,
825!! Global Change Biology, 207, 337-347.
826!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
827!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
828!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
829!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
830!!
831!! FLOWCHART    :
832!! \latexonly
833!! \includegraphics[scale = 1]{pheno_moi.png}
834!! \endlatexonly
835!! \n
836!_ ================================================================================================================================
837
838  SUBROUTINE pheno_moi (npts, j, PFTpresent, allow_initpheno, &
839       time_hum_min, &
840       moiavail_month, moiavail_week, &
841       begin_leaves)
842
843    !
844    !! 0. Variable and parameter declaration
845    !
846
847    !
848    !! 0.1 Input variables
849    !
850    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
851    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
852    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
853    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
854                                                                                !! growing season? (true/false)
855    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: time_hum_min    !! time elapsed since strongest moisture
856                                                                                !! availability (days)
857    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month  !! "monthly" moisture availability (0-1, unitless)
858    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week   !! "weekly" moisture availability (0-1, unitless)
859
860    !
861    !! 0.2 Output variables
862    !
863    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
864
865    !
866    !! 0.3 Modified variables
867    !
868
869    !
870    !! 0.4 Local variables
871    !
872    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
873                                                                                                !! set for tree or grass
874                                                                                                !! (0-1, unitless)
875    INTEGER(i_std)                                           :: i                               !! index (unitless)
876
877!_ ================================================================================================================================
878
879    IF (printlev>=3) WRITE(numout,*) 'Entering moi'
880
881    !
882    !! 1. Initializations
883    !
884
885    !
886    !! 1.1 first call - outputs the name of onset model and the moisture availability
887    !!     parameters for tree and grass
888    !
889
890    IF ( firstcall_moi ) THEN
891
892       WRITE(numout,*) 'pheno_moi:'
893       WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
894       WRITE(numout,*) '         trees (::moiavail_always_tree):', moiavail_always_tree
895       WRITE(numout,*) '         grasses (::moiavail_always_grass):', moiavail_always_grass
896
897       firstcall_moi = .FALSE.
898
899    ENDIF
900
901    !
902    !! 1.2 initialize output
903    !
904
905    begin_leaves(:,j) = .FALSE.
906
907    !
908    !! 1.3 check the critical value ::hum_min_time is definded. If not, stop
909    !
910
911    IF ( hum_min_time(j) .EQ. undef ) THEN
912
913       WRITE(numout,*) 'moi: hum_min_time is undefined for PFT (::j) ',j
914       CALL ipslerr_p(3,'stomate phenology','hum_min_time is undefined for this PFT','','')
915
916    ENDIF
917
918    !
919    !! 1.4 set the critical monthly moisture availability above which we always detect the beginning of the
920    !!     growing season - set as the moisture availability for trees or grass.
921    !
922
923    IF ( is_tree(j) ) THEN
924       moiavail_always = moiavail_always_tree
925    ELSE
926       moiavail_always = moiavail_always_grass
927    ENDIF
928
929    !
930    !! 2. Check if biometeorological conditions are favourable for leaf growth.
931    !! The PFT has to be there and start of growing season must be allowed.
932    !
933
934    DO i = 1, npts
935
936       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
937         
938          !! 2.1 Determine if growing season should start (if so, ::begin_leaves set to TRUE).
939          !!     The favorable season starts if the moisture minimum (::time_hum_min) was a sufficiently long
940          !!     time ago, i.e. greater than the threshold specified by the parameter ::hum_min_time
941          !!     and if the "monthly" moisture availability is lower than the "weekly"
942          !!     availability (indicating that soil moisture is increasing).
943          !!     OR if the monthly moisture availability is high enough (i.e. above the threshold value
944          !!     ::moiavail_always), initiate the growing season if this has not happened yet.
945
946          IF  ( ( ( moiavail_week(i,j) .GT. moiavail_month(i,j) ) .AND. &
947               ( time_hum_min(i,j) .GT. hum_min_time(j) )    ) .OR. &
948               ( moiavail_month(i,j) .GE. moiavail_always )                     ) THEN
949             begin_leaves(i,j) = .TRUE.
950          ENDIF
951
952       ENDIF        ! PFT there and start of growing season allowed
953
954    ENDDO ! end loop over grid points
955
956    IF (printlev>=4) WRITE(numout,*) 'Leaving moi'
957
958  END SUBROUTINE pheno_moi
959
960
961!! ================================================================================================================================
962!! SUBROUTINE   : pheno_humgdd
963!!
964!>\BRIEF          The 'humgdd' onset model initiates leaf onset based on mixed conditions of
965!!                temperature and moisture availability criteria.
966!!                Currently no PFTs are assigned to this onset model.
967!!
968!! DESCRIPTION  : In this model the Growing Degree Day (GDD) model (Chuine, 2000) is combined
969!!                with the 'hum' onset model (::pheno_hum), which has previously been described,
970!!                in order to account for dependence on both temperature and moisture conditions
971!!                in warmer climates. \n.
972!!                The GDD model specifies that daily temperatures above a threshold of -5 
973!!                degrees C are summed, minus this threshold, giving the GDD, starting from
974!!                the beginning of the dormancy period (::time_lowgpp>0), i.e. since the leaves
975!!                were lost. \n.
976!!                The dormancy time-length is represented by the variable
977!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
978!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
979!!                it is set to zero. \n
980!!                Leaf onset begins when the a PFT-dependent GDD-threshold is reached.
981!!                In addition there are temperature and moisture conditions.
982!!                The temperature condition specifies that the monthly temperature has to be
983!!                higher than a constant threshold (::t_always) OR
984!!                the weekly temperature is higher than the monthly temperature.
985!!                There has to be at least some moisture. The moisture condition
986!!                is exactly the same as the 'hum' onset model (::pheno_hum), which has already
987!!                been described. \n
988!!                The GDD (::gdd_m5_dormance) is calculated in ::stomate_season. GDD is set to
989!!                undef if beginning of the growing season detected, i.e. when there is GPP
990!!                (::time_lowgpp>0).
991!!                The parameter ::t_always is defined as 10 degrees C in this subroutine,
992!!                as are the parameters ::moisture_avail_tree and ::moisture_avail_grass
993!!                (set to 1 and 0.6 respectively), which are used in the moisture condition
994!!                (see ::pheno_moi onset model description). \n
995!!                The PFT-dependent GDD threshold (::gdd_crit) is calculated as in the onset
996!!                model ::pheno_humgdd, using the equation:
997!!                \latexonly
998!!                \input{phenology_hummoigdd_gddcrit_eqn4.tex}
999!!                \endlatexonly
1000!!                \n
1001!!                The three GDDcrit parameters (::gdd(j,*)) are set for each PFT in
1002!!                ::stomate_data, and three tables defining each of the three critical GDD
1003!!                parameters for each PFT is given in ::gdd_crit1_tab, ::gdd_crit2_tab and
1004!!                ::gdd_crit3_tab in ::stomate_constants. \n
1005!!                The ::pheno_humgdd subroutine is called in the subroutine ::phenology.
1006!!
1007!! RECENT CHANGES: None
1008!!               
1009!! MAIN OUTPUT VARIABLES: ::begin_leaves - specifies whether leaf growth can start
1010!!
1011!! REFERENCE(S) :
1012!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1013!! A global prognostic scheme of leaf onset using satellite data,
1014!! Global Change Biology, 207, 337-347.
1015!! - Chuine, I (2000), A unified model for the budburst of trees, Journal of
1016!! Theoretical Biology, 207, 337-347.
1017!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1018!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1019!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1020!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1021!!
1022!! FLOWCHART    :
1023!! \latexonly
1024!! \includegraphics[scale = 1]{pheno_humgdd.png}
1025!! \endlatexonly
1026!! \n             
1027!_ ================================================================================================================================
1028
1029  SUBROUTINE pheno_humgdd (npts, j, PFTpresent, allow_initpheno, gdd, &
1030       maxmoiavail_lastyear, minmoiavail_lastyear, &
1031       t2m_longterm, t2m_month, t2m_week, &
1032       moiavail_week, moiavail_month, &
1033       begin_leaves)
1034
1035    !
1036    !! 0. Variable and parameter declaration
1037    !
1038
1039    !
1040    !! 0.1 Input variables
1041    !
1042    INTEGER(i_std), INTENT(in)                               :: npts                    !! Domain size - number of grid cells
1043                                                                                        !! (unitless)
1044    INTEGER(i_std), INTENT(in)                               :: j                       !! PFT index (unitless)
1045    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent              !! PFT exists (true/false)
1046    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno         !! are we allowed to declare the beginning
1047                                                                                        !! of the growing season? (true/false)
1048    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gdd                     !! growing degree days, calculated since
1049                                                                                        !! leaves have fallen (C)
1050    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: maxmoiavail_lastyear    !! last year's maximum moisture
1051                                                                                        !! availability (0-1, unitless)
1052    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: minmoiavail_lastyear    !! last year's minimum moisture
1053                                                                                        !! availability (0-1, unitless)
1054    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm            !! "long term" 2 meter temperatures (K)
1055    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month               !! "monthly" 2-meter temperatures (K)
1056    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week                !! "weekly" 2-meter temperatures (K)
1057    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week           !! "weekly" moisture availability
1058                                                                                        !! (0-1, unitless)
1059    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month          !! "monthly" moisture availability
1060                                                                                        !! (0-1, unitless)
1061
1062    !
1063    !! 0.2 Output variables
1064    !
1065    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves            !! signal to start putting leaves on
1066                                                                                        !! (true/false)
1067
1068    !
1069    !! 0.3 Modified variables
1070    !
1071
1072    !
1073    !! 0.4 Local variables
1074    !
1075    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
1076                                                                                                !! set for tree or grass
1077                                                                                                !! (0-1, unitless)
1078    REAL(r_std), DIMENSION(npts)                             :: moiavail_crit                   !! critical moisture availability
1079                                                                                                !! (0-1, unitless)
1080    REAL(r_std), DIMENSION(npts)                             :: tl                              !! long term temperature (C)
1081    REAL(r_std), DIMENSION(npts)                             :: gdd_crit                        !! critical GDD (C)
1082    INTEGER(i_std)                                           :: i                               !! index (unitless)
1083
1084!_ ================================================================================================================================
1085
1086    IF (printlev>=3) WRITE(numout,*) 'Entering humgdd'
1087
1088    !
1089    !! 1. Initializations
1090    !
1091
1092    !
1093    !! 1.1 first call - outputs the name of the onset model, the values of the 
1094    !!     moisture availability parameters for tree and grass, and the value of the
1095    !!     critical monthly temperature.
1096    !
1097
1098    IF ( firstcall_humgdd ) THEN
1099
1100       WRITE(numout,*) 'pheno_humgdd:'
1101       WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1102       WRITE(numout,*) '         trees (::moiavail_always_tree): ', moiavail_always_tree
1103       WRITE(numout,*) '         grasses (::moiavail_always_grass): ', moiavail_always_grass
1104       WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter: ', &
1105            t_always
1106
1107       firstcall_humgdd = .FALSE.
1108
1109    ENDIF
1110
1111    !
1112    !! 1.2 initialize output
1113    !
1114
1115    begin_leaves(:,j) = .FALSE.
1116
1117    !
1118    !! 1.3 check the critical values ::gdd and ::pheno_crit_hum_frac are defined.
1119    !!     If not, stop.
1120    !
1121
1122    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1123
1124       WRITE(numout,*) 'humgdd: pheno_gdd_crit is undefined for PFT (::j) ',j
1125       CALL ipslerr_p(3,'stomate phenology','pheno_gdd_crit is undefined for this PFT','','')
1126
1127    ENDIF
1128
1129    IF ( hum_frac(j) .EQ. undef ) THEN
1130
1131       WRITE(numout,*) 'humgdd: hum_frac is undefined for PFT (::j) ',j
1132       CALL ipslerr_p(3,'stomate phenology','hum_frac is undefined for this PFT','','')
1133
1134    ENDIF
1135
1136    !
1137    !! 1.4 set the critical moisture availability above which we always detect the beginning of the
1138    !!     growing season - set as the moisture availability for trees or grass.
1139    !
1140
1141    IF ( is_tree(j) ) THEN
1142       moiavail_always = moiavail_always_tree
1143    ELSE
1144       moiavail_always = moiavail_always_grass
1145    ENDIF
1146
1147    !
1148    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1149    !!   The PFT has to be there, start of growing season must be allowed,
1150    !!   and GDD has to be defined.
1151    !
1152
1153    DO i = 1, npts
1154
1155       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1156            ( gdd(i,j) .NE. undef )                           ) THEN
1157
1158          !! 2.1 Calculate the critical weekly moisture availability: depends linearly on the last year
1159          !! minimum and maximum moisture availabilities, and on the parameter ::hum_frac.,
1160          !! (as in the ::pheno_hum model), as per the equation:
1161
1162          moiavail_crit(i) = minmoiavail_lastyear(i,j) + hum_frac(j) * &
1163               ( maxmoiavail_lastyear(i,j) - minmoiavail_lastyear(i,j) )
1164
1165          !! 2.2 Calculate the critical GDD (::gdd_crit), which is a function of the PFT-dependent
1166          !!     critical GDD and the "long term" 2 meter air temperatures. 
1167
1168          tl(i) =  t2m_longterm(i) - ZeroCelsius
1169          gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
1170               tl(i)*tl(i)*pheno_gdd_crit(j,3)
1171         
1172          !! 2.3 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1173          !!     - Has the critical gdd been reached and is the temperature increasing?
1174          !!     - Is there at least some humidity/moisture availability?
1175          !!     This occurs if the critical gdd (::gdd_crit) has been reached
1176          !!     AND that is temperature increasing, which is true either if the monthly
1177          !!     temperature being higher than the threshold ::t_always, OR if the weekly
1178          !!     temperature is higher than the monthly,
1179          !!     AND finally that there is sufficient moisture availability, which is
1180          !!     the same condition as for the ::pheno_hum onset model.
1181
1182          IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
1183               ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
1184               ( t2m_month(i) .GT. t_always )          ) .AND. &
1185               ( ( ( moiavail_week(i,j)  .GE. moiavail_crit(i) ) .AND. &
1186               ( moiavail_month(i,j) .LT. moiavail_crit(i) )        ) .OR. &
1187               ( moiavail_month(i,j) .GE. moiavail_always )                   ) )  THEN
1188             begin_leaves(i,j) = .TRUE.
1189          ENDIF
1190
1191       ENDIF        ! PFT there and start of growing season allowed
1192
1193    ENDDO ! End loop over grid points
1194
1195    IF (printlev>=4) WRITE(numout,*) 'Leaving humgdd'
1196
1197  END SUBROUTINE pheno_humgdd
1198
1199
1200!! ================================================================================================================================
1201!! SUBROUTINE   : pheno_moigdd
1202!!
1203!>\BRIEF          The 'moigdd' onset model initiates leaf onset based on mixed temperature
1204!!                and moisture availability criteria.
1205!!                Currently PFTs 10 - 13 (C3 and C4 grass, and C3 and C4 agriculture)
1206!!                are assigned to this model.
1207!!
1208!! DESCRIPTION  : This onset model combines the GDD model (Chuine, 2000), as described for
1209!!                the 'humgdd' onset model (::pheno_humgdd), and the 'moi' model, in order
1210!!                to account for dependence on both temperature and moisture conditions in
1211!!                warmer climates. \n
1212!!                Leaf onset begins when the a PFT-dependent GDD threshold is reached.
1213!!                In addition there are temperature and moisture conditions.
1214!!                The temperature condition specifies that the monthly temperature has to be
1215!!                higher than a constant threshold (::t_always) OR
1216!!                the weekly temperature is higher than the monthly temperature.
1217!!                There has to be at least some moisture. The moisture condition
1218!!                is exactly the same as the 'moi' onset model (::pheno_moi), which has
1219!!                already been described. \n
1220!!                GDD is set to undef if beginning of the growing season detected.
1221!!                As in the ::pheno_humgdd model, the parameter ::t_always is defined as
1222!!                10 degrees C in this subroutine, as are the parameters ::moisture_avail_tree
1223!!                and ::moisture_avail_grass (set to 1 and 0.6 respectively), which are used
1224!!                in the moisture condition (see ::pheno_moi onset model description). \n
1225!!                The PFT-dependent GDD threshold (::gdd_crit) is calculated as in the onset
1226!!                model ::pheno_humgdd, using the equation:
1227!!                \latexonly
1228!!                \input{phenology_hummoigdd_gddcrit_eqn4.tex}
1229!!                \endlatexonly
1230!!                \n
1231!!                where i and j are the grid cell and PFT respectively.
1232!!                The three GDDcrit parameters (::gdd(j,*)) are set for each PFT in
1233!!                ::stomate_data, and three tables defining each of the three critical GDD
1234!!                parameters for each PFT is given in ::gdd_crit1_tab, ::gdd_crit2_tab and
1235!!                ::gdd_crit3_tab in ::stomate_constants. \n
1236!!                The ::pheno_moigdd subroutine is called in the subroutine ::phenology.
1237!!
1238!! RECENT CHANGE(S): Added temperature threshold for C4 grass (pheno_moigdd_t_crit), Dan Zhu april 2015
1239!!               
1240!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1241!!
1242!! REFERENCE(S) :
1243!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1244!! A global prognostic scheme of leaf onset using satellite data,
1245!! Global Change Biology, 207, 337-347.
1246!! - Chuine, I (2000), A unified model for the budburst of trees, Journal of
1247!! Theoretical Biology, 207, 337-347.
1248!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1249!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1250!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1251!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1252!! - Still et al., Global distribution of C3 and C4 vegetation: Carbon cycle implications,
1253!! 2003, Global Biogeochemmical Cycles, DOI: 10.1029/2001GB001807.
1254!!
1255!! FLOWCHART    :
1256!! \latexonly
1257!! \includegraphics[scale = 1]{pheno_moigdd.png}
1258!! \endlatexonly
1259!! \n
1260!_ ================================================================================================================================
1261
1262  SUBROUTINE pheno_moigdd (npts, j, PFTpresent, allow_initpheno, gdd, &
1263       time_hum_min, &
1264       t2m_longterm, t2m_month, t2m_week, &
1265       moiavail_week, moiavail_month, &
1266       begin_leaves, pdlai, slai)
1267
1268    !
1269    !! 0. Variable and parameter declaration
1270    !
1271
1272    !
1273    !! 0.1 Input variables
1274    !
1275    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1276    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1277    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1278    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to decalre the beginning of the
1279                                                                                !! growing season? (true/false)
1280    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gdd             !! growing degree days, calculated since leaves
1281                                                                                !! have fallen (C)
1282    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: time_hum_min    !! time elapsed since strongest moisture
1283                                                                                !! availability (days)
1284    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm    !! "long term" 2 meter temperatures (K)
1285    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1286    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1287    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week   !! "weekly" moisture availability (0-1, unitless)
1288    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month  !! "monthly" moisture availability (0-1, unitless)
1289    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: pdlai
1290    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: slai
1291
1292    !
1293    !! 0.2 Output variables
1294    !
1295
1296    !
1297    !! 0.3 Modified variables
1298    !
1299    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1300
1301    !
1302    !! 0.4 Local variables
1303    !
1304    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
1305                                                                                                !! set for tree or grass
1306                                                                                                !! (0-1, unitless)
1307    REAL(r_std), DIMENSION(npts)                             :: tl                              !! long term temperature (C)
1308    REAL(r_std), DIMENSION(npts)                             :: gdd_crit                        !! critical GDD (C)
1309    INTEGER(i_std)                                           :: i                               !! index (unitless)
1310
1311!_ ================================================================================================================================
1312
1313    IF (printlev>=3) WRITE(numout,*) 'Entering moigdd'
1314
1315    !
1316    !! 1. Initializations
1317    !
1318
1319    !
1320    !! 1.1 first call - outputs the name of the onset model, the values of the 
1321    !!     moisture availability parameters for tree and grass, and the value of the
1322    !!     critical monthly temperature.
1323    !
1324
1325    IF ( firstcall_moigdd ) THEN
1326
1327       WRITE(numout,*) 'pheno_moigdd:'
1328       WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1329       WRITE(numout,*) '         trees (::moiavail_always_tree) :', moiavail_always_tree
1330       WRITE(numout,*) '         grasses (::moiavail_always_grass) :', moiavail_always_grass
1331       WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter (::t_always): ', &
1332            t_always
1333
1334       firstcall_moigdd = .FALSE.
1335
1336    ENDIF
1337
1338    !
1339    !! 1.2 initialize output
1340    !
1341
1342    begin_leaves(:,j) = .FALSE.
1343
1344    !
1345    !! 1.3 check the critical values ::gdd and ::pheno_crit_hum_min_time are defined.
1346    !!     If not, stop.
1347    !
1348
1349    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1350
1351       WRITE(numout,*) 'moigdd: pheno_gdd_crit is undefined for PFT',j
1352       CALL ipslerr_p(3,'stomate phenology','pheno_gdd is undefined for this PFT','','')
1353
1354    ENDIF
1355
1356    IF ( hum_min_time(j) .EQ. undef ) THEN
1357
1358       WRITE(numout,*) 'moigdd: hum_min_time is undefined for PFT',j
1359       CALL ipslerr_p(3,'stomate phenology','hum_min is undefined for this PFT','','')
1360
1361    ENDIF
1362
1363    !
1364    !! 1.4 set the critical moisture availability above which we always detect the beginning of the
1365    !!     growing season - set as the moisture availability for trees or grass.
1366    !
1367
1368    IF ( is_tree(j) ) THEN
1369       moiavail_always = moiavail_always_tree
1370    ELSE
1371       moiavail_always = moiavail_always_grass
1372    ENDIF
1373
1374    !
1375    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1376    !!    The PFT has to be there, the start of growing season must be allowed,
1377    !!    and GDD has to be defined.
1378    !
1379
1380    DO i = 1, npts
1381        IF ( ok_LAIdev(j) ) THEN
1382
1383            IF ( ( (slai(i, j)-pdlai(i, j)) .gt. zero ) .AND. ( pdlai(i, j) .eq. zero ) ) THEN
1384                begin_leaves(i, j) = .TRUE.
1385            ELSE
1386                begin_leaves(i, j) = .FALSE.
1387            ENDIF
1388        ELSE ! natural PFTs
1389            IF (printlev>=4) THEN
1390                WRITE(numout,*),'PFTpresent(i,j)',PFTpresent(i,j)
1391                WRITE(numout,*) 'allow_initpheno(i,j)', allow_initpheno(i,j)
1392                WRITE(numout,*) 'gdd(i,j)', gdd(i,j)
1393           ENDIF
1394
1395           IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1396                ( gdd(i,j) .NE. undef )                           ) THEN
1397             
1398              !! 2.1 Calculate the critical GDD (::gdd_crit), which is a function of the PFT-dependent
1399              !!     critical GDD and the "long term" 2 meter air temperatures
1400             
1401              tl(i) = t2m_longterm(i) - ZeroCelsius
1402              gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
1403                   tl(i)*tl(i)*pheno_gdd_crit(j,3)
1404              IF (printlev>=4) THEN 
1405                !!! debug output xuhui
1406                WRITE(numout,*) 'gdd(i,j)', gdd(i,j)
1407                WRITE(numout,*) 'time_hum_min(i,j)', time_hum_min(i,j)
1408                WRITE(numout,*) 'gdd_crit(i)', gdd_crit(i)
1409                WRITE(numout,*) 't_always',t_always
1410                WRITE(numout,*) 'moiavail_always',moiavail_always
1411              ENDIF
1412   
1413   
1414              !! 2.2 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1415              !!     This occurs if the critical gdd (::gdd_crit) has been reached
1416              !!     AND that is temperature increasing, which is true either if the monthly
1417              !!     temperature being higher than the threshold ::t_always, OR if the weekly
1418              !!     temperature is higher than the monthly,
1419              !!     AND finally that there is sufficient moisture availability, which is
1420              !!     the same condition as for the ::pheno_moi onset model.
1421              !!     AND when pheno_moigdd_t_crit is set(for C4 grass), if the average temperature threshold is reached
1422
1423              IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
1424                   ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
1425                     ( t2m_month(i) .GT. t_always )  ) .AND. &
1426                   ( ( ( time_hum_min(i,j) .GT. hum_min_time(j) ) .AND. &
1427                     ( moiavail_week(i,j) .GT. moiavail_month(i,j) ) ) .OR. &
1428                     ( moiavail_month(i,j) .GE. moiavail_always )  ) .AND. &
1429                   ( ( pheno_moigdd_t_crit(j) == undef ) .OR. &
1430                     (t2m_month(i) .GT. (ZeroCelsius + pheno_moigdd_t_crit(j))) ) ) THEN
1431   
1432                 begin_leaves(i,j) = .TRUE.
1433                 
1434              ENDIF
1435   
1436           ENDIF        ! PFT there and start of growing season allowed
1437        ENDIF ! crop PFT   
1438    ENDDO
1439
1440    IF (printlev>=4) WRITE(numout,*) 'Leaving moigdd'
1441
1442  END SUBROUTINE pheno_moigdd
1443
1444
1445!! ================================================================================================================================
1446!! SUBROUTINE   : pheno_ncdgdd
1447!!
1448!>\BRIEF          The Number of Chilling Days - Growing Degree Day (NCD-GDD) model initiates
1449!!                leaf onset if a certain relationship between the number of chilling days (NCD)
1450!!                since leaves were lost, and the growing degree days (GDD) since midwinter, is
1451!!                fulfilled.
1452!!                Currently PFT 6 (Temperate Broad-leaved Summergreen) and PFT 8 (Boreal Broad-
1453!!                leaved Summergreen) are assigned to this model.
1454!!
1455!! DESCRIPTION  : Experiments have shown that some
1456!!                species have a "chilling" requirement, i.e. their physiology needs cold
1457!!                temperatures to trigger the mechanism that will allow the following budburst
1458!!                (e.g. Orlandi et al., 2004).
1459!!                An increase in chilling days, defined as a day with a daily mean air
1460!!                temperature below a PFT-dependent threshold, reduces a plant's GDD demand
1461!!                (Cannell and Smith, 1986; Murray et al., (1989); Botta et al., 2000).
1462!!                The GDD threshold therefore decreases as NCD
1463!!                increases, using the following empirical negative explonential law:
1464!!                \latexonly
1465!!                \input{phenology_ncdgdd_gddmin_eqn5.tex}
1466!!                \endlatexonly
1467!!                \n
1468!!                The constants used have been calibrated against data CHECK FOR REFERENCE OR PERSON WHO DID UPDATE.
1469!!                Leaf onset begins if the GDD is higher than the calculated minimum GDD
1470!!                (dependent upon NCD) AND if the weekly temperature is higher than the monthly
1471!!                temperature. This is to ensure the temperature is increasing. \n
1472!!                The dormancy time-length is represented by the variable
1473!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
1474!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
1475!!                it is set to zero. \n
1476!!                The NCD (::ncd_dormance) is calculated in ::stomate_season as 
1477!!                the number of days with a temperature below a PFT-dependent constant threshold
1478!!                (::ncdgdd_temp), starting from the beginning of the dormancy period
1479!!                (::time_lowgpp>0), i.e. since the leaves were lost. \n
1480!!                The growing degree day sum of the temperatures higher than
1481!!                ::ncdgdd_temp (GDD) since midwinter (::gdd_midwinter)
1482!!                is also calculated in ::stomate_season.
1483!!                Midwinter is detected if the monthly temperature is lower than the weekly
1484!!                temperature AND  the monthly temperature is lower than the long-term
1485!!                temperature. ::gdd_minter is therefore set to 0 at the beginning of midwinter
1486!!                and increased with each temperature greater than the PFT-dependent threshold.
1487!!                When midsummer is detected (the opposite of the above conditions),
1488!!                ::gdd_midwinter is set to undef.
1489!!                CHECK! WHEN TO START OF DORMANCY BEEN MODIFIED FROM BOTTA- ADD IN?
1490!!                The ::pheno_ncdgdd subroutine is called in the subroutine ::phenology.
1491!!
1492!! RECENT CHANGE(S): None
1493!!               
1494!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1495!!
1496!! REFERENCE(S) :
1497!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1498!! A global prognostic scheme of leaf onset using satellite data,
1499!! Global Change Biology, 207, 337-347.
1500!! - Cannell, M.J.R. and R.I. Smith (1986), Climatic warming, spring budburst and
1501!! frost damage on trees, Journal of Applied Ecology, 23, 177-191.
1502!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1503!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1504!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1505!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1506!! - Murray, M.B., G.R. Cannell and R.I. Smith (1989), Date of budburst of fifteen
1507!! tree species in Britain following climatic warming, Journal of Applied Ecology,
1508!! 26, 693-700.
1509!! - Orlandi, F., H. Garcia-Mozo, L.V. Ezquerra, B. Romano, E. Dominquez, C. Galan,
1510!! and M. Fornaciari (2004), Phenological olive chilling requirements in Umbria
1511!! (Italy) and Andalusia (Spain), Plant Biosystems, 138, 111-116.
1512!!
1513!! FLOWCHART    :
1514!! \latexonly
1515!! \includegraphics[scale = 1]{pheno_ncdgdd.png}
1516!! \endlatexonly
1517!! \n
1518!_ ================================================================================================================================
1519
1520  SUBROUTINE pheno_ncdgdd (npts, j, PFTpresent, allow_initpheno, &
1521       ncd_dormance, gdd_midwinter, &
1522       t2m_month, t2m_week, begin_leaves)
1523
1524    !
1525    !! 0. Variable and parameter declaration
1526    !
1527
1528    !
1529    !! 0.1 Input variables
1530    !
1531    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1532    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1533    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1534    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
1535                                                                                !! growing season? (true/false)
1536    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: ncd_dormance    !! number of chilling days since leaves were lost
1537                                                                                !! (days)
1538    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: gdd_midwinter   !! growing degree days since midwinter (C)
1539    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1540    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1541
1542    !
1543    !! 0.2 Output variables
1544    !
1545
1546    !
1547    !! 0.3 Modified variables
1548    !
1549    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1550
1551    !
1552    !! 0.4 Local variables
1553    !
1554    INTEGER(i_std)                                           :: i               !! index (unitless)
1555    REAL(r_std)                                              :: gdd_min         !! critical gdd (C)
1556
1557!_ ================================================================================================================================
1558
1559    IF (printlev>=3) WRITE(numout,*) 'Entering ncdgdd'
1560
1561    !
1562    !! 1. Initializations
1563    !
1564
1565    !
1566    !! 1.1 initialize output
1567    !
1568
1569    begin_leaves(:,j) = .FALSE.
1570
1571    !
1572    !! 1.2 check the critical value ::ncdgdd_temp is defined.
1573    !!     If not, stop.
1574    !
1575
1576    IF ( ncdgdd_temp(j) .EQ. undef ) THEN
1577
1578       WRITE(numout,*) 'ncdgdd: ncdgdd_temp is undefined for PFT (::j) ',j
1579       CALL ipslerr_p(3,'stomate phenology','ncdgdd_temp this PFT','','')
1580
1581    ENDIF
1582
1583    !
1584    !! 2. Check if biometeorological conditions are favourable for leaf growth.   
1585    !!    PFT has to be there and start of growing season must be allowed.
1586    !
1587
1588    DO i = 1, npts ! loop over grid points
1589
1590       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1591            ( gdd_midwinter(i,j) .NE. undef ) .AND. &
1592            ( ncd_dormance(i,j) .NE. undef )                  ) THEN
1593
1594          !! 2.1 Calculate the critical gdd, which is related to ::ncd_dormance
1595          !!     using an empirical negative exponential law as described above.           
1596
1597          gdd_min = ( gddncd_ref / exp(gddncd_curve*ncd_dormance(i,j)) - gddncd_offset )
1598
1599          !! 2.2 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1600          !!     This occurs if the critical GDD been reached AND the temperatures are increasing.
1601          !!     If the growing season has started, ::gdd_midwinter is set to "undef".
1602
1603          IF ( ( gdd_midwinter(i,j) .GE. gdd_min ) .AND. &
1604               ( t2m_week(i) .GT. t2m_month(i) ) ) THEN
1605             begin_leaves(i,j) = .TRUE.
1606             gdd_midwinter(i,j)=undef
1607          ENDIF
1608
1609       ENDIF        ! PFT there and start of growing season allowed
1610
1611    ENDDO ! end loop over grid points
1612
1613    IF (printlev>=4) WRITE(numout,*) 'Leaving ncdgdd'
1614
1615  END SUBROUTINE pheno_ncdgdd
1616
1617
1618!! ================================================================================================================================
1619!! SUBROUTINE   : pheno_ngd
1620!!
1621!>\BRIEF          The Number of Growing Days (NGD) leaf onset model initiates leaf onset if the NGD,
1622!!                defined as the number of days with temperature above a constant threshold,
1623!!                exceeds a critical value.
1624!!                Currently PFT 9 (Boreal Leedleleaf Summergreen) is assigned to this model.
1625!!
1626!! DESCRIPTION    The NGD model is a variant of the GDD model. The model was proposed by Botta et
1627!!                al. (2000) for boreal and arctic biomes, and is designed to estimate
1628!!                leaf onset after the end of soil frost.
1629!!                The NDG (::ngd_minus5) is the number of days with a daily mean air
1630!!                temperature of greater than -5 degrees C,
1631!!                starting from the beginning of the dormancy period (i.e. time since the leaves
1632!!                were lost/GPP below a certain threshold).
1633!!                Leaf onset begins if the NGD is higher than the PFT-dependent constant threshold,
1634!!                ::ngd,  AND if the weekly temperature is higher than the monthly
1635!!                temperature. \n
1636!!                The dormancy time-length is represented by the variable
1637!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
1638!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
1639!!                it is set to zero. \n
1640!!                ::ngd_minus5 is also calculated in ::stomate_season. It is initialised at the
1641!!                beginning of the dormancy period (::time_lowgpp>0), and increased by the
1642!!                stomate time step when the temperature > -5 degrees C. \n
1643!!                ::ngd is set for each PFT in ::stomate_data, and a
1644!!                table defining the minimum NGD for each PFT is given in ::ngd_crit_tab
1645!!                in ::stomate_constants. \n
1646!!                The ::pheno_ngd subroutine is called in the subroutine ::phenology.     
1647!!
1648!! RECENT CHANGE(S): None
1649!!               
1650!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1651!!
1652!! REFERENCE(S) :
1653!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1654!! A global prognostic scheme of leaf onset using satellite data,
1655!! Global Change Biology, 207, 337-347.
1656!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1657!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1658!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1659!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1660!!
1661!! FLOWCHART    :
1662!! \latexonly
1663!! \includegraphics[scale = 1]{pheno_ngd.png}
1664!! \endlatexonly
1665!! \n
1666!_ ================================================================================================================================
1667
1668  SUBROUTINE pheno_ngd (npts, j, PFTpresent, allow_initpheno, ngd, &
1669       t2m_month, t2m_week, begin_leaves)
1670
1671    !
1672    !! 0. Variable and parameter declaration
1673    !
1674
1675    !
1676    !! 0.1 Input variables
1677    !
1678    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1679    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1680    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1681    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
1682                                                                                !! growing season? (true/false)
1683    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: ngd             !! growing degree days (C)
1684    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1685    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1686
1687    !
1688    !! 0.2 Output variables
1689    !
1690
1691    !
1692    !! 0.3 Modified variables
1693    !
1694    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1695
1696    !
1697    !! 0.4 Local variables
1698    !
1699    INTEGER(i_std)                                           :: i               !! index (unitless)
1700
1701    !! =========================================================================
1702
1703    IF (printlev>=3) WRITE(numout,*) 'Entering ngd'
1704
1705    !
1706    !! 1. Initializations
1707    !
1708
1709    !
1710    !! 1.1 initialize output
1711    !
1712
1713    begin_leaves(:,j) = .FALSE.
1714
1715    !
1716    !! 1.2 check the critical value ::ngd_crit is defined.
1717    !!     If not, stop.
1718    !
1719
1720    IF ( ngd_crit(j) .EQ. undef ) THEN
1721
1722       WRITE(numout,*) 'ngd: ngd_crit is undefined for PFT (::j) ',j
1723       CALL ipslerr_p(3,'stomate phenology','ngd_crit is undefined for this PFT','','')
1724
1725    ENDIF
1726
1727    !
1728    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1729    !!    PFT has to be there and start of growing season must be allowed.
1730    !
1731
1732    DO i = 1, npts
1733
1734       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
1735
1736          !! 2.1 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1737          !!     This occurs if the critical NGD has been reached AND are temperatures increasing.
1738
1739          IF ( ( ngd(i,j) .GE. ngd_crit(j) ) .AND. &
1740               ( t2m_week(i) .GT. t2m_month(i) )        ) THEN
1741             begin_leaves(i,j) = .TRUE.
1742          ENDIF
1743
1744       ENDIF        ! PFT there and start of growing season allowed
1745
1746    ENDDO ! end loop over grid points
1747
1748    IF (printlev>=4) WRITE(numout,*) 'Leaving ngd'
1749
1750  END SUBROUTINE pheno_ngd
1751  !
1752  ! ==============================================================================
1753  ! DZ modified for C4 grass: mean monthly temperature must be greater than 22
1754  ! degree for C4 to begin leaves (based on moigdd).
1755  !
1756
1757  SUBROUTINE pheno_moi_C4 (npts, j, PFTpresent, allow_initpheno, gdd, &
1758       time_hum_min, &
1759       t2m_longterm, t2m_month, t2m_week, &
1760       moiavail_week, moiavail_month, &
1761       begin_leaves)
1762
1763    !
1764    ! 0 declarations
1765    !
1766
1767    ! 0.1 input
1768
1769    ! Domain size
1770    INTEGER(i_std), INTENT(in)                                     :: npts
1771    ! PFT index
1772    INTEGER(i_std), INTENT(in)                               :: j
1773    ! PFT exists
1774    LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: PFTpresent
1775    ! are we allowed to decalre the beginning of the growing season?
1776    LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: allow_initpheno
1777    ! growing degree days, calculated since leaves have fallen
1778    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: gdd
1779    ! time elapsed since strongest moisture availability (d)
1780    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: time_hum_min
1781    ! "long term" 2 meter temperatures (K)
1782    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm
1783    ! "monthly" 2-meter temperatures (K)
1784    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month
1785    ! "weekly" 2-meter temperatures (K)
1786    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week
1787    ! "weekly" moisture availability
1788    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_week
1789    ! "monthly" moisture availability
1790    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)            :: moiavail_month
1791
1792    ! 0.2 output
1793
1794    ! signal to start putting leaves on
1795    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves
1796    ! 0.3 local
1797
1798    ! moisture availability above which moisture tendency doesn't matter
1799    REAL(r_std)                                              :: moiavail_always
1800    ! long term temperature, C
1801    REAL(r_std), DIMENSION(npts)                             :: tl
1802    ! critical GDD
1803    REAL(r_std), DIMENSION(npts)                             :: gdd_crit
1804    ! index
1805    INTEGER(i_std)                                           :: i
1806
1807    ! =========================================================================
1808
1809    IF (printlev>=3) WRITE(numout,*) 'Entering moi_C4'
1810
1811    !
1812    ! 1 Initializations
1813    !
1814    ! 1.1 messages
1815    !
1816
1817    IF ( firstcall_moi_C4 ) THEN
1818
1819       WRITE(numout,*) 'pheno_moi_C4:'
1820       WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1821       WRITE(numout,*) '         trees:', moiavail_always_tree
1822       WRITE(numout,*) '         grasses:', moiavail_always_grass
1823       WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter: ', &
1824            t_always
1825
1826       firstcall_moi_C4 = .FALSE.
1827
1828    ENDIF
1829
1830    !
1831
1832    ! 1.1 initialize output
1833    !
1834
1835    begin_leaves(:,j) = .FALSE.
1836
1837    !
1838    ! 1.2 check the prescribed critical values
1839    !
1840    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1841
1842       WRITE(numout,*) 'moi_C4: pheno_gdd_crit is undefined for PFT',j
1843       WRITE(numout,*) 'We stop.'
1844       STOP
1845
1846    ENDIF
1847
1848    IF ( hum_min_time(j) .EQ. undef ) THEN
1849
1850       WRITE(numout,*) 'moi_C4: hum_min_time is undefined for PFT',j
1851       WRITE(numout,*) 'We stop.'
1852       STOP
1853
1854    ENDIF
1855
1856    !
1857    ! 1.3 critical moisture availability above which we always detect the
1858    ! beginning of the
1859    !     growing season.
1860    !
1861
1862    IF ( is_tree(j) ) THEN
1863       moiavail_always = moiavail_always_tree
1864    ELSE
1865       moiavail_always = moiavail_always_grass
1866    ENDIF
1867
1868    !
1869    ! 2 PFT has to be there, start of growing season must be allowed,
1870    !   and gdd has to be defined
1871    !
1872
1873    DO i = 1, npts
1874
1875       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1876            ( gdd(i,j) .NE. undef )                           ) THEN
1877
1878          ! is critical gdd reached and is temperature increasing?
1879          ! has enough time gone by since moisture minimum and is moisture
1880          ! increasing?
1881
1882          tl(i) = t2m_longterm(i) - ZeroCelsius
1883          gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
1884               tl(i)*tl(i)*pheno_gdd_crit(j,3)
1885
1886          IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
1887               ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
1888               ( t2m_month(i) .GT. t_always )          ) .AND. &
1889               ( ( ( time_hum_min(i,j) .GT. hum_min_time(j) ) .AND. &
1890               ( moiavail_week(i,j) .GT. moiavail_month(i,j) )    ) .OR. &
1891               ( moiavail_month(i,j) .GE. moiavail_always )    ) .AND. &
1892               ( t2m_month(i) .GT. (ZeroCelsius + 22)  )    )  THEN
1893             begin_leaves(i,j) = .TRUE.
1894          ENDIF
1895
1896       ENDIF        ! PFT there and start of growing season allowed
1897
1898    ENDDO
1899
1900    IF (printlev>=3) WRITE(numout,*) 'Leaving moi_C4'
1901
1902  END SUBROUTINE pheno_moi_C4
1903!! ================================================================================================================================
1904!! SUBROUTINE   : pheno_siggdd
1905!!
1906!>\BRIEF          The 'siggdd' onset model based on moigdd, it is for peat PFT,
1907!!                the mechanism are same to moigdd except that the gdd_crit function is sigmoid
1908!_ ================================================================================================================================
1909
1910  SUBROUTINE pheno_siggdd (npts, j, PFTpresent, allow_initpheno, gdd, &
1911       time_hum_min, &
1912       t2m_longterm, t2m_month, t2m_week, &
1913       moiavail_week, moiavail_month, &
1914       begin_leaves)
1915
1916    !
1917    !! 0. Variable and parameter declaration
1918    !
1919
1920    !
1921    !! 0.1 Input variables
1922    !
1923    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1924    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1925    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1926    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to decalre the beginning of the
1927                                                                                !! growing season? (true/false)
1928    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gdd             !! growing degree days, calculated since leaves
1929                                                                                !! have fallen (C)
1930    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: time_hum_min    !! time elapsed since strongest moisture
1931                                                                                !! availability (days)
1932    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm    !! "long term" 2 meter temperatures (K)
1933    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1934    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1935    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week   !! "weekly" moisture availability (0-1, unitless)
1936    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month  !! "monthly" moisture availability (0-1, unitless)
1937
1938    !
1939    !! 0.2 Output variables
1940    !
1941    !
1942    !! 0.3 Modified variables
1943    !
1944    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1945
1946    !
1947    !! 0.4 Local variables
1948    !
1949    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
1950                                                                                                !! set for tree or grass
1951                                                                                                !! (0-1, unitless)
1952    REAL(r_std), DIMENSION(npts)                             :: tl                              !! long term temperature (C)
1953    REAL(r_std), DIMENSION(npts)                             :: gdd_crit                        !! critical GDD (C)
1954    INTEGER(i_std)                                           :: i                               !! index (unitless)
1955
1956!_ ================================================================================================================================
1957
1958    IF (printlev>=3) WRITE(numout,*) 'Entering siggdd'
1959
1960    !
1961    !! 1. Initializations
1962    !
1963
1964    !
1965    !! 1.1 first call - outputs the name of the onset model, the values of the 
1966    !!     moisture availability parameters for tree and grass, and the value of the
1967    !!     critical monthly temperature.
1968    !
1969
1970    IF ( firstcall_siggdd ) THEN
1971
1972       WRITE(numout,*) 'pheno_siggdd:'
1973       WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1974       WRITE(numout,*) '         trees (::moiavail_always_tree) :', moiavail_always_tree
1975       WRITE(numout,*) '         grasses (::moiavail_always_grass) :', moiavail_always_grass
1976       WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter (::t_always): ', &
1977            t_always
1978
1979       firstcall_siggdd = .FALSE.
1980    ENDIF
1981
1982    !
1983    !! 1.2 initialize output
1984    !
1985
1986    begin_leaves(:,j) = .FALSE.
1987
1988    !
1989    !! 1.3 check the critical values ::gdd and ::pheno_crit_hum_min_time are defined.
1990    !!     If not, stop.
1991    !
1992
1993    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1994
1995       WRITE(numout,*) 'siggdd: pheno_gdd_crit is undefined for PFT',j
1996       CALL ipslerr_p(3,'stomate phenology','pheno_gdd is undefined for this PFT','','')
1997
1998    ENDIF
1999
2000    IF ( hum_min_time(j) .EQ. undef ) THEN
2001
2002       WRITE(numout,*) 'siggdd: hum_min_time is undefined for PFT',j
2003       CALL ipslerr_p(3,'stomate phenology','hum_min is undefined for this PFT','','')
2004
2005    ENDIF
2006    !
2007    !! 1.4 set the critical moisture availability above which we always detect the beginning of the
2008    !!     growing season - set as the moisture availability for trees or grass.
2009    !
2010
2011    IF ( is_tree(j) ) THEN
2012       moiavail_always = moiavail_always_tree
2013    ELSE
2014       moiavail_always = moiavail_always_grass
2015    ENDIF
2016    !
2017    !! 2. Check if biometeorological conditions are favourable for leaf growth.
2018    !!    The PFT has to be there, the start of growing season must be allowed,
2019    !!    and GDD has to be defined.
2020    !
2021
2022    DO i = 1, npts
2023
2024       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
2025            ( gdd(i,j) .NE. undef )                           ) THEN
2026
2027          !! 2.1 Calculate the critical GDD (::gdd_crit), which is a function of the PFT-dependent
2028          !!     critical GDD and the "long term" 2 meter air temperatures
2029
2030          tl(i) = t2m_longterm(i) - ZeroCelsius
2031       !   gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
2032       !        tl(i)*tl(i)*pheno_gdd_crit(j,3)
2033          gdd_crit(i)=1.92717865E+5/(1+EXP(-8.13142588E-2*(tl(i)-8.78682785E+1)))
2034          !! 2.2 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
2035          !!     This occurs if the critical gdd (::gdd_crit) has been reached
2036          !!     AND that is temperature increasing, which is true either if the monthly
2037          !!     temperature being higher than the threshold ::t_always, OR if the weekly
2038          !!     temperature is higher than the monthly,
2039          !!     AND finally that there is sufficient moisture availability, which is
2040          !!     the same condition as for the ::pheno_moi onset model.
2041          !!     AND when pheno_moigdd_t_crit is set(for C4 grass), if the average temperature threshold is reached
2042
2043          IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
2044               ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
2045                 ( t2m_month(i) .GT. t_always )  ) .AND. &
2046               ( ( ( time_hum_min(i,j) .GT. hum_min_time(j) ) .AND. &
2047                 ( moiavail_week(i,j) .GT. moiavail_month(i,j) ) ) .OR. &
2048                 ( moiavail_month(i,j) .GE. moiavail_always )  ) .AND. &
2049               ( ( pheno_moigdd_t_crit(j) == undef ) .OR. &
2050                 (t2m_month(i) .GT. (ZeroCelsius + pheno_moigdd_t_crit(j))) ) ) THEN
2051
2052             begin_leaves(i,j) = .TRUE.
2053          ENDIF
2054
2055       ENDIF        ! PFT there and start of growing season allowed
2056
2057    ENDDO
2058
2059    IF (printlev>=4) WRITE(numout,*) 'Leaving siggdd'
2060
2061  END SUBROUTINE pheno_siggdd
2062
2063
2064END MODULE stomate_phenology
Note: See TracBrowser for help on using the repository browser.