source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/stomate_phenology.f90 @ 6737

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

Merge: from revisions [4491:4695/trunk/ORCHIDEE]

Merge done in [4671:4718/perso/albert.jornet/MICT_MERGE]

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