source: tags/ORCHIDEE_4_1/ORCHIDEE/src_stomate/stomate_data.f90 @ 7852

Last change on this file since 7852 was 7347, checked in by josefine.ghattas, 3 years ago
  • Remove tau_soilhum_month, soilhum_month and soilhum_daily never used
  • Clean initalization phase in season_pre_disturbance which was the cause of the restart problem previously, see ticket #796. The variables are truncated after calculation instead of in the initalization phase (see gpp_week, turnover_longterm, npp_longterm, ngd_minus5
  • default value if no restart file was corrected for minrelsoilmoist_thisyear from one to large_value
  • Property svn:keywords set to HeadURL Date Author Revision
File size: 20.7 KB
Line 
1! =================================================================================================================================
2! MODULE        : stomate_data
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         "stomate_data" module defines the values about the PFT parameters. It will print
10!! the values of the parameters for STOMATE in the standard outputs.
11!!
12!!\n DESCRIPTION: None
13!!
14!! RECENT CHANGE(S): Sonke Zaehle: Reich et al, 1992 find no statistically significant differences
15!!                  between broadleaved and coniferous forests, specifically, the assumption that grasses grow
16!!                  needles is not justified. Replacing the function with the one based on Reich et al. 1997.
17!!                  Given that sla=100cm2/gDW at 9 months, sla is:
18!!                  sla=exp(5.615-0.46*ln(leaflon in months))
19!!
20!! REFERENCE(S) : None
21!!
22!! SVN          :
23!! $HeadURL$
24!! $Date$
25!! $Revision$
26!! \n
27!_ ================================================================================================================================
28
29MODULE stomate_data
30
31  ! modules used:
32
33  USE constantes
34  USE time, ONLY : one_day, dt_sechiba, one_year
35  USE pft_parameters
36  USE defprec
37 
38
39  IMPLICIT NONE
40
41  INTEGER(i_std), SAVE, PRIVATE                :: printlev_loc   !! local printlev for this module
42!$OMP THREADPRIVATE(printlev_loc)
43
44  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: hori_index     !! Move to Horizontal indices
45!$OMP THREADPRIVATE(hori_index)
46
47  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: horipft_index  !! Horizontal + PFT indices
48!$OMP THREADPRIVATE(horipft_index)
49
50  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: horican_index  !! Horizontal + canopy levels indices
51!$OMP THREADPRIVATE(horican_index)
52 
53  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: horicut_index  !! Horizontal + cut times indices
54!$OMP THREADPRIVATE(horicut_index)
55
56  !
57  ! Land cover change
58  !
59  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip_s_index   !! Horizontal + P short indices
60!$OMP THREADPRIVATE(horip_s_index)
61  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip_m_index   !! Horizontal + P medium indices
62!$OMP THREADPRIVATE(horip_m_index)
63  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip_l_index   !! Horizontal + P long indice
64!$OMP THREADPRIVATE(horip_l_index)
65  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip_ss_index  !! Horizontal + P short indices
66!$OMP THREADPRIVATE(horip_ss_index)
67  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip_mm_index  !! Horizontal + P medium indices
68!$OMP THREADPRIVATE(horip_mm_index)
69  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip_ll_index  !! Horizontal + P long indices
70!$OMP THREADPRIVATE(horip_ll_index)
71
72  INTEGER(i_std),SAVE :: itime                 !! time step
73!$OMP THREADPRIVATE(itime)
74  INTEGER(i_std),SAVE :: hist_id_stomate       !! STOMATE history file ID
75!$OMP THREADPRIVATE(hist_id_stomate)
76  INTEGER(i_std),SAVE :: hist_id_stomate_IPCC  !! STOMATE history file ID for IPCC output
77!$OMP THREADPRIVATE(hist_id_stomate_IPCC)
78  INTEGER(i_std),SAVE :: rest_id_stomate       !! STOMATE restart file ID
79!$OMP THREADPRIVATE(rest_id_stomate)
80
81  REAL(r_std),PARAMETER :: adapted_crit = 1. - ( 1. / euler ) !! critical value for being adapted (1-1/e) (unitless)
82  REAL(r_std),PARAMETER :: regenerate_crit = 1. / euler       !! critical value for being regenerative (1/e) (unitless)
83
84
85  ! private & public routines
86
87  PUBLIC data
88
89CONTAINS
90
91!! ================================================================================================================================
92!! SUBROUTINE   : data
93!!
94!>\BRIEF         This routine defines the values of the PFT parameters. It will print the values of the parameters for STOMATE
95!!               in the standard outputs of ORCHIDEE.
96!!
97!! DESCRIPTION : This routine defines PFT parameters. It initializes the pheno_crit structure by tabulated parameters.\n
98!!               Some initializations are done for parameters. The SLA is calculated according *to* Reich et al (1992).\n
99!!               Another formulation by Reich et al(1997) could be used for the computation of the SLA.
100!!               The geographical coordinates might be used for defining some additional parameters
101!!               (e.g. frequency of anthropogenic fires, irrigation of agricultural surfaces, etc.). \n
102!!               For the moment, this possibility is not used. \n
103!!               The specifc leaf area (SLA) is calculated according Reich et al, 1992 by :
104!!               \latexonly
105!!               \input{stomate_data_SLA.tex}
106!!               \endlatexonly
107!!               The sapling (young) biomass for trees and for each compartment of biomass is calculated by :
108!!               \latexonly
109!!               \input{stomate_data_sapl_tree.tex}
110!!               \endlatexonly
111!!               The sapling biomass for grasses and for each compartment of biomass is calculated by :
112!!               \latexonly
113!!               \input{stomate_data_sapl_grass.tex}
114!!               \endlatexonly
115!!               The critical stem diameter is given by the following formula :
116!!               \latexonly
117!!               \input{stomate_data_stem_diameter.tex}
118!!               \endlatexonly
119!!
120!! RECENT CHANGE(S): Sonke Zaehle: Reich et al, 1992 find no statistically significant differences
121!!                  between broadleaved and coniferous forests, specifically, the assumption that grasses grow
122!!                  needles is not justified. Replacing the function with the one based on Reich et al. 1997.
123!!                  Given that sla=100cm2/gDW at 9 months, sla is:
124!!                  sla=exp(5.615-0.46*ln(leaflon in months))
125!!                   \latexonly
126!!                   \input{stomate_data_SLA_Reich_97.tex}
127!!                   \endlatexonly
128!!
129!! MAIN OUTPUT VARIABLE(S):
130!!
131!! REFERENCE(S) :
132!! - Reich PB, Walters MB, Ellsworth DS, (1992), Leaf life-span in relation to leaf, plant and
133!! stand characteristics among diverse ecosystems. Ecological Monographs, Vol 62, pp 365-392.
134!! - Reich PB, Walters MB, Ellsworth DS (1997) From tropics to tundra: global convergence in plant
135!!  functioning. Proc Natl Acad Sci USA, 94:13730 13734
136!!
137!! FLOWCHART    :
138!! \n
139!_ ================================================================================================================================
140
141  SUBROUTINE data
142
143
144    INTEGER(i_std)                               :: i,j     !! Index (unitless)
145
146!_ ================================================================================================================================
147
148    ! Initialize local printlev
149    printlev_loc=get_printlev('data')
150   
151
152    !- pheno_gdd_crit
153    pheno_gdd_crit(:,1) = pheno_gdd_crit_c(:)
154    pheno_gdd_crit(:,2) = pheno_gdd_crit_b(:)         
155    pheno_gdd_crit(:,3) = pheno_gdd_crit_a(:) 
156    !
157    !- senescence_temp
158    senescence_temp(:,1) = senescence_temp_c(:)
159    senescence_temp(:,2) = senescence_temp_b(:)
160    senescence_temp(:,3) = senescence_temp_a(:)
161    !
162    !-LC
163    LC(:,ileaf) = LC_leaf(:) 
164    LC(:,isapabove) = LC_sapabove(:) 
165    LC(:,isapbelow) = LC_sapbelow(:) 
166    LC(:,iheartabove) = LC_heartabove(:) 
167    LC(:,iheartbelow) = LC_heartbelow(:) 
168    LC(:,iroot) = LC_root(:) 
169    LC(:,ifruit) = LC_fruit(:) 
170    LC(:,icarbres) = LC_carbres(:) 
171    LC(:,ilabile) = LC_labile(:) 
172
173    IF ( printlev_loc >= 2 ) WRITE(numout,*) 'data: PFT characteristics'
174
175    DO j = 2,nvm ! Loop over # PFTS
176
177       IF ( printlev_loc >= 2 ) WRITE(numout,'(a,i3,a,a)') '    > PFT#',j,': ', PFT_name(j)
178
179       !
180       ! 1 tree? (true/false)
181       !
182       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       tree: (::is_tree) ', is_tree(j)
183
184       !
185       ! 2 flamability (0-1, unitless)
186       !
187
188       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       litter flamability (::flam) :', flam(j)
189
190       !
191       ! 3 fire resistance (unitless)
192       !
193
194       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       fire resistance (::resist) :', resist(j)
195
196       !
197       ! 4 specific leaf area per mass carbon = 2 * sla / dry mass (m^2.gC^{-1})
198       !
199
200       ! S. Zaehle: Reich et al, 1992 find no statistically significant differences between broadleaved and coniferous
201       ! forests, specifically, the assumption that grasses grow needles is not justified. Replacing the function
202       ! with the one based on Reich et al. 1997. Given that sla=100cm2/gDW at 9 months, sla is:
203       ! sla=exp(5.615-0.46*ln(leaflon in months))
204
205       ! Oct 2010 : sla values are prescribed by values given by N.Viovy
206
207       ! includes conversion from
208       !!       sla(j) = 2. * 1e-4 * EXP(5.615 - 0.46 * log(12./(longevity_eff_leaf(j)/365)))
209       !!\latexonly
210       !!\input{stomate_data_SLA.tex}
211       !!\endlatexonly
212!       IF ( leaf_tab(j) .EQ. 2 ) THEN
213!
214!          ! needle leaved tree
215!          sla(j) = 2. * ( 10. ** ( 2.29 - 0.4 * LOG10(12./(longevity_eff_leaf(j)/365)) ) ) *1e-4
216!
217!       ELSE
218!
219!          ! broad leaved tree or grass (Reich et al 1992)
220!          sla(j) = 2. * ( 10. ** ( 2.41 - 0.38 * LOG10(12./(longevity_eff_leaf(j)/365)) ) ) *1e-4
221!
222!       ENDIF
223
224!!!$      IF ( leaf_tab(j) .EQ. 1 ) THEN
225!!!$
226!!!$        ! broad leaved tree
227!!!$
228!!!$        sla(j) = 2. * ( 10. ** ( 2.41 - 0.38 * LOG10(12./(longevity_eff_leaf(j)/365)) ) ) *1e-4
229!!!$
230!!!$      ELSE
231!!!$
232!!!$        ! needle leaved or grass (Reich et al 1992)
233!!!$
234!!!$        sla(j) = 2. * ( 10. ** ( 2.29 - 0.4 * LOG10(12./(longevity_eff_leaf(j)/365)) ) ) *1e-4
235!!!$
236!!!$      ENDIF
237!!!$
238!!!$      IF ( ( leaf_tab(j) .EQ. 2 ) .AND. ( pheno_type_tab(j) .EQ. 2 ) ) THEN
239!!!$
240!!!$        ! summergreen needle leaf
241!!!$
242!!!$        sla(j) = 1.25 * sla(j)
243!!!$
244!!!$      ENDIF
245
246!!$       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       specific leaf area (m**2/gC) (::sla):', sla(j), 12./(longevity_eff_leaf(j)/365)
247
248
249       !+++CHECK+++
250       ! May be needed for the DGVM but no longer needed for stomate_prescribe. There
251       ! is a separate subroutine make_sapling that can be called whenever the initial
252       ! biomass of a sapling needs to be calculated. Estimating sapling biomass
253       ! on-the-fly rather than once at the start of a simulation has the advantage that
254       ! allocation factors can be adapted to the site conditions.
255       !+++++++++++
256
257       !
258       ! 6 migration speed (m/year)
259       !
260
261       IF ( is_tree(j) ) THEN
262
263          migrate(j) = migrate_tree
264
265       ELSE
266
267          ! can be any value as grasses are, per *definition*, everywhere (big leaf).
268          migrate(j) = migrate_grass
269
270       ENDIF !( is_tree(j) )
271
272       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       migration speed (m/year): (::migrate(j))', migrate(j)
273
274       !
275       ! 7 critical stem diameter: beyond this diameter, the crown area no longer
276       !     increases (m)
277       !
278
279       IF ( is_tree(j) ) THEN
280
281          !!\latexonly
282          !!\input{stomate_data_stem_diameter.tex}
283          !!\endlatexonly
284
285          maxdia(j) = ( ( pipe_tune4(j) / ((pipe_tune2(j)*pipe_tune3(j))/(maxdia_coeff(1)**pipe_tune3(j))) ) &
286               ** ( un / ( pipe_tune3(j) - un ) ) ) * maxdia_coeff(2)
287          cn_sapl(j) = cn_sapl_init !crown of individual tree, first year
288
289       ELSE
290
291          maxdia(j) = undef
292          cn_sapl(j)=1
293
294       ENDIF !( is_tree(j) )
295
296       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       critical stem diameter (m): (::maxdia(j))', maxdia(j)
297
298       !
299       ! 8 Coldest tolerable temperature (K)
300       !
301
302       IF ( ABS( tmin_crit(j) - undef ) .GT. min_stomate ) THEN
303          tmin_crit(j) = tmin_crit(j) + ZeroCelsius
304       ELSE
305          tmin_crit(j) = undef
306       ENDIF
307
308       IF ( printlev_loc >= 2 ) &
309            WRITE(numout,*) '       coldest tolerable temperature (K): (::tmin_crit(j))', tmin_crit(j)
310
311       !
312       ! 9 Maximum temperature of the coldest month: need to be below this temperature
313       !      for a certain time to regrow leaves next spring *(vernalization)* (K)
314       !
315
316       IF ( ABS ( tcm_crit(j) - undef ) .GT. min_stomate ) THEN
317          tcm_crit(j) = tcm_crit(j) + ZeroCelsius
318       ELSE
319          tcm_crit(j) = undef
320       ENDIF
321
322       IF ( printlev_loc >= 2 ) &
323            WRITE(numout,*) '       vernalization temperature (K): (::tcm_crit(j))', tcm_crit(j)
324
325       !
326       ! 10 critical values for phenology
327       !
328
329       ! 10.1 model used
330
331       IF ( printlev_loc >= 2 ) &
332            WRITE(numout,*) '       phenology model used: (::pheno_model(j)) ',pheno_model(j)
333
334       ! 10.2 growing degree days. What kind of gdd is meant (i.e. threshold 0 or -5 deg C
335       !        or whatever), depends on how this is used in stomate_phenology.
336
337
338       IF ( ( printlev_loc >= 2 ) .AND. ( ALL(pheno_gdd_crit(j,:) .NE. undef) ) ) THEN
339          WRITE(numout,*) '         critical GDD is a function of long term T (C): (::gdd)'
340          WRITE(numout,*) '          ',pheno_gdd_crit(j,1), &
341               ' + T *',pheno_gdd_crit(j,2), &
342               ' + T^2 *',pheno_gdd_crit(j,3)
343       ENDIF
344
345       ! consistency check
346
347       IF ( ( ( pheno_model(j) .EQ. 'moigdd' ) .OR. &
348            ( pheno_model(j) .EQ. 'humgdd' )       ) .AND. &
349            ( ANY(pheno_gdd_crit(j,:) .EQ. undef) )                      ) THEN
350          CALL ipslerr_p(3,'stomate_data','problem with phenology parameters, critical GDD. (::pheno_model)','','')
351       ENDIF
352
353       ! 10.3 number of growing days
354
355       IF ( ( printlev_loc >= 2 ) .AND. ( ngd_crit(j) .NE. undef ) ) &
356            WRITE(numout,*) '         critical NGD: (::ngd_crit(j))', ngd_crit(j)
357
358       ! 10.4 critical temperature for ncd vs. gdd function in phenology (C)
359
360       IF ( ( printlev_loc >= 2 ) .AND. ( ncdgdd_temp(j) .NE. undef ) ) &
361            WRITE(numout,*) '         critical temperature for NCD vs. GDD (C): (::ncdgdd_temp(j))', &
362            ncdgdd_temp(j)
363
364       ! 10.5 humidity fractions (0-1, unitless)
365
366       IF ( ( printlev_loc >= 2 ) .AND. ( hum_frac(j) .NE. undef ) ) &
367            WRITE(numout,*) '         critical humidity fraction: (::hum_frac(j))', &
368            &  hum_frac(j)
369
370
371       ! 10.6 minimum time elapsed since moisture minimum (days)
372
373       IF ( ( printlev_loc >= 2 ) .AND. ( hum_min_time(j) .NE. undef ) ) &
374            WRITE(numout,*) '         time to wait after moisture min (d): (::hum_min_time(j))', &
375        &    hum_min_time(j)
376
377       !
378       ! 11 critical values for senescence
379       !
380
381       ! 11.1 type of senescence
382
383       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       type of senescence: (::senescence_type(j))',&
384            senescence_type(j)
385
386       ! 11.2 critical temperature for senescence (C)
387
388       IF ( ( printlev_loc >= 2 ) .AND. ( ALL(senescence_temp(j,:) .NE. undef) ) ) THEN
389          WRITE(numout,*) '         critical temperature for senescence (C) is'
390          WRITE(numout,*) '          a function of long term T (C): (::senescence_temp)'
391          WRITE(numout,*) '          ',senescence_temp(j,1), &
392               ' + T *',senescence_temp(j,2), &
393               ' + T^2 *',senescence_temp(j,3)
394       ENDIF
395
396       ! consistency check
397
398       IF ( ( ( senescence_type(j) .EQ. 'cold' ) .OR. &
399            ( senescence_type(j) .EQ. 'mixed' )      ) .AND. &
400            ( ANY(senescence_temp(j,:) .EQ. undef ) )           ) THEN
401          CALL ipslerr_p(3,'stomate_data','Problem with senescence parameters, temperature. (::senescence_type)','','')
402       ENDIF
403
404       ! 11.3 critical relative moisture availability for senescence
405
406       IF ( ( printlev_loc >= 2 ) .AND. ( senescence_hum(j) .NE. undef ) ) THEN
407          WRITE(numout,*)  ' max. critical relative moisture availability for' 
408          WRITE(numout,*)  ' senescence: (::senescence_hum(j))',  &
409               & senescence_hum(j)
410       ENDIF
411
412       ! consistency check
413
414       IF ( ( ( senescence_type(j) .EQ. 'dry' ) .OR. &
415            ( senescence_type(j) .EQ. 'mixed' )     ) .AND. &
416            ( senescence_hum(j) .EQ. undef )                   ) THEN
417          CALL ipslerr_p(3,'stomate_data','Problem with senescence parameters, humidity.(::senescence_type)','','')
418       ENDIF
419
420       ! 14.3 relative moisture availability above which there is no moisture-related
421       !      senescence (0-1, unitless)
422
423       IF ( ( printlev_loc >= 2 ) .AND. ( nosenescence_hum(j) .NE. undef ) ) THEN
424          WRITE(numout,*) '         relative moisture availability above which there is' 
425          WRITE(numout,*) '             no moisture-related senescence: (::nosenescence_hum(j))', &
426               &  nosenescence_hum(j)
427       ENDIF
428
429       ! consistency check
430
431       IF ( ( ( senescence_type(j) .EQ. 'dry' ) .OR. &
432            ( senescence_type(j) .EQ. 'mixed' )     ) .AND. &
433            ( nosenescence_hum(j) .EQ. undef )                   ) THEN
434          CALL ipslerr_p(3,'stomate_data','Problem with senescence parameters, humidity. (::senescence_type)','','')
435       ENDIF
436
437       !
438       ! 12 sapwood -> heartwood conversion time (days)
439       !
440
441       IF ( printlev_loc >= 2 ) &
442            WRITE(numout,*) '       sapwood -> heartwood conversion time (d): (::longevity_sap(j))', longevity_sap(j)
443
444       !
445       ! 13 fruit lifetime (days)
446       !
447
448       IF ( printlev_loc >= 2 ) WRITE(numout,*) '       fruit lifetime (d): (::longevity_fruit(j))', longevity_fruit(j)
449
450       !
451       ! 14 length of leaf death (days)
452       !      For evergreen trees, this variable determines the lifetime of the leaves.
453       !      Note that it is different from the value given in (longevity_eff_leaf/365).
454       !
455
456       IF ( printlev_loc >= 2 ) &
457            WRITE(numout,*) '       length of leaf death (d): (::leaffall(j))', leaffall(j)
458
459
460       !
461       ! 17 minimum lai, initial (m^2.m^{-2})
462       !
463
464       IF ( is_tree(j) ) THEN
465          lai_initmin(j) = lai_initmin_tree
466       ELSE
467          lai_initmin(j) = lai_initmin_grass
468       ENDIF !( is_tree(j) )
469
470       IF ( printlev_loc >= 2 ) &
471            WRITE(numout,*) '       initial LAI: (::lai_initmin(j))', lai_initmin(j)
472
473       !
474       ! 19 maximum LAI (m^2.m^{-2})
475       !
476
477       IF ( printlev_loc >= 2 ) &
478            WRITE(numout,*) '       critical LAI above which no leaf allocation: (::lai_max(j))', lai_max(j)
479
480       !
481       ! 20 fraction of primary leaf and root allocation put into reserve (0-1, unitless)
482       !
483
484       IF ( printlev_loc >= 2 ) &
485            WRITE(numout,*) '       reserve allocation factor: (::ecureuil(j))', ecureuil(j)
486
487
488       ! 23 natural ?
489       !
490
491       IF ( printlev_loc >= 2 ) &
492            WRITE(numout,*) '       Natural: (::natural(j))', natural(j)
493
494       !
495       ! 24 Vcmax et Vjmax (umol.m^{-2}.s^{-1})
496       !
497
498       IF ( printlev_loc >= 2 ) &
499            WRITE(numout,*) '       Maximum rate of carboxylation: (::Vcmax_25(j))', vcmax25(j)
500       !
501       ! 25 constants for photosynthesis temperatures
502       !
503
504       IF ( printlev_loc >= 2 ) THEN
505
506
507          !
508          ! 26 Properties
509          !
510          WRITE(numout,*) '       C4 photosynthesis: (::is_c4(j))', is_c4(j)
511
512       ENDIF
513
514       !
515       ! 27 extinction coefficient of the Monsi and Saeki (1953) relationship
516       !
517       IF ( printlev_loc >= 2 ) THEN
518          WRITE(numout,*) '       extinction coefficient: (::ext_coeff(j))', ext_coeff(j)
519       ENDIF
520
521       !
522       ! 30 fraction of allocatable biomass which is lost as growth respiration (0-1, unitless)
523       !
524       IF ( printlev_loc >= 2 ) &
525            WRITE(numout,*) '       growth respiration fraction: (::frac_growthresp(j))', frac_growthresp(j)
526
527    ENDDO ! Loop over # PFTS
528
529    !
530    ! 29 time scales for phenology and other processes (in days)
531    !
532
533    tau_longterm_max = coeff_tau_longterm * one_year
534
535    IF ( printlev_loc >= 2 ) THEN
536
537       WRITE(numout,*) '   > time scale for ''monthly'' moisture availability (d): (::tau_hum_month)', &
538            tau_hum_month
539       WRITE(numout,*) '   > time scale for ''weekly'' moisture availability (d): (::tau_hum_week)', &
540           tau_hum_week
541       WRITE(numout,*) '   > time scale for ''monthly'' 2 meter temperature (d): (::tau_t2m_month)', &
542            tau_t2m_month
543       WRITE(numout,*) '   > time scale for ''weekly'' 2 meter temperature (d): (::tau_t2m_week)', &
544            tau_t2m_week
545       WRITE(numout,*) '   > time scale for ''weekly'' GPP (d): (::tau_gpp_week)', &
546            tau_gpp_week
547       WRITE(numout,*) '   > time scale for ''monthly'' soil temperature (d): (::tau_tsoil_month)', &
548            tau_tsoil_month
549       WRITE(numout,*) '   > time scale for vigour calculations (y): (::tau_longterm_max / one_year)', &
550            tau_longterm_max / one_year
551
552    ENDIF
553
554    !
555    ! 30 Maintenance respiration
556    !
557
558    maint_resp_slope(:,1) = maint_resp_slope_c(:)               
559    maint_resp_slope(:,2) = maint_resp_slope_b(:) 
560    maint_resp_slope(:,3) = maint_resp_slope_a(:)
561 
562    IF (printlev_loc >= 4) WRITE(numout,*) 'Leaving stomate_data'
563
564  END SUBROUTINE data
565
566END MODULE stomate_data
Note: See TracBrowser for help on using the repository browser.