source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate_data.f90 @ 257

Last change on this file since 257 was 257, checked in by didier.solyga, 13 years ago

Externalized version merged with the trunk

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