source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_stomate/stomate_data.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 25.7 KB
Line 
1! =================================================================================================================================
2! MODULE        : stomate_data
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         "stomate_data" module defines the values about the PFT parameters. It will print
10!! the values of the parameters for STOMATE in the standard outputs.
11!!
12!!\n DESCRIPTION: None
13!!
14!! RECENT CHANGE(S): Sonke Zaehle: Reich et al, 1992 find no statistically significant differences
15!!                  between broadleaved and coniferous forests, specifically, the assumption that grasses grow
16!!                  needles is not justified. Replacing the function with the one based on Reich et al. 1997.
17!!                  Given that sla=100cm2/gDW at 9 months, sla is:
18!!                  sla=exp(5.615-0.46*ln(leaflon in months))
19!!
20!! REFERENCE(S) : None
21!!
22!! SVN          :
23!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_data.f90 $
24!! $Date: 2017-10-18 11:15:06 +0200 (Wed, 18 Oct 2017) $
25!! $Revision: 4693 $
26!! \n
27!_ ================================================================================================================================
28
29MODULE stomate_data
30
31  ! modules used:
32
33  USE constantes
34  USE time, ONLY : one_day, dt_sechiba, one_year
35  USE pft_parameters
36  USE defprec
37 
38
39  IMPLICIT NONE
40
41  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: hori_index     !! Move to Horizontal indices
42!$OMP THREADPRIVATE(hori_index)
43
44  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: horipft_index  !! Horizontal + PFT indices
45!$OMP THREADPRIVATE(horipft_index)
46
47  ! Land cover change
48
49  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip10_index   !! Horizontal + P10 indices
50!$OMP THREADPRIVATE(horip10_index)
51  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip100_index  !! Horizontal + P100 indice
52!$OMP THREADPRIVATE(horip100_index)
53  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip11_index   !! Horizontal + P11 indices
54!$OMP THREADPRIVATE(horip11_index)
55  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip101_index  !! Horizontal + P101 indices
56!$OMP THREADPRIVATE(horip101_index)
57
58  INTEGER(i_std),SAVE :: itime                 !! time step
59!$OMP THREADPRIVATE(itime)
60  INTEGER(i_std),SAVE :: hist_id_stomate       !! STOMATE history file ID
61!$OMP THREADPRIVATE(hist_id_stomate)
62  INTEGER(i_std),SAVE :: hist_id_stomate_IPCC  !! STOMATE history file ID for IPCC output
63!$OMP THREADPRIVATE(hist_id_stomate_IPCC)
64  INTEGER(i_std),SAVE :: rest_id_stomate       !! STOMATE restart file ID
65!$OMP THREADPRIVATE(rest_id_stomate)
66
67  REAL(r_std),PARAMETER :: adapted_crit = 1. - ( 1. / euler ) !! critical value for being adapted (1-1/e) (unitless)
68  REAL(r_std),PARAMETER :: regenerate_crit = 1. / euler       !! critical value for being regenerative (1/e) (unitless)
69
70
71  ! private & public routines
72
73  PUBLIC data
74
75CONTAINS
76
77!! ================================================================================================================================
78!! SUBROUTINE   : data
79!!
80!>\BRIEF         This routine defines the values of the PFT parameters. It will print the values of the parameters for STOMATE
81!!               in the standard outputs of ORCHIDEE.
82!!
83!! DESCRIPTION : This routine defines PFT parameters. It initializes the pheno_crit structure by tabulated parameters.\n
84!!               Some initializations are done for parameters. The SLA is calculated according *to* Reich et al (1992).\n
85!!               Another formulation by Reich et al(1997) could be used for the computation of the SLA.
86!!               The geographical coordinates might be used for defining some additional parameters
87!!               (e.g. frequency of anthropogenic fires, irrigation of agricultural surfaces, etc.). \n
88!!               For the moment, this possibility is not used. \n
89!!               The specifc leaf area (SLA) is calculated according Reich et al, 1992 by :
90!!               \latexonly
91!!               \input{stomate_data_SLA.tex}
92!!               \endlatexonly
93!!               The sapling (young) biomass for trees and for each compartment of biomass is calculated by :
94!!               \latexonly
95!!               \input{stomate_data_sapl_tree.tex}
96!!               \endlatexonly
97!!               The sapling biomass for grasses and for each compartment of biomass is calculated by :
98!!               \latexonly
99!!               \input{stomate_data_sapl_grass.tex}
100!!               \endlatexonly
101!!               The critical stem diameter is given by the following formula :
102!!               \latexonly
103!!               \input{stomate_data_stem_diameter.tex}
104!!               \endlatexonly
105!!
106!! RECENT CHANGE(S): Sonke Zaehle: Reich et al, 1992 find no statistically significant differences
107!!                  between broadleaved and coniferous forests, specifically, the assumption that grasses grow
108!!                  needles is not justified. Replacing the function with the one based on Reich et al. 1997.
109!!                  Given that sla=100cm2/gDW at 9 months, sla is:
110!!                  sla=exp(5.615-0.46*ln(leaflon in months))
111!!                   \latexonly
112!!                   \input{stomate_data_SLA_Reich_97.tex}
113!!                   \endlatexonly
114!!
115!! MAIN OUTPUT VARIABLE(S):
116!!
117!! REFERENCE(S) :
118!! - Reich PB, Walters MB, Ellsworth DS, (1992), Leaf life-span in relation to leaf, plant and
119!! stand characteristics among diverse ecosystems. Ecological Monographs, Vol 62, pp 365-392.
120!! - Reich PB, Walters MB, Ellsworth DS (1997) From tropics to tundra: global convergence in plant
121!!  functioning. Proc Natl Acad Sci USA, 94:13730 13734
122!!
123!! FLOWCHART    :
124!! \n
125!_ ================================================================================================================================
126
127  SUBROUTINE data (npts, lalo)
128
129
130    !! 0. Variables and parameter declaration
131
132
133    !! 0.1 Input variables
134
135    INTEGER(i_std), INTENT(in)                   :: npts    !! [DISPENSABLE] Domain size (unitless)
136    REAL(r_std),DIMENSION (npts,2), INTENT (in)  :: lalo    !! [DISPENSABLE] Geographical coordinates (latitude,longitude)
137
138    !! 0.4 Local variables
139
140    INTEGER(i_std)                               :: j       !! Index (unitless)
141    REAL(r_std)                                  :: alpha   !! alpha's : (unitless)
142    REAL(r_std)                                  :: dia     !! stem diameter (m)
143    REAL(r_std)                                  :: csa_sap !! Crown specific area sapling @tex $(m^2.ind^{-1})$ @endtex
144
145!_ ================================================================================================================================
146
147    !- pheno_gdd_crit
148    pheno_gdd_crit(:,1) = pheno_gdd_crit_c(:)
149    pheno_gdd_crit(:,2) = pheno_gdd_crit_b(:)         
150    pheno_gdd_crit(:,3) = pheno_gdd_crit_a(:) 
151    !
152    !- senescence_temp
153    senescence_temp(:,1) = senescence_temp_c(:)
154    senescence_temp(:,2) = senescence_temp_b(:)
155    senescence_temp(:,3) = senescence_temp_a(:)
156    !
157    !- maint_resp_slope
158    maint_resp_slope(:,1) = maint_resp_slope_c(:)             
159    maint_resp_slope(:,2) = maint_resp_slope_b(:)
160    maint_resp_slope(:,3) = maint_resp_slope_a(:)
161    !
162    !-coeff_maint_zero
163    coeff_maint_zero(:,ileaf) = cm_zero_leaf(:)
164    coeff_maint_zero(:,isapabove) = cm_zero_sapabove(:)
165    coeff_maint_zero(:,isapbelow) = cm_zero_sapbelow(:)
166    coeff_maint_zero(:,iheartabove) = cm_zero_heartabove(:)
167    coeff_maint_zero(:,iheartbelow) = cm_zero_heartbelow(:)
168    coeff_maint_zero(:,iroot) = cm_zero_root(:)
169    coeff_maint_zero(:,ifruit) = cm_zero_fruit(:)
170    coeff_maint_zero(:,icarbres) = cm_zero_carbres(:)
171
172
173    IF ( printlev >= 2 ) WRITE(numout,*) 'data: PFT characteristics'
174
175    DO j = 2,nvm ! Loop over # PFTS
176
177       IF ( printlev >= 2 ) WRITE(numout,'(a,i3,a,a)') '    > PFT#',j,': ', PFT_name(j)
178
179       !
180       ! 1 tree? (true/false)
181       !
182       IF ( printlev >= 2 ) WRITE(numout,*) '       tree: (::is_tree) ', is_tree(j)
183
184       !
185       ! 2 flamability (0-1, unitless)
186       !
187
188       IF ( printlev >= 2 ) WRITE(numout,*) '       litter flamability (::flam) :', flam(j)
189
190       !
191       ! 3 fire resistance (unitless)
192       !
193
194       IF ( printlev >= 2 ) WRITE(numout,*) '       fire resistance (::resist) :', resist(j)
195
196       !
197       ! 4 specific leaf area per mass carbon = 2 * sla / dry mass (m^2.gC^{-1})
198       !
199
200       ! S. Zaehle: Reich et al, 1992 find no statistically significant differences between broadleaved and coniferous
201       ! forests, specifically, the assumption that grasses grow needles is not justified. Replacing the function
202       ! with the one based on Reich et al. 1997. Given that sla=100cm2/gDW at 9 months, sla is:
203       ! sla=exp(5.615-0.46*ln(leaflon in months))
204
205       ! Oct 2010 : sla values are prescribed by values given by N.Viovy
206
207       ! includes conversion from
208       !!       sla(j) = 2. * 1e-4 * EXP(5.615 - 0.46 * log(12./leaflife_tab(j)))
209       !!\latexonly
210       !!\input{stomate_data_SLA.tex}
211       !!\endlatexonly
212!       IF ( leaf_tab(j) .EQ. 2 ) THEN
213!
214!          ! needle leaved tree
215!          sla(j) = 2. * ( 10. ** ( 2.29 - 0.4 * LOG10(12./leaflife_tab(j)) ) ) *1e-4
216!
217!       ELSE
218!
219!          ! broad leaved tree or grass (Reich et al 1992)
220!          sla(j) = 2. * ( 10. ** ( 2.41 - 0.38 * LOG10(12./leaflife_tab(j)) ) ) *1e-4
221!
222!       ENDIF
223
224!!!$      IF ( leaf_tab(j) .EQ. 1 ) THEN
225!!!$
226!!!$        ! broad leaved tree
227!!!$
228!!!$        sla(j) = 2. * ( 10. ** ( 2.41 - 0.38 * LOG10(12./leaflife_tab(j)) ) ) *1e-4
229!!!$
230!!!$      ELSE
231!!!$
232!!!$        ! needle leaved or grass (Reich et al 1992)
233!!!$
234!!!$        sla(j) = 2. * ( 10. ** ( 2.29 - 0.4 * LOG10(12./leaflife_tab(j)) ) ) *1e-4
235!!!$
236!!!$      ENDIF
237!!!$
238!!!$      IF ( ( leaf_tab(j) .EQ. 2 ) .AND. ( pheno_type_tab(j) .EQ. 2 ) ) THEN
239!!!$
240!!!$        ! summergreen needle leaf
241!!!$
242!!!$        sla(j) = 1.25 * sla(j)
243!!!$
244!!!$      ENDIF
245
246       IF ( printlev >= 2 ) WRITE(numout,*) '       specific leaf area (m**2/gC) (::sla):', sla(j), 12./leaflife_tab(j)
247
248       !
249       ! 5 sapling characteristics
250       !
251
252       IF ( is_tree(j) ) THEN
253
254          !> 5.1 trees
255
256          !!\latexonly
257          !!\input{stomate_data_sapl_tree.tex}
258          !!\endlatexonly
259
260          alpha = alpha_tree
261
262          bm_sapl(j,ileaf,icarbon) = &
263               &     ((bm_sapl_leaf(1)*pipe_tune1*(mass_ratio_heart_sap *bm_sapl_leaf(2)*sla(j)/(pi*pipe_k1)) & 
264               &     **bm_sapl_leaf(3))/sla(j))**bm_sapl_leaf(4)
265
266          IF ( pheno_type(j) .NE. 1 ) THEN
267             ! not evergreen
268             bm_sapl(j,icarbres,icarbon) = bm_sapl_carbres * bm_sapl(j,ileaf,icarbon)
269          ELSE
270             bm_sapl(j,icarbres,icarbon) = zero
271          ENDIF ! (pheno_type_tab(j) .NE. 1 )
272
273          csa_sap = bm_sapl(j,ileaf,icarbon) / ( pipe_k1 / sla(j) )
274
275          dia = (mass_ratio_heart_sap * csa_sap * dia_coeff(1) / pi ) ** dia_coeff(2)
276
277          bm_sapl(j,isapabove,icarbon) = &
278               bm_sapl_sapabove * pipe_density * csa_sap * pipe_tune2 * dia ** pipe_tune3
279          bm_sapl(j,isapbelow,icarbon) = bm_sapl(j,isapabove,icarbon)
280
281          bm_sapl(j,iheartabove,icarbon) = bm_sapl_heartabove * bm_sapl(j,isapabove,icarbon)
282          bm_sapl(j,iheartbelow,icarbon) = bm_sapl_heartbelow * bm_sapl(j,isapbelow,icarbon)
283
284       ELSE
285
286          !> 5.2 grasses
287
288          !!\latexonly
289          !!\input{stomate_data_sapl_grass.tex}
290          !!\endlatexonly
291
292          alpha = alpha_grass
293
294          IF ( natural(j) ) THEN
295             bm_sapl(j,ileaf,icarbon) = init_sapl_mass_leaf_nat / sla(j)
296          ELSE
297             bm_sapl(j,ileaf,icarbon) = init_sapl_mass_leaf_agri / sla(j)
298          ENDIF
299
300          bm_sapl(j,icarbres,icarbon) = init_sapl_mass_carbres *bm_sapl(j,ileaf,icarbon)
301
302          bm_sapl(j,isapabove,icarbon) = zero
303          bm_sapl(j,isapbelow,icarbon) = zero
304
305          bm_sapl(j,iheartabove,icarbon) = zero
306          bm_sapl(j,iheartbelow,icarbon) = zero
307
308       ENDIF !( is_tree(j) )
309
310       bm_sapl(j,iroot,icarbon) = init_sapl_mass_root * (1./alpha) * bm_sapl(j,ileaf,icarbon)
311
312       bm_sapl(j,ifruit,icarbon) = init_sapl_mass_fruit  * bm_sapl(j,ileaf,icarbon)
313
314       IF ( printlev >= 2 ) THEN
315          WRITE(numout,*) '       sapling biomass (gC):'
316          WRITE(numout,*) '         leaves: (::bm_sapl(j,ileaf,icarbon))',bm_sapl(j,ileaf,icarbon)
317          WRITE(numout,*) '         sap above ground: (::bm_sapl(j,ispabove,icarbon)):',bm_sapl(j,isapabove,icarbon)
318          WRITE(numout,*) '         sap below ground: (::bm_sapl(j,isapbelow,icarbon))',bm_sapl(j,isapbelow,icarbon)
319          WRITE(numout,*) '         heartwood above ground: (::bm_sapl(j,iheartabove,icarbon))',bm_sapl(j,iheartabove,icarbon)
320          WRITE(numout,*) '         heartwood below ground: (::bm_sapl(j,iheartbelow,icarbon))',bm_sapl(j,iheartbelow,icarbon)
321          WRITE(numout,*) '         roots: (::bm_sapl(j,iroot,icarbon))',bm_sapl(j,iroot,icarbon)
322          WRITE(numout,*) '         fruits: (::bm_sapl(j,ifruit,icarbon))',bm_sapl(j,ifruit,icarbon)
323          WRITE(numout,*) '         carbohydrate reserve: (::bm_sapl(j,icarbres,icarbon))',bm_sapl(j,icarbres,icarbon)
324       ENDIF
325
326       !
327       ! 6 migration speed (m/year)
328       !
329
330       IF ( is_tree(j) ) THEN
331
332          migrate(j) = migrate_tree
333
334       ELSE
335
336          ! can be any value as grasses are, per *definition*, everywhere (big leaf).
337          migrate(j) = migrate_grass
338
339       ENDIF !( is_tree(j) )
340
341       IF ( printlev >= 2 ) WRITE(numout,*) '       migration speed (m/year): (::migrate(j))', migrate(j)
342
343       !
344       ! 7 critical stem diameter: beyond this diameter, the crown area no longer
345       !     increases (m)
346       !
347
348       IF ( is_tree(j) ) THEN
349
350          !!\latexonly
351          !!\input{stomate_data_stem_diameter.tex}
352          !!\endlatexonly
353
354          maxdia(j) = ( ( pipe_tune4 / ((pipe_tune2*pipe_tune3)/(maxdia_coeff(1)**pipe_tune3)) ) &
355               ** ( un / ( pipe_tune3 - un ) ) ) * maxdia_coeff(2)
356          cn_sapl(j) = cn_sapl_init !crown of individual tree, first year
357
358       ELSE
359
360          maxdia(j) = undef
361          cn_sapl(j)=1
362
363       ENDIF !( is_tree(j) )
364
365       IF ( printlev >= 2 ) WRITE(numout,*) '       critical stem diameter (m): (::maxdia(j))', maxdia(j)
366
367       !
368       ! 8 Coldest tolerable temperature (K)
369       !
370
371       IF ( ABS( tmin_crit(j) - undef ) .GT. min_stomate ) THEN
372          tmin_crit(j) = tmin_crit(j) + ZeroCelsius
373       ELSE
374          tmin_crit(j) = undef
375       ENDIF
376
377       IF ( printlev >= 2 ) &
378            WRITE(numout,*) '       coldest tolerable temperature (K): (::tmin_crit(j))', tmin_crit(j)
379
380       !
381       ! 9 Maximum temperature of the coldest month: need to be below this temperature
382       !      for a certain time to regrow leaves next spring *(vernalization)* (K)
383       !
384
385       IF ( ABS ( tcm_crit(j) - undef ) .GT. min_stomate ) THEN
386          tcm_crit(j) = tcm_crit(j) + ZeroCelsius
387       ELSE
388          tcm_crit(j) = undef
389       ENDIF
390
391       IF ( printlev >= 2 ) &
392            WRITE(numout,*) '       vernalization temperature (K): (::tcm_crit(j))', tcm_crit(j)
393
394       !
395       ! 10 critical values for phenology
396       !
397
398       ! 10.1 model used
399
400       IF ( printlev >= 2 ) &
401            WRITE(numout,*) '       phenology model used: (::pheno_model(j)) ',pheno_model(j)
402
403       ! 10.2 growing degree days. What kind of gdd is meant (i.e. threshold 0 or -5 deg C
404       !        or whatever), depends on how this is used in stomate_phenology.
405
406
407       IF ( ( printlev >= 2 ) .AND. ( ALL(pheno_gdd_crit(j,:) .NE. undef) ) ) THEN
408          WRITE(numout,*) '         critical GDD is a function of long term T (C): (::gdd)'
409          WRITE(numout,*) '          ',pheno_gdd_crit(j,1), &
410               ' + T *',pheno_gdd_crit(j,2), &
411               ' + T^2 *',pheno_gdd_crit(j,3)
412       ENDIF
413
414       ! consistency check
415
416       IF ( ( ( pheno_model(j) .EQ. 'moigdd' ) .OR. &
417            ( pheno_model(j) .EQ. 'humgdd' )       ) .AND. &
418            ( ANY(pheno_gdd_crit(j,:) .EQ. undef) )                      ) THEN
419          CALL ipslerr_p(3,'stomate_data','problem with phenology parameters, critical GDD. (::pheno_model)','','')
420       ENDIF
421
422       ! 10.3 number of growing days
423
424       IF ( ( printlev >= 2 ) .AND. ( ngd_crit(j) .NE. undef ) ) &
425            WRITE(numout,*) '         critical NGD: (::ngd_crit(j))', ngd_crit(j)
426
427       ! 10.4 critical temperature for ncd vs. gdd function in phenology (C)
428
429       IF ( ( printlev >= 2 ) .AND. ( ncdgdd_temp(j) .NE. undef ) ) &
430            WRITE(numout,*) '         critical temperature for NCD vs. GDD (C): (::ncdgdd_temp(j))', &
431            ncdgdd_temp(j)
432
433       ! 10.5 humidity fractions (0-1, unitless)
434
435       IF ( ( printlev >= 2 ) .AND. ( hum_frac(j) .NE. undef ) ) &
436            WRITE(numout,*) '         critical humidity fraction: (::hum_frac(j))', &
437            &  hum_frac(j)
438
439
440       ! 10.6 minimum time elapsed since moisture minimum (days)
441
442       IF ( ( printlev >= 2 ) .AND. ( hum_min_time(j) .NE. undef ) ) &
443            WRITE(numout,*) '         time to wait after moisture min (d): (::hum_min_time(j))', &
444        &    hum_min_time(j)
445
446       !
447       ! 11 critical values for senescence
448       !
449
450       ! 11.1 type of senescence
451
452       IF ( printlev >= 2 ) &
453            WRITE(numout,*) '       type of senescence: (::senescence_type(j))',senescence_type(j)
454
455       ! 11.2 critical temperature for senescence (C)
456
457       IF ( ( printlev >= 2 ) .AND. ( ALL(senescence_temp(j,:) .NE. undef) ) ) THEN
458          WRITE(numout,*) '         critical temperature for senescence (C) is'
459          WRITE(numout,*) '          a function of long term T (C): (::senescence_temp)'
460          WRITE(numout,*) '          ',senescence_temp(j,1), &
461               ' + T *',senescence_temp(j,2), &
462               ' + T^2 *',senescence_temp(j,3)
463       ENDIF
464
465       ! consistency check
466
467       IF ( ( ( senescence_type(j) .EQ. 'cold' ) .OR. &
468            ( senescence_type(j) .EQ. 'mixed' )      ) .AND. &
469            ( ANY(senescence_temp(j,:) .EQ. undef ) )           ) THEN
470          CALL ipslerr_p(3,'stomate_data','Problem with senescence parameters, temperature. (::senescence_type)','','')
471       ENDIF
472
473       ! 11.3 critical relative moisture availability for senescence
474
475       IF ( ( printlev >= 2 ) .AND. ( senescence_hum(j) .NE. undef ) ) THEN
476          WRITE(numout,*)  '  max. critical relative moisture availability for' 
477          WRITE(numout,*)  '  senescence: (::senescence_hum(j))',  &
478               & senescence_hum(j)
479       END IF
480
481       ! consistency check
482
483       IF ( ( ( senescence_type(j) .EQ. 'dry' ) .OR. &
484            ( senescence_type(j) .EQ. 'mixed' )     ) .AND. &
485            ( senescence_hum(j) .EQ. undef )                   ) THEN
486          CALL ipslerr_p(3,'stomate_data','Problem with senescence parameters, humidity.(::senescence_type)','','')
487       ENDIF
488
489       ! 14.3 relative moisture availability above which there is no moisture-related
490       !      senescence (0-1, unitless)
491
492       IF ( ( printlev >= 2 ) .AND. ( nosenescence_hum(j) .NE. undef ) ) THEN
493          WRITE(numout,*) '         relative moisture availability above which there is' 
494          WRITE(numout,*) '             no moisture-related senescence: (::nosenescence_hum(j))', nosenescence_hum(j)
495       END IF
496       ! consistency check
497
498       IF ( ( ( senescence_type(j) .EQ. 'dry' ) .OR. &
499            ( senescence_type(j) .EQ. 'mixed' )     ) .AND. &
500            ( nosenescence_hum(j) .EQ. undef )                   ) THEN
501          CALL ipslerr_p(3,'stomate_data','Problem with senescence parameters, humidity. (::senescence_type)','','')
502       ENDIF
503
504       !
505       ! 12 sapwood -> heartwood conversion time (days)
506       !
507
508       IF ( printlev >= 2 ) &
509            WRITE(numout,*) '       sapwood -> heartwood conversion time (d): (::tau_sap(j))', tau_sap(j)
510
511       !
512       ! 13 fruit lifetime (days)
513       !
514
515       IF ( printlev >= 2 ) WRITE(numout,*) '       fruit lifetime (d): (::tau_fruit(j))', tau_fruit(j)
516
517       !
518       ! 14 length of leaf death (days)
519       !      For evergreen trees, this variable determines the lifetime of the leaves.
520       !      Note that it is different from the value given in leaflife_tab.
521       !
522
523       IF ( printlev >= 2 ) &
524            WRITE(numout,*) '       length of leaf death (d): (::leaffall(j))', leaffall(j)
525
526       !
527       ! 15 maximum lifetime of leaves (days)
528       !
529
530       IF ( ( printlev >= 2 ) .AND. ( leafagecrit(j) .NE. undef ) ) &
531            WRITE(numout,*) '       critical leaf age (d): (::leafagecrit(j))', leafagecrit(j)
532
533       !
534       ! 16 time constant for leaf age discretisation (days)
535       !
536
537       leaf_timecst(j) = leafagecrit(j) / REAL( nleafages,r_std )
538
539       IF ( printlev >= 2 ) &
540            WRITE(numout,*) '       time constant for leaf age discretisation (d): (::leaf_timecst(j))', &
541            leaf_timecst(j)
542
543       !
544       ! 17 minimum lai, initial (m^2.m^{-2})
545       !
546
547       IF ( is_tree(j) ) THEN
548          lai_initmin(j) = lai_initmin_tree
549       ELSE
550          lai_initmin(j) = lai_initmin_grass
551       ENDIF !( is_tree(j) )
552
553       IF ( printlev >= 2 ) &
554            WRITE(numout,*) '       initial LAI: (::lai_initmin(j))', lai_initmin(j)
555
556       !
557       ! 19 maximum LAI (m^2.m^{-2})
558       !
559
560       IF ( printlev >= 2 ) &
561            WRITE(numout,*) '       critical LAI above which no leaf allocation: (::lai_max(j))', lai_max(j)
562
563       !
564       ! 20 fraction of primary leaf and root allocation put into reserve (0-1, unitless)
565       !
566
567       IF ( printlev >= 2 ) &
568            WRITE(numout,*) '       reserve allocation factor: (::ecureuil(j))', ecureuil(j)
569
570       !
571       ! 21 maintenance respiration coefficient (g/g/day) at 0 deg C
572       !
573
574       IF ( printlev >= 2 ) THEN
575
576          WRITE(numout,*) '       maintenance respiration coefficient (g/g/day) at 0 deg C:'
577          WRITE(numout,*) '         . leaves: (::coeff_maint_zero(j,ileaf))',coeff_maint_zero(j,ileaf)
578          WRITE(numout,*) '         . sapwood above ground: (::coeff_maint_zero(j,isapabove)) ',&
579                        & coeff_maint_zero(j,isapabove)
580          WRITE(numout,*) '         . sapwood below ground: (::coeff_maint_zero(j,isapbelow))  ',&
581                       & coeff_maint_zero(j,isapbelow)
582          WRITE(numout,*) '         . heartwood above ground: (::coeff_maint_zero(j,iheartabove)) ',&
583                       & coeff_maint_zero(j,iheartabove)
584          WRITE(numout,*) '         . heartwood below ground: (::coeff_maint_zero(j,iheartbelow)) ',&
585                       & coeff_maint_zero(j,iheartbelow)
586          WRITE(numout,*) '         . roots: (::coeff_maint_zero(j,iroot))',coeff_maint_zero(j,iroot)
587          WRITE(numout,*) '         . fruits: (::coeff_maint_zero(j,ifruit)) ',coeff_maint_zero(j,ifruit)
588          WRITE(numout,*) '         . carbohydrate reserve: (::coeff_maint_zero(j,icarbres)) ',&
589                       & coeff_maint_zero(j,icarbres)
590
591       ENDIF !( printlev >= 2 )
592
593       !
594       ! 22 parameter for temperature sensitivity of maintenance respiration
595       !
596
597       IF ( printlev >= 2 ) THEN
598          WRITE(numout,*) '       temperature sensitivity of maintenance respiration (1/K) is'
599          WRITE(numout,*) '          a function of long term T (C): (::maint_resp_slope)'
600          WRITE(numout,*) '          ',maint_resp_slope(j,1),' + T *',maint_resp_slope(j,2), &
601               ' + T^2 *',maint_resp_slope(j,3)
602       END IF
603       !
604       ! 23 natural ?
605       !
606
607       IF ( printlev >= 2 ) &
608            WRITE(numout,*) '       Natural: (::natural(j))', natural(j)
609
610       !
611       ! 24 Vcmax et Vjmax (umol.m^{-2}.s^{-1})
612       !
613
614       IF ( printlev >= 2 ) &
615            WRITE(numout,*) '       Maximum rate of carboxylation: (::Vcmax_25(j))', vcmax25(j)
616       !
617       ! 25 constants for photosynthesis temperatures
618       !
619
620       IF ( printlev >= 2 ) THEN
621
622
623          !
624          ! 26 Properties
625          !
626
627          WRITE(numout,*) '       C4 photosynthesis: (::is_c4(j))', is_c4(j)
628          WRITE(numout,*) '       Depth constant for root profile (m): (::1./humcste(j))', 1./humcste(j)
629
630       ENDIF
631
632       !
633       ! 27 extinction coefficient of the Monsi and Saeki (1953) relationship
634       !
635       IF ( printlev >= 2 ) THEN
636          WRITE(numout,*) '       extinction coefficient: (::ext_coeff(j))', ext_coeff(j)
637       ENDIF
638
639       !
640       ! 30 fraction of allocatable biomass which is lost as growth respiration (0-1, unitless)
641       !
642       IF ( printlev >= 2 ) &
643            WRITE(numout,*) '       growth respiration fraction: (::frac_growthresp(j))', frac_growthresp(j)
644
645    ENDDO ! Loop over # PFTS
646
647    !
648    ! 29 time scales for phenology and other processes (in days)
649    !
650
651    tau_longterm_max = coeff_tau_longterm * one_year
652
653    IF ( printlev >= 2 ) THEN
654
655       WRITE(numout,*) '   > time scale for ''monthly'' moisture availability (d): (::tau_hum_month)', &
656            tau_hum_month
657       WRITE(numout,*) '   > time scale for ''weekly'' moisture availability (d): (::tau_hum_week)', &
658           tau_hum_week
659       WRITE(numout,*) '   > time scale for ''monthly'' 2 meter temperature (d): (::tau_t2m_month)', &
660            tau_t2m_month
661       WRITE(numout,*) '   > time scale for ''weekly'' 2 meter temperature (d): (::tau_t2m_week)', &
662            tau_t2m_week
663       WRITE(numout,*) '   > time scale for ''weekly'' GPP (d): (::tau_gpp_week)', &
664            tau_gpp_week
665       WRITE(numout,*) '   > time scale for ''monthly'' soil temperature (d): (::tau_tsoil_month)', &
666            tau_tsoil_month
667       WRITE(numout,*) '   > time scale for ''monthly'' soil humidity (d): (::tau_soilhum_month)', &
668            tau_soilhum_month
669       WRITE(numout,*) '   > time scale for vigour calculations (y): (::tau_longterm_max / one_year)', &
670            tau_longterm_max / one_year
671
672    ENDIF
673
674    IF (printlev >= 4) WRITE(numout,*) 'Leaving stomate_data'
675
676  END SUBROUTINE data
677
678END MODULE stomate_data
Note: See TracBrowser for help on using the repository browser.