source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_stomate/stomate_data.f90 @ 8398

Last change on this file since 8398 was 2469, checked in by josefine.ghattas, 9 years ago

Change in comment : SZ into S. Zaehle

Ticket #78

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