source: tags/ORCHIDEE_1_9_6/ORCHIDEE/src_stomate/stomate_data.f90 @ 880

Last change on this file since 880 was 864, checked in by didier.solyga, 12 years ago

Thanks to N.Viovy potential bug corrected in module pft_parameters. Specific leaf area (SLA) is prescribed (and externalized) now and not calculated anymore.

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