source: tags/ORCHIDEE_2_0/ORCHIDEE/src_stomate/stomate_phenology.f90 @ 5110

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

Allow vegetation to start grow again after it has died out. Made flag ALWAYS_INIT pft dependent.

See ticket #417

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 83.0 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          ENDIF
445        END DO
446      END DO
447    END IF
448
449
450    DO j = 2,nvm ! Loop over # PFTs
451
452       age_reset(:) = .FALSE.
453
454       DO i = 1, npts
455
456          IF ( begin_leaves(i,j) ) THEN
457
458             !! 4.1 First minimum biomass is calculated using the following equation:
459             !!     \latexonly
460             !!     \input{phenology_lm_min_eqn2.tex}
461             !!     \endlatexonly
462             !!     \n
463
464             lm_min(i) = lai_initmin(j) / sla(j)
465
466             !! 4.2 If leaf biomass is lower than the minimum biomass then biomass must be allocated from the carbohydrate
467             !!     reserves to leaves and roots.
468
469             IF ( biomass(i,j,ileaf,icarbon) .LT. lm_min(i) ) THEN
470
471                !
472                !! 4.2.1 Determine how much biomass is available to use
473                !!       First calculate how much biomass is wanted/required
474                !!       (::bm_wanted = 2 x the minimum leaf biomass).
475                !
476
477                bm_wanted(i) = 2. * lm_min(i)
478
479                !! 4.2.2 If the biomass in the carbohydrate reserves is less than the required biomass
480                !!       take the required amount of carbon from the atmosphere and put it into the
481                !!       carbohydrate reserve. This only occurs if the parameter ::always_init
482                !!       (set at beginning of this ::subroutine) is TRUE. Default is FALSE.
483
484                IF ( always_init(j) .AND. ( biomass(i,j,icarbres,icarbon) .LT. bm_wanted(i) ) ) THEN
485                   !NV passage 2D
486                   co2_to_bm(i,j) = co2_to_bm(i,j) + ( bm_wanted(i) - biomass(i,j,icarbres,icarbon) ) / dt
487
488                   biomass(i,j,icarbres,icarbon) = bm_wanted(i)
489
490                ENDIF
491               
492                !! 4.2.3 The biomass available to use is set to be the minimum of the biomass of the carbohydrate reservoir (if
493                !! carbon not taken from the atmosphere), and the wanted biomass.
494                bm_use(i) = MIN( biomass(i,j,icarbres,icarbon), bm_wanted(i) )
495
496                !
497                !! 4.2.4 divide the biomass which is available to use equally between the leaves and roots.
498                !
499
500                biomass(i,j,ileaf,icarbon) = biomass(i,j,ileaf,icarbon) + bm_use(i) / 2.
501
502                biomass(i,j,iroot,icarbon) = biomass(i,j,iroot,icarbon) + bm_use(i) / 2.
503
504                !
505                !! 4.2.5 decrease carbohydrate reservoir biomass by the amount that's been allocated to the leaves and roots
506                !
507
508                biomass(i,j,icarbres,icarbon) = biomass(i,j,icarbres,icarbon) - bm_use(i)
509
510                !
511                !! 4.2.6 set reset leaf age distribution (::age_reset) flag. Default is TRUE.
512                !     (done later for better vectorization)
513                !
514
515                age_reset(i) = .TRUE.
516
517             ENDIF  ! leaf mass is very low
518
519             !
520             !! 4.3 reset when_growthinit counter: start of the growing season
521             !
522
523             when_growthinit(i,j) = zero
524
525          ENDIF    ! start of the growing season
526
527       ENDDO      ! loop over grid points
528
529       !
530       !! 4.4 reset leaf age distribution where necessary (i.e. when age_reset is TRUE)
531       !!     simply say that everything is in the youngest age class
532       !
533
534       !! 4.4.1 fractions - set the youngest age class fraction to 1 and all other leaf age class fractions to 0.
535
536       WHERE ( age_reset(:) )
537          leaf_frac(:,j,1) = un
538       ENDWHERE
539       DO m = 2, nleafages
540          WHERE ( age_reset(:) )
541             leaf_frac(:,j,m) = zero
542          ENDWHERE
543       ENDDO
544
545       !! 4.4.2 ages - set all leaf ages to 0.
546
547       DO m = 1, nleafages
548          WHERE ( age_reset(:) )
549             leaf_age(:,j,m) = zero
550          ENDWHERE
551       ENDDO
552
553    ENDDO        ! loop over # PFTs
554
555
556    IF (printlev>=3) WRITE(numout,*) 'Leaving phenology'
557
558  END SUBROUTINE phenology
559
560
561!! ================================================================================================================================
562!! SUBROUTINE   : pheno_hum
563!!
564!>\BRIEF          The 'hum' onset model initiate leaf onset based exclusively on moisture
565!!                availability criteria.
566!!                Currently no PFTs are assigned to this onset model.
567!!
568!! DESCRIPTION  : This model is for tropical biomes, where temperatures are high but moisture
569!!                might be a limiting factor on growth. It is based on leaf onset model 4a in
570!!                Botta et al. (2000), which adopts the approach of Le Roux (1995). \n
571!!                Leaf onset occurs if the monthly moisture availability is still quite
572!!                low (i.e. lower than the weekly availability), but the weekly availability is
573!!                higher than the critical threshold ::availability_crit (as it reacts faster),
574!!                which indicates the weekly moisture availability is increasing.
575!!                OR if the monthly moisture availability is high enough (i.e. above the
576!!                threshold value ::moiavail_always), leaf onset is initiated if this has not
577!!                already happened. This allows vegetation in arid areas to respond to rapidly
578!!                changing soil moisture conditions (Krinner et al., 2005). \n
579!!                The critical weekly moisture availability threshold (::availability_crit), is
580!!                calculated in this subroutine, and is a function of last year's maximum and
581!!                minimum moisture availability and the PFT-dependent parameter
582!!                ::hum_frac, which specifies how much of last year's available
583!!                moisture is required for leaf onset, as per the equation:
584!!                \latexonly
585!!                \input{phenology_moi_availcrit_eqn3.tex}
586!!                \endlatexonly
587!!                \n
588!!                ::hum_frac is set for each PFT in ::stomate_data from a table
589!!                which contains all the PFT values (::hum_frac_tab) in ::stomate_constants. \n
590!!                Last year's maximum and minimum moisture availability and the monthly and
591!!                weekly moisture availability are 
592!!                The ::pheno_hum subroutine is called in the subroutine ::phenology.
593!!
594!! RECENT CHANGE(S): None
595!!
596!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start.
597!!
598!! REFERENCE(S) :
599!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
600!! A global prognostic scheme of leaf onset using satellite data,
601!! Global Change Biology, 207, 337-347.
602!! - Le Roux, X. (1995), Etude et modelisation des echanges d'eau et d'energie
603!! sol-vegetation-atmosphere dans une savane humide, PhD Thesis, University
604!! Pierre et Marie Curie, Paris, France.
605!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
606!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
607!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
608!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
609!!
610!! FLOWCHART    :
611!! \latexonly
612!! \includegraphics[scale = 1]{pheno_hum.png}
613!! \endlatexonly
614!! \n             
615!_ ================================================================================================================================
616
617  SUBROUTINE pheno_hum (npts, j, PFTpresent, allow_initpheno, &
618       moiavail_month, moiavail_week, &
619       maxmoiavail_lastyear, minmoiavail_lastyear, &
620       begin_leaves)
621
622    !
623    !! 0. Variable and parameter declarations
624    !
625
626    !
627    !! 0.1 Input variables
628    !
629    INTEGER(i_std), INTENT(in)                                             :: npts                  !! Domain size - number of
630                                                                                                    !! grid cells (unitless)
631    INTEGER(i_std), INTENT(in)                                             :: j                     !! PFT index (unitless)
632    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                               :: PFTpresent            !! PFT exists (true/false)
633    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                               :: allow_initpheno       !! are we allowed to
634                                                                                                    !! declare the beginning of
635                                                                                                    !! the growing season?
636                                                                                                    !! (true/false)
637    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: moiavail_month        !! "monthly" moisture
638                                                                                                    !! availability (0-1, unitless)
639    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: moiavail_week         !! "weekly" moisture
640                                                                                                    !! availability (0-1, unitless)
641    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: maxmoiavail_lastyear  !! last year's maximum
642                                                                                                    !! moisture availability
643                                                                                                    !! (0-1, unitless)
644    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: minmoiavail_lastyear  !! last year's minimum
645                                                                                                    !! moisture availability
646                                                                                                    !! (0-1, unitless)
647
648    !
649    !! 0.2 Output variables
650    !
651
652    !
653    !! 0.3 Modified variables
654    !
655    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                            :: begin_leaves          !! signal to start putting
656                                                                                                    !! leaves on (true/false)
657
658    !
659    !! 0.4 Local variables
660    !
661    REAL(r_std)                                                            :: moiavail_always       !! critical monthly
662                                                                                                    !! moisture availability - set
663                                                                                                    !! for tree or grass
664                                                                                                    !! (0-1, unitless)
665    REAL(r_std), DIMENSION(npts)                                           :: availability_crit     !! critical weekly moisture
666                                                                                                    !! availability (0-1, unitless)
667    INTEGER(i_std)                                                         :: i                     !! index (unitless)
668
669!_ ================================================================================================================================
670
671    IF (printlev>=3) WRITE(numout,*) 'Entering hum'
672
673    !
674    !! 1. Initializations
675    !
676
677    !
678    !! 1.1 first call - outputs the name of onset model and the moisture availability
679    !!     parameters for tree and grass
680    !
681
682    IF ( firstcall_hum ) THEN
683
684       IF (printlev >= 2) THEN
685          WRITE(numout,*) 'pheno_hum:'
686          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
687          WRITE(numout,*) '         trees (::moiavail_always_tree): ', moiavail_always_tree
688          WRITE(numout,*) '         grasses (::moiavail_always_grass):', moiavail_always_grass
689       END IF
690       firstcall_hum = .FALSE.
691
692    ENDIF
693
694    !
695    !! 1.2 initialize output
696    !
697
698    begin_leaves(:,j) = .FALSE.
699
700    !
701    !! 1.3 check the critical value ::hum_frac is defined. If not, stop.
702    !
703
704    IF ( hum_frac(j) .EQ. undef ) THEN
705
706       WRITE(numout,*) 'hum: hum_frac is undefined for PFT (::j)',j
707       CALL ipslerr_p(3,'stomate phenology','hum_frac is undefined for this PFT','','')
708
709    ENDIF
710
711    !
712    !! 1.4 set the critical monthly moisture availability above which we always detect the beginning of the
713    !!     growing season - set as the moisture availability for trees or grass.
714    !
715
716    IF ( is_tree(j) ) THEN
717       moiavail_always = moiavail_always_tree
718    ELSE
719       moiavail_always = moiavail_always_grass
720    ENDIF
721
722    !
723    !! 2. Check if biometeorological conditions are favourable for leaf growth.
724    !! The PFT has to be there and start of growing season must be allowed
725    !
726
727    DO i = 1, npts
728
729       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
730
731          !! 2.1 Calculate the critical weekly moisture availability: depends linearly on the last year
732          !! minimum and maximum moisture availabilities, and on the parameter ::hum_frac.
733
734          availability_crit(i) = minmoiavail_lastyear(i,j) + hum_frac(j) * &
735               ( maxmoiavail_lastyear(i,j) - minmoiavail_lastyear(i,j) )
736
737          !! 2.2 Determine if growing season should start (if so, ::begin_leaves set to TRUE).
738          !!     Leaf onset occurs if the monthly moisture availability is still quite
739          !!     low (i.e. lower than the weekly availability), but the weekly availability is
740          !!     already higher than the critical threshold ::availability_crit (as it reacts faster),
741          !!     which indicates the weekly moisture availability is increasing.
742          !!     OR if the monthly moisture availability is high enough (i.e. above the threshold value
743          !!     ::moiavail_always), leaf onset is initiated if this has not already happened.
744
745          IF ( ( ( moiavail_week(i,j)  .GE. availability_crit(i) ) .AND. &
746               ( moiavail_month(i,j) .LT. moiavail_week(i,j) )   ) .OR. &
747               ( moiavail_month(i,j) .GE. moiavail_always )                ) THEN
748             begin_leaves(i,j) = .TRUE.
749          ENDIF
750
751       ENDIF        ! PFT there and start of growing season allowed
752
753    ENDDO ! end loop over grid points
754
755    IF (printlev>=4) WRITE(numout,*) 'Leaving hum'
756
757  END SUBROUTINE pheno_hum
758
759
760!! ================================================================================================================================
761!! SUBROUTINE   : pheno_moi
762!!
763!>\BRIEF          The 'moi' onset model (::pheno_moi) initiates leaf onset based exclusively
764!!                on moisture availability criteria.
765!!                It is very similar to the 'hum' onset model but instead of the weekly moisture
766!!                availability being higher than a constant threshold, the condition is that the
767!!                moisture minimum happened a sufficiently long time ago.
768!!                Currently PFT 3 (Tropical Broad-leaved Raingreen) is assigned to this model.
769!!
770!! DESCRIPTION  : This model is for tropical biomes, where temperatures are high but moisture
771!!                might be a limiting factor on growth. It is based on leaf onset model 4b in
772!!                Botta et al. (2000).
773!!                Leaf onset begins if the plant moisture availability minimum was a sufficiently 
774!!                time ago, as specified by the PFT-dependent parameter ::hum_min_time
775!!                AND if the "monthly" moisture availability is lower than the "weekly"
776!!                availability (indicating that soil moisture is increasing).
777!!                OR if the monthly moisture availability is high enough (i.e. above the threshold
778!!                value ::moiavail_always), leaf onset is initiated if this has not already
779!!                happened. \n
780!!                ::hum_min_time is set for each PFT in ::stomate_data, and is
781!!                defined in the table ::hum_min_time_tab in ::stomate_constants. \n
782!!                ::moiavail_always is defined for both tree and grass in this subroutine
783!!                (set to 1. and 0.6 respectively). \n
784!!                The ::pheno_moi subroutine is called in the subroutine ::phenology.
785!!
786!! RECENT CHANGE(S): None
787!!       
788!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start.
789!!
790!! REFERENCE(S) :
791!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
792!! A global prognostic scheme of leaf onset using satellite data,
793!! Global Change Biology, 207, 337-347.
794!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
795!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
796!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
797!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
798!!
799!! FLOWCHART    :
800!! \latexonly
801!! \includegraphics[scale = 1]{pheno_moi.png}
802!! \endlatexonly
803!! \n
804!_ ================================================================================================================================
805
806  SUBROUTINE pheno_moi (npts, j, PFTpresent, allow_initpheno, &
807       time_hum_min, &
808       moiavail_month, moiavail_week, &
809       begin_leaves)
810
811    !
812    !! 0. Variable and parameter declaration
813    !
814
815    !
816    !! 0.1 Input variables
817    !
818    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
819    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
820    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
821    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
822                                                                                !! growing season? (true/false)
823    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: time_hum_min    !! time elapsed since strongest moisture
824                                                                                !! availability (days)
825    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month  !! "monthly" moisture availability (0-1, unitless)
826    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week   !! "weekly" moisture availability (0-1, unitless)
827
828    !
829    !! 0.2 Output variables
830    !
831    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
832
833    !
834    !! 0.3 Modified variables
835    !
836
837    !
838    !! 0.4 Local variables
839    !
840    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
841                                                                                                !! set for tree or grass
842                                                                                                !! (0-1, unitless)
843    INTEGER(i_std)                                           :: i                               !! index (unitless)
844
845!_ ================================================================================================================================
846
847    IF (printlev>=3) WRITE(numout,*) 'Entering moi'
848
849    !
850    !! 1. Initializations
851    !
852
853    !
854    !! 1.1 first call - outputs the name of onset model and the moisture availability
855    !!     parameters for tree and grass
856    !
857
858    IF ( firstcall_moi ) THEN
859       IF (printlev >= 2) THEN
860          WRITE(numout,*) 'pheno_moi:'
861          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
862          WRITE(numout,*) '         trees (::moiavail_always_tree):', moiavail_always_tree
863          WRITE(numout,*) '         grasses (::moiavail_always_grass):', moiavail_always_grass
864       END IF
865       firstcall_moi = .FALSE.
866
867    ENDIF
868
869    !
870    !! 1.2 initialize output
871    !
872
873    begin_leaves(:,j) = .FALSE.
874
875    !
876    !! 1.3 check the critical value ::hum_min_time is definded. If not, stop
877    !
878
879    IF ( hum_min_time(j) .EQ. undef ) THEN
880
881       WRITE(numout,*) 'moi: hum_min_time is undefined for PFT (::j) ',j
882       CALL ipslerr_p(3,'stomate phenology','hum_min_time is undefined for this PFT','','')
883
884    ENDIF
885
886    !
887    !! 1.4 set the critical monthly moisture availability above which we always detect the beginning of the
888    !!     growing season - set as the moisture availability for trees or grass.
889    !
890
891    IF ( is_tree(j) ) THEN
892       moiavail_always = moiavail_always_tree
893    ELSE
894       moiavail_always = moiavail_always_grass
895    ENDIF
896
897    !
898    !! 2. Check if biometeorological conditions are favourable for leaf growth.
899    !! The PFT has to be there and start of growing season must be allowed.
900    !
901
902    DO i = 1, npts
903
904       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
905         
906          !! 2.1 Determine if growing season should start (if so, ::begin_leaves set to TRUE).
907          !!     The favorable season starts if the moisture minimum (::time_hum_min) was a sufficiently long
908          !!     time ago, i.e. greater than the threshold specified by the parameter ::hum_min_time
909          !!     and if the "monthly" moisture availability is lower than the "weekly"
910          !!     availability (indicating that soil moisture is increasing).
911          !!     OR if the monthly moisture availability is high enough (i.e. above the threshold value
912          !!     ::moiavail_always), initiate the growing season if this has not happened yet.
913
914          IF  ( ( ( moiavail_week(i,j) .GT. moiavail_month(i,j) ) .AND. &
915               ( time_hum_min(i,j) .GT. hum_min_time(j) )    ) .OR. &
916               ( moiavail_month(i,j) .GE. moiavail_always )                     ) THEN
917             begin_leaves(i,j) = .TRUE.
918          ENDIF
919
920       ENDIF        ! PFT there and start of growing season allowed
921
922    ENDDO ! end loop over grid points
923
924    IF (printlev>=4) WRITE(numout,*) 'Leaving moi'
925
926  END SUBROUTINE pheno_moi
927
928
929!! ================================================================================================================================
930!! SUBROUTINE   : pheno_humgdd
931!!
932!>\BRIEF          The 'humgdd' onset model initiates leaf onset based on mixed conditions of
933!!                temperature and moisture availability criteria.
934!!                Currently no PFTs are assigned to this onset model.
935!!
936!! DESCRIPTION  : In this model the Growing Degree Day (GDD) model (Chuine, 2000) is combined
937!!                with the 'hum' onset model (::pheno_hum), which has previously been described,
938!!                in order to account for dependence on both temperature and moisture conditions
939!!                in warmer climates. \n.
940!!                The GDD model specifies that daily temperatures above a threshold of -5 
941!!                degrees C are summed, minus this threshold, giving the GDD, starting from
942!!                the beginning of the dormancy period (::time_lowgpp>0), i.e. since the leaves
943!!                were lost. \n.
944!!                The dormancy time-length is represented by the variable
945!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
946!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
947!!                it is set to zero. \n
948!!                Leaf onset begins when the a PFT-dependent GDD-threshold is reached.
949!!                In addition there are temperature and moisture conditions.
950!!                The temperature condition specifies that the monthly temperature has to be
951!!                higher than a constant threshold (::t_always) OR
952!!                the weekly temperature is higher than the monthly temperature.
953!!                There has to be at least some moisture. The moisture condition
954!!                is exactly the same as the 'hum' onset model (::pheno_hum), which has already
955!!                been described. \n
956!!                The GDD (::gdd_m5_dormance) is calculated in ::stomate_season. GDD is set to
957!!                undef if beginning of the growing season detected, i.e. when there is GPP
958!!                (::time_lowgpp>0).
959!!                The parameter ::t_always is defined as 10 degrees C in this subroutine,
960!!                as are the parameters ::moisture_avail_tree and ::moisture_avail_grass
961!!                (set to 1 and 0.6 respectively), which are used in the moisture condition
962!!                (see ::pheno_moi onset model description). \n
963!!                The PFT-dependent GDD threshold (::gdd_crit) is calculated as in the onset
964!!                model ::pheno_humgdd, using the equation:
965!!                \latexonly
966!!                \input{phenology_hummoigdd_gddcrit_eqn4.tex}
967!!                \endlatexonly
968!!                \n
969!!                The three GDDcrit parameters (::gdd(j,*)) are set for each PFT in
970!!                ::stomate_data, and three tables defining each of the three critical GDD
971!!                parameters for each PFT is given in ::gdd_crit1_tab, ::gdd_crit2_tab and
972!!                ::gdd_crit3_tab in ::stomate_constants. \n
973!!                The ::pheno_humgdd subroutine is called in the subroutine ::phenology.
974!!
975!! RECENT CHANGES: None
976!!               
977!! MAIN OUTPUT VARIABLES: ::begin_leaves - specifies whether leaf growth can start
978!!
979!! REFERENCE(S) :
980!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
981!! A global prognostic scheme of leaf onset using satellite data,
982!! Global Change Biology, 207, 337-347.
983!! - Chuine, I (2000), A unified model for the budburst of trees, Journal of
984!! Theoretical Biology, 207, 337-347.
985!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
986!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
987!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
988!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
989!!
990!! FLOWCHART    :
991!! \latexonly
992!! \includegraphics[scale = 1]{pheno_humgdd.png}
993!! \endlatexonly
994!! \n             
995!_ ================================================================================================================================
996
997  SUBROUTINE pheno_humgdd (npts, j, PFTpresent, allow_initpheno, gdd, &
998       maxmoiavail_lastyear, minmoiavail_lastyear, &
999       t2m_longterm, t2m_month, t2m_week, &
1000       moiavail_week, moiavail_month, &
1001       begin_leaves)
1002
1003    !
1004    !! 0. Variable and parameter declaration
1005    !
1006
1007    !
1008    !! 0.1 Input variables
1009    !
1010    INTEGER(i_std), INTENT(in)                               :: npts                    !! Domain size - number of grid cells
1011                                                                                        !! (unitless)
1012    INTEGER(i_std), INTENT(in)                               :: j                       !! PFT index (unitless)
1013    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent              !! PFT exists (true/false)
1014    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno         !! are we allowed to declare the beginning
1015                                                                                        !! of the growing season? (true/false)
1016    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gdd                     !! growing degree days, calculated since
1017                                                                                        !! leaves have fallen (C)
1018    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: maxmoiavail_lastyear    !! last year's maximum moisture
1019                                                                                        !! availability (0-1, unitless)
1020    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: minmoiavail_lastyear    !! last year's minimum moisture
1021                                                                                        !! availability (0-1, unitless)
1022    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm            !! "long term" 2 meter temperatures (K)
1023    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month               !! "monthly" 2-meter temperatures (K)
1024    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week                !! "weekly" 2-meter temperatures (K)
1025    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week           !! "weekly" moisture availability
1026                                                                                        !! (0-1, unitless)
1027    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month          !! "monthly" moisture availability
1028                                                                                        !! (0-1, unitless)
1029
1030    !
1031    !! 0.2 Output variables
1032    !
1033    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves            !! signal to start putting leaves on
1034                                                                                        !! (true/false)
1035
1036    !
1037    !! 0.3 Modified variables
1038    !
1039
1040    !
1041    !! 0.4 Local variables
1042    !
1043    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
1044                                                                                                !! set for tree or grass
1045                                                                                                !! (0-1, unitless)
1046    REAL(r_std), DIMENSION(npts)                             :: moiavail_crit                   !! critical moisture availability
1047                                                                                                !! (0-1, unitless)
1048    REAL(r_std), DIMENSION(npts)                             :: tl                              !! long term temperature (C)
1049    REAL(r_std), DIMENSION(npts)                             :: gdd_crit                        !! critical GDD (C)
1050    INTEGER(i_std)                                           :: i                               !! index (unitless)
1051
1052!_ ================================================================================================================================
1053
1054    IF (printlev>=3) WRITE(numout,*) 'Entering humgdd'
1055
1056    !
1057    !! 1. Initializations
1058    !
1059
1060    !
1061    !! 1.1 first call - outputs the name of the onset model, the values of the 
1062    !!     moisture availability parameters for tree and grass, and the value of the
1063    !!     critical monthly temperature.
1064    !
1065
1066    IF ( firstcall_humgdd ) THEN
1067
1068       IF (printlev >= 2) THEN
1069          WRITE(numout,*) 'pheno_humgdd:'
1070          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1071          WRITE(numout,*) '         trees (::moiavail_always_tree): ', moiavail_always_tree
1072          WRITE(numout,*) '         grasses (::moiavail_always_grass): ', moiavail_always_grass
1073          WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter: ', &
1074               t_always
1075       END IF
1076
1077       firstcall_humgdd = .FALSE.
1078
1079    ENDIF
1080
1081    !
1082    !! 1.2 initialize output
1083    !
1084
1085    begin_leaves(:,j) = .FALSE.
1086
1087    !
1088    !! 1.3 check the critical values ::gdd and ::pheno_crit_hum_frac are defined.
1089    !!     If not, stop.
1090    !
1091
1092    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1093
1094       WRITE(numout,*) 'humgdd: pheno_gdd_crit is undefined for PFT (::j) ',j
1095       CALL ipslerr_p(3,'stomate phenology','pheno_gdd_crit is undefined for this PFT','','')
1096
1097    ENDIF
1098
1099    IF ( hum_frac(j) .EQ. undef ) THEN
1100
1101       WRITE(numout,*) 'humgdd: hum_frac is undefined for PFT (::j) ',j
1102       CALL ipslerr_p(3,'stomate phenology','hum_frac is undefined for this PFT','','')
1103
1104    ENDIF
1105
1106    !
1107    !! 1.4 set the critical moisture availability above which we always detect the beginning of the
1108    !!     growing season - set as the moisture availability for trees or grass.
1109    !
1110
1111    IF ( is_tree(j) ) THEN
1112       moiavail_always = moiavail_always_tree
1113    ELSE
1114       moiavail_always = moiavail_always_grass
1115    ENDIF
1116
1117    !
1118    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1119    !!   The PFT has to be there, start of growing season must be allowed,
1120    !!   and GDD has to be defined.
1121    !
1122
1123    DO i = 1, npts
1124
1125       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1126            ( gdd(i,j) .NE. undef )                           ) THEN
1127
1128          !! 2.1 Calculate the critical weekly moisture availability: depends linearly on the last year
1129          !! minimum and maximum moisture availabilities, and on the parameter ::hum_frac.,
1130          !! (as in the ::pheno_hum model), as per the equation:
1131
1132          moiavail_crit(i) = minmoiavail_lastyear(i,j) + hum_frac(j) * &
1133               ( maxmoiavail_lastyear(i,j) - minmoiavail_lastyear(i,j) )
1134
1135          !! 2.2 Calculate the critical GDD (::gdd_crit), which is a function of the PFT-dependent
1136          !!     critical GDD and the "long term" 2 meter air temperatures. 
1137
1138          tl(i) =  t2m_longterm(i) - ZeroCelsius
1139          gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
1140               tl(i)*tl(i)*pheno_gdd_crit(j,3)
1141         
1142          !! 2.3 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1143          !!     - Has the critical gdd been reached and is the temperature increasing?
1144          !!     - Is there at least some humidity/moisture availability?
1145          !!     This occurs if the critical gdd (::gdd_crit) has been reached
1146          !!     AND that is temperature increasing, which is true either if the monthly
1147          !!     temperature being higher than the threshold ::t_always, OR if the weekly
1148          !!     temperature is higher than the monthly,
1149          !!     AND finally that there is sufficient moisture availability, which is
1150          !!     the same condition as for the ::pheno_hum onset model.
1151
1152          IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
1153               ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
1154               ( t2m_month(i) .GT. t_always )          ) .AND. &
1155               ( ( ( moiavail_week(i,j)  .GE. moiavail_crit(i) ) .AND. &
1156               ( moiavail_month(i,j) .LT. moiavail_crit(i) )        ) .OR. &
1157               ( moiavail_month(i,j) .GE. moiavail_always )                   ) )  THEN
1158             begin_leaves(i,j) = .TRUE.
1159          ENDIF
1160
1161       ENDIF        ! PFT there and start of growing season allowed
1162
1163    ENDDO ! End loop over grid points
1164
1165    IF (printlev>=4) WRITE(numout,*) 'Leaving humgdd'
1166
1167  END SUBROUTINE pheno_humgdd
1168
1169
1170!! ================================================================================================================================
1171!! SUBROUTINE   : pheno_moigdd
1172!!
1173!>\BRIEF          The 'moigdd' onset model initiates leaf onset based on mixed temperature
1174!!                and moisture availability criteria.
1175!!                Currently PFTs 10 - 13 (C3 and C4 grass, and C3 and C4 agriculture)
1176!!                are assigned to this model.
1177!!
1178!! DESCRIPTION  : This onset model combines the GDD model (Chuine, 2000), as described for
1179!!                the 'humgdd' onset model (::pheno_humgdd), and the 'moi' model, in order
1180!!                to account for dependence on both temperature and moisture conditions in
1181!!                warmer climates. \n
1182!!                Leaf onset begins when the a PFT-dependent GDD threshold is reached.
1183!!                In addition there are temperature and moisture conditions.
1184!!                The temperature condition specifies that the monthly temperature has to be
1185!!                higher than a constant threshold (::t_always) OR
1186!!                the weekly temperature is higher than the monthly temperature.
1187!!                There has to be at least some moisture. The moisture condition
1188!!                is exactly the same as the 'moi' onset model (::pheno_moi), which has
1189!!                already been described. \n
1190!!                GDD is set to undef if beginning of the growing season detected.
1191!!                As in the ::pheno_humgdd model, the parameter ::t_always is defined as
1192!!                10 degrees C in this subroutine, as are the parameters ::moisture_avail_tree
1193!!                and ::moisture_avail_grass (set to 1 and 0.6 respectively), which are used
1194!!                in the moisture condition (see ::pheno_moi onset model description). \n
1195!!                The PFT-dependent GDD threshold (::gdd_crit) is calculated as in the onset
1196!!                model ::pheno_humgdd, using the equation:
1197!!                \latexonly
1198!!                \input{phenology_hummoigdd_gddcrit_eqn4.tex}
1199!!                \endlatexonly
1200!!                \n
1201!!                where i and j are the grid cell and PFT respectively.
1202!!                The three GDDcrit parameters (::gdd(j,*)) are set for each PFT in
1203!!                ::stomate_data, and three tables defining each of the three critical GDD
1204!!                parameters for each PFT is given in ::gdd_crit1_tab, ::gdd_crit2_tab and
1205!!                ::gdd_crit3_tab in ::stomate_constants. \n
1206!!                The ::pheno_moigdd subroutine is called in the subroutine ::phenology.
1207!!
1208!! RECENT CHANGE(S): Added temperature threshold for C4 grass (pheno_moigdd_t_crit), Dan Zhu april 2015
1209!!               
1210!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1211!!
1212!! REFERENCE(S) :
1213!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1214!! A global prognostic scheme of leaf onset using satellite data,
1215!! Global Change Biology, 207, 337-347.
1216!! - Chuine, I (2000), A unified model for the budburst of trees, Journal of
1217!! Theoretical Biology, 207, 337-347.
1218!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1219!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1220!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1221!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1222!! - Still et al., Global distribution of C3 and C4 vegetation: Carbon cycle implications,
1223!! 2003, Global Biogeochemmical Cycles, DOI: 10.1029/2001GB001807.
1224!!
1225!! FLOWCHART    :
1226!! \latexonly
1227!! \includegraphics[scale = 1]{pheno_moigdd.png}
1228!! \endlatexonly
1229!! \n
1230!_ ================================================================================================================================
1231
1232  SUBROUTINE pheno_moigdd (npts, j, PFTpresent, allow_initpheno, gdd, &
1233       time_hum_min, &
1234       t2m_longterm, t2m_month, t2m_week, &
1235       moiavail_week, moiavail_month, &
1236       begin_leaves)
1237
1238    !
1239    !! 0. Variable and parameter declaration
1240    !
1241
1242    !
1243    !! 0.1 Input variables
1244    !
1245    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1246    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1247    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1248    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to decalre the beginning of the
1249                                                                                !! growing season? (true/false)
1250    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gdd             !! growing degree days, calculated since leaves
1251                                                                                !! have fallen (C)
1252    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: time_hum_min    !! time elapsed since strongest moisture
1253                                                                                !! availability (days)
1254    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm    !! "long term" 2 meter temperatures (K)
1255    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1256    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1257    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week   !! "weekly" moisture availability (0-1, unitless)
1258    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month  !! "monthly" moisture availability (0-1, unitless)
1259
1260    !
1261    !! 0.2 Output variables
1262    !
1263
1264    !
1265    !! 0.3 Modified variables
1266    !
1267    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1268
1269    !
1270    !! 0.4 Local variables
1271    !
1272    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
1273                                                                                                !! set for tree or grass
1274                                                                                                !! (0-1, unitless)
1275    REAL(r_std), DIMENSION(npts)                             :: tl                              !! long term temperature (C)
1276    REAL(r_std), DIMENSION(npts)                             :: gdd_crit                        !! critical GDD (C)
1277    INTEGER(i_std)                                           :: i                               !! index (unitless)
1278
1279!_ ================================================================================================================================
1280
1281    IF (printlev>=3) WRITE(numout,*) 'Entering moigdd'
1282
1283    !
1284    !! 1. Initializations
1285    !
1286
1287    !
1288    !! 1.1 first call - outputs the name of the onset model, the values of the 
1289    !!     moisture availability parameters for tree and grass, and the value of the
1290    !!     critical monthly temperature.
1291    !
1292
1293    IF ( firstcall_moigdd ) THEN
1294
1295       IF (printlev >= 2) THEN
1296          WRITE(numout,*) 'pheno_moigdd:'
1297          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1298          WRITE(numout,*) '         trees (::moiavail_always_tree) :', moiavail_always_tree
1299          WRITE(numout,*) '         grasses (::moiavail_always_grass) :', moiavail_always_grass
1300          WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter (::t_always): ', &
1301               t_always
1302       END IF
1303       firstcall_moigdd = .FALSE.
1304
1305    ENDIF
1306
1307    !
1308    !! 1.2 initialize output
1309    !
1310
1311    begin_leaves(:,j) = .FALSE.
1312
1313    !
1314    !! 1.3 check the critical values ::gdd and ::pheno_crit_hum_min_time are defined.
1315    !!     If not, stop.
1316    !
1317
1318    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1319
1320       WRITE(numout,*) 'moigdd: pheno_gdd_crit is undefined for PFT',j
1321       CALL ipslerr_p(3,'stomate phenology','pheno_gdd is undefined for this PFT','','')
1322
1323    ENDIF
1324
1325    IF ( hum_min_time(j) .EQ. undef ) THEN
1326
1327       WRITE(numout,*) 'moigdd: hum_min_time is undefined for PFT',j
1328       CALL ipslerr_p(3,'stomate phenology','hum_min is undefined for this PFT','','')
1329
1330    ENDIF
1331
1332    !
1333    !! 1.4 set the critical moisture availability above which we always detect the beginning of the
1334    !!     growing season - set as the moisture availability for trees or grass.
1335    !
1336
1337    IF ( is_tree(j) ) THEN
1338       moiavail_always = moiavail_always_tree
1339    ELSE
1340       moiavail_always = moiavail_always_grass
1341    ENDIF
1342
1343    !
1344    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1345    !!    The PFT has to be there, the start of growing season must be allowed,
1346    !!    and GDD has to be defined.
1347    !
1348
1349    DO i = 1, npts
1350
1351       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1352            ( gdd(i,j) .NE. undef )                           ) THEN
1353         
1354          !! 2.1 Calculate the critical GDD (::gdd_crit), which is a function of the PFT-dependent
1355          !!     critical GDD and the "long term" 2 meter air temperatures
1356         
1357          tl(i) = t2m_longterm(i) - ZeroCelsius
1358          gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
1359               tl(i)*tl(i)*pheno_gdd_crit(j,3)
1360
1361          !! 2.2 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1362          !!     This occurs if the critical gdd (::gdd_crit) has been reached
1363          !!     AND that is temperature increasing, which is true either if the monthly
1364          !!     temperature being higher than the threshold ::t_always, OR if the weekly
1365          !!     temperature is higher than the monthly,
1366          !!     AND finally that there is sufficient moisture availability, which is
1367          !!     the same condition as for the ::pheno_moi onset model.
1368          !!     AND when pheno_moigdd_t_crit is set(for C4 grass), if the average temperature threshold is reached
1369
1370          IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
1371               ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
1372                 ( t2m_month(i) .GT. t_always )  ) .AND. &
1373               ( ( ( time_hum_min(i,j) .GT. hum_min_time(j) ) .AND. &
1374                 ( moiavail_week(i,j) .GT. moiavail_month(i,j) ) ) .OR. &
1375                 ( moiavail_month(i,j) .GE. moiavail_always )  ) .AND. &
1376               ( ( pheno_moigdd_t_crit(j) == undef ) .OR. &
1377                 (t2m_month(i) .GT. (ZeroCelsius + pheno_moigdd_t_crit(j))) ) ) THEN
1378
1379             begin_leaves(i,j) = .TRUE.
1380             
1381          ENDIF
1382
1383       ENDIF        ! PFT there and start of growing season allowed
1384
1385    ENDDO
1386
1387    IF (printlev>=4) WRITE(numout,*) 'Leaving moigdd'
1388
1389  END SUBROUTINE pheno_moigdd
1390
1391
1392!! ================================================================================================================================
1393!! SUBROUTINE   : pheno_ncdgdd
1394!!
1395!>\BRIEF          The Number of Chilling Days - Growing Degree Day (NCD-GDD) model initiates
1396!!                leaf onset if a certain relationship between the number of chilling days (NCD)
1397!!                since leaves were lost, and the growing degree days (GDD) since midwinter, is
1398!!                fulfilled.
1399!!                Currently PFT 6 (Temperate Broad-leaved Summergreen) and PFT 8 (Boreal Broad-
1400!!                leaved Summergreen) are assigned to this model.
1401!!
1402!! DESCRIPTION  : Experiments have shown that some
1403!!                species have a "chilling" requirement, i.e. their physiology needs cold
1404!!                temperatures to trigger the mechanism that will allow the following budburst
1405!!                (e.g. Orlandi et al., 2004).
1406!!                An increase in chilling days, defined as a day with a daily mean air
1407!!                temperature below a PFT-dependent threshold, reduces a plant's GDD demand
1408!!                (Cannell and Smith, 1986; Murray et al., (1989); Botta et al., 2000).
1409!!                The GDD threshold therefore decreases as NCD
1410!!                increases, using the following empirical negative explonential law:
1411!!                \latexonly
1412!!                \input{phenology_ncdgdd_gddmin_eqn5.tex}
1413!!                \endlatexonly
1414!!                \n
1415!!                The constants used have been calibrated against data CHECK FOR REFERENCE OR PERSON WHO DID UPDATE.
1416!!                Leaf onset begins if the GDD is higher than the calculated minimum GDD
1417!!                (dependent upon NCD) AND if the weekly temperature is higher than the monthly
1418!!                temperature. This is to ensure the temperature is increasing. \n
1419!!                The dormancy time-length is represented by the variable
1420!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
1421!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
1422!!                it is set to zero. \n
1423!!                The NCD (::ncd_dormance) is calculated in ::stomate_season as 
1424!!                the number of days with a temperature below a PFT-dependent constant threshold
1425!!                (::ncdgdd_temp), starting from the beginning of the dormancy period
1426!!                (::time_lowgpp>0), i.e. since the leaves were lost. \n
1427!!                The growing degree day sum of the temperatures higher than
1428!!                ::ncdgdd_temp (GDD) since midwinter (::gdd_midwinter)
1429!!                is also calculated in ::stomate_season.
1430!!                Midwinter is detected if the monthly temperature is lower than the weekly
1431!!                temperature AND  the monthly temperature is lower than the long-term
1432!!                temperature. ::gdd_minter is therefore set to 0 at the beginning of midwinter
1433!!                and increased with each temperature greater than the PFT-dependent threshold.
1434!!                When midsummer is detected (the opposite of the above conditions),
1435!!                ::gdd_midwinter is set to undef.
1436!!                CHECK! WHEN TO START OF DORMANCY BEEN MODIFIED FROM BOTTA- ADD IN?
1437!!                The ::pheno_ncdgdd subroutine is called in the subroutine ::phenology.
1438!!
1439!! RECENT CHANGE(S): None
1440!!               
1441!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1442!!
1443!! REFERENCE(S) :
1444!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1445!! A global prognostic scheme of leaf onset using satellite data,
1446!! Global Change Biology, 207, 337-347.
1447!! - Cannell, M.J.R. and R.I. Smith (1986), Climatic warming, spring budburst and
1448!! frost damage on trees, Journal of Applied Ecology, 23, 177-191.
1449!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1450!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1451!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1452!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1453!! - Murray, M.B., G.R. Cannell and R.I. Smith (1989), Date of budburst of fifteen
1454!! tree species in Britain following climatic warming, Journal of Applied Ecology,
1455!! 26, 693-700.
1456!! - Orlandi, F., H. Garcia-Mozo, L.V. Ezquerra, B. Romano, E. Dominquez, C. Galan,
1457!! and M. Fornaciari (2004), Phenological olive chilling requirements in Umbria
1458!! (Italy) and Andalusia (Spain), Plant Biosystems, 138, 111-116.
1459!!
1460!! FLOWCHART    :
1461!! \latexonly
1462!! \includegraphics[scale = 1]{pheno_ncdgdd.png}
1463!! \endlatexonly
1464!! \n
1465!_ ================================================================================================================================
1466
1467  SUBROUTINE pheno_ncdgdd (npts, j, PFTpresent, allow_initpheno, &
1468       ncd_dormance, gdd_midwinter, &
1469       t2m_month, t2m_week, begin_leaves)
1470
1471    !
1472    !! 0. Variable and parameter declaration
1473    !
1474
1475    !
1476    !! 0.1 Input variables
1477    !
1478    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1479    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1480    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1481    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
1482                                                                                !! growing season? (true/false)
1483    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: ncd_dormance    !! number of chilling days since leaves were lost
1484                                                                                !! (days)
1485    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: gdd_midwinter   !! growing degree days since midwinter (C)
1486    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1487    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1488
1489    !
1490    !! 0.2 Output variables
1491    !
1492
1493    !
1494    !! 0.3 Modified variables
1495    !
1496    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1497
1498    !
1499    !! 0.4 Local variables
1500    !
1501    INTEGER(i_std)                                           :: i               !! index (unitless)
1502    REAL(r_std)                                              :: gdd_min         !! critical gdd (C)
1503
1504!_ ================================================================================================================================
1505
1506    IF (printlev>=3) WRITE(numout,*) 'Entering ncdgdd'
1507
1508    !
1509    !! 1. Initializations
1510    !
1511
1512    !
1513    !! 1.1 initialize output
1514    !
1515
1516    begin_leaves(:,j) = .FALSE.
1517
1518    !
1519    !! 1.2 check the critical value ::ncdgdd_temp is defined.
1520    !!     If not, stop.
1521    !
1522
1523    IF ( ncdgdd_temp(j) .EQ. undef ) THEN
1524
1525       WRITE(numout,*) 'ncdgdd: ncdgdd_temp is undefined for PFT (::j) ',j
1526       CALL ipslerr_p(3,'stomate phenology','ncdgdd_temp this PFT','','')
1527
1528    ENDIF
1529
1530    !
1531    !! 2. Check if biometeorological conditions are favourable for leaf growth.   
1532    !!    PFT has to be there and start of growing season must be allowed.
1533    !
1534
1535    DO i = 1, npts ! loop over grid points
1536
1537       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1538            ( gdd_midwinter(i,j) .NE. undef ) .AND. &
1539            ( ncd_dormance(i,j) .NE. undef )                  ) THEN
1540
1541          !! 2.1 Calculate the critical gdd, which is related to ::ncd_dormance
1542          !!     using an empirical negative exponential law as described above.           
1543
1544          gdd_min = ( gddncd_ref / exp(gddncd_curve*ncd_dormance(i,j)) - gddncd_offset )
1545
1546          !! 2.2 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1547          !!     This occurs if the critical GDD been reached AND the temperatures are increasing.
1548          !!     If the growing season has started, ::gdd_midwinter is set to "undef".
1549
1550          IF ( ( gdd_midwinter(i,j) .GE. gdd_min ) .AND. &
1551               ( t2m_week(i) .GT. t2m_month(i) ) ) THEN
1552             begin_leaves(i,j) = .TRUE.
1553             gdd_midwinter(i,j)=undef
1554          ENDIF
1555
1556       ENDIF        ! PFT there and start of growing season allowed
1557
1558    ENDDO ! end loop over grid points
1559
1560    IF (printlev>=4) WRITE(numout,*) 'Leaving ncdgdd'
1561
1562  END SUBROUTINE pheno_ncdgdd
1563
1564
1565!! ================================================================================================================================
1566!! SUBROUTINE   : pheno_ngd
1567!!
1568!>\BRIEF          The Number of Growing Days (NGD) leaf onset model initiates leaf onset if the NGD,
1569!!                defined as the number of days with temperature above a constant threshold,
1570!!                exceeds a critical value.
1571!!                Currently PFT 9 (Boreal Leedleleaf Summergreen) is assigned to this model.
1572!!
1573!! DESCRIPTION    The NGD model is a variant of the GDD model. The model was proposed by Botta et
1574!!                al. (2000) for boreal and arctic biomes, and is designed to estimate
1575!!                leaf onset after the end of soil frost.
1576!!                The NDG (::ngd_minus5) is the number of days with a daily mean air
1577!!                temperature of greater than -5 degrees C,
1578!!                starting from the beginning of the dormancy period (i.e. time since the leaves
1579!!                were lost/GPP below a certain threshold).
1580!!                Leaf onset begins if the NGD is higher than the PFT-dependent constant threshold,
1581!!                ::ngd,  AND if the weekly temperature is higher than the monthly
1582!!                temperature. \n
1583!!                The dormancy time-length is represented by the variable
1584!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
1585!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
1586!!                it is set to zero. \n
1587!!                ::ngd_minus5 is also calculated in ::stomate_season. It is initialised at the
1588!!                beginning of the dormancy period (::time_lowgpp>0), and increased by the
1589!!                stomate time step when the temperature > -5 degrees C. \n
1590!!                ::ngd is set for each PFT in ::stomate_data, and a
1591!!                table defining the minimum NGD for each PFT is given in ::ngd_crit_tab
1592!!                in ::stomate_constants. \n
1593!!                The ::pheno_ngd subroutine is called in the subroutine ::phenology.     
1594!!
1595!! RECENT CHANGE(S): None
1596!!               
1597!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1598!!
1599!! REFERENCE(S) :
1600!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1601!! A global prognostic scheme of leaf onset using satellite data,
1602!! Global Change Biology, 207, 337-347.
1603!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1604!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1605!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1606!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1607!!
1608!! FLOWCHART    :
1609!! \latexonly
1610!! \includegraphics[scale = 1]{pheno_ngd.png}
1611!! \endlatexonly
1612!! \n
1613!_ ================================================================================================================================
1614
1615  SUBROUTINE pheno_ngd (npts, j, PFTpresent, allow_initpheno, ngd, &
1616       t2m_month, t2m_week, begin_leaves)
1617
1618    !
1619    !! 0. Variable and parameter declaration
1620    !
1621
1622    !
1623    !! 0.1 Input variables
1624    !
1625    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1626    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1627    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1628    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
1629                                                                                !! growing season? (true/false)
1630    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: ngd             !! growing degree days (C)
1631    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1632    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1633
1634    !
1635    !! 0.2 Output variables
1636    !
1637
1638    !
1639    !! 0.3 Modified variables
1640    !
1641    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1642
1643    !
1644    !! 0.4 Local variables
1645    !
1646    INTEGER(i_std)                                           :: i               !! index (unitless)
1647
1648    !! =========================================================================
1649
1650    IF (printlev>=3) WRITE(numout,*) 'Entering ngd'
1651
1652    !
1653    !! 1. Initializations
1654    !
1655
1656    !
1657    !! 1.1 initialize output
1658    !
1659
1660    begin_leaves(:,j) = .FALSE.
1661
1662    !
1663    !! 1.2 check the critical value ::ngd_crit is defined.
1664    !!     If not, stop.
1665    !
1666
1667    IF ( ngd_crit(j) .EQ. undef ) THEN
1668
1669       WRITE(numout,*) 'ngd: ngd_crit is undefined for PFT (::j) ',j
1670       CALL ipslerr_p(3,'stomate phenology','ngd_crit is undefined for this PFT','','')
1671
1672    ENDIF
1673
1674    !
1675    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1676    !!    PFT has to be there and start of growing season must be allowed.
1677    !
1678
1679    DO i = 1, npts
1680
1681       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
1682
1683          !! 2.1 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1684          !!     This occurs if the critical NGD has been reached AND are temperatures increasing.
1685
1686          IF ( ( ngd(i,j) .GE. ngd_crit(j) ) .AND. &
1687               ( t2m_week(i) .GT. t2m_month(i) )        ) THEN
1688             begin_leaves(i,j) = .TRUE.
1689          ENDIF
1690
1691       ENDIF        ! PFT there and start of growing season allowed
1692
1693    ENDDO ! end loop over grid points
1694
1695    IF (printlev>=4) WRITE(numout,*) 'Leaving ngd'
1696
1697  END SUBROUTINE pheno_ngd
1698
1699END MODULE stomate_phenology
Note: See TracBrowser for help on using the repository browser.