source: tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_stomate/stomate_data.f90 @ 2061

Last change on this file since 2061 was 45, checked in by mmaipsl, 14 years ago

MM: Tests with lf95 compiler : correct f95 strict norm problems.

There is no change in numerical result after these commits.

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