source: branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_phenology.f90 @ 6393

Last change on this file since 6393 was 5614, checked in by josefine.ghattas, 6 years ago

Add reinitialization of leaf_age and leaf_frac. See ticket #444

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