source: tags/ORCHIDEE/src_stomate/stomate_data.f90 @ 6

Last change on this file since 6 was 6, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

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