source: tags/ORCHIDEE_1_9_5_1/ORCHIDEE/src_stomate/stomate_constants.f90 @ 4114

Last change on this file since 4114 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: 36.3 KB
Line 
1!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_constants.f90,v 1.21 2010/05/17 14:25:41 ssipsl Exp $
2!IPSL (2006)
3! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
4!-
5MODULE stomate_constants
6!---------------------------------------------------------------------
7  USE defprec
8  USE constantes_veg
9  USE ioipsl 
10  USE parallel
11! bare soil in Sechiba
12  INTEGER(i_std),PARAMETER :: ibare_sechiba = 1
13!-
14! 0 = no, 4 = full online diagnostics
15  INTEGER(i_std),SAVE :: bavard=1
16! write forcing file for carbon spinup?
17  LOGICAL,SAVE :: write_carbonforce
18! Horizontal indices
19  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: hori_index
20! Horizonatal + PFT indices
21  INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: horipft_index
22!-
23  ! Land cover change
24! Horizontal + P10 indices
25  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip10_index
26! Horizontal + P100 indices
27  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip100_index 
28! Horizontal + P11 indices
29  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip11_index
30! Horizontal + P101 indices
31  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip101_index 
32!-
33! time step
34  INTEGER(i_std),SAVE :: itime
35! STOMATE history file ID
36  INTEGER(i_std),SAVE :: hist_id_stomate
37! STOMATE history file ID for IPCC output
38  INTEGER(i_std),SAVE :: hist_id_stomate_IPCC
39! STOMATE restart file ID
40  INTEGER(i_std),SAVE :: rest_id_stomate
41!-
42! Freezing point
43  REAL(r_std),PARAMETER :: ZeroCelsius = 273.15
44! e
45  REAL(r_std),PARAMETER :: euler = 2.71828182846
46! Epsilon to detect a near zero floating point
47  REAL(r_std),PARAMETER :: min_stomate = 1.E-8_r_std
48! some large value
49  REAL(r_std),PARAMETER :: large_value = 1.E33_r_std
50! Special value
51  REAL(r_std),PARAMETER :: undef = -9999.
52!-
53! maximum reference long term temperature (K)
54  REAL(r_std),PARAMETER :: tlong_ref_max=303.1
55! minimum reference long term temperature (K)
56  REAL(r_std),PARAMETER :: tlong_ref_min=253.1
57!-
58! trees and litter: indices for the parts of heart- and sapwood above
59!   and below the ground
60  INTEGER(i_std),PARAMETER :: iabove = 1
61  INTEGER(i_std),PARAMETER :: ibelow = 2
62  INTEGER(i_std),PARAMETER :: nlevs = 2
63!-
64! litter: indices for metabolic and structural part
65  INTEGER(i_std),PARAMETER :: imetabolic = 1
66  INTEGER(i_std),PARAMETER :: istructural = 2
67  INTEGER(i_std),PARAMETER :: nlitt = 2
68!-
69! carbon pools: indices
70  INTEGER(i_std),PARAMETER :: iactive = 1
71  INTEGER(i_std),PARAMETER :: islow = 2
72  INTEGER(i_std),PARAMETER :: ipassive = 3
73  INTEGER(i_std),PARAMETER :: ncarb = 3
74!-
75! litter fractions: indices
76  INTEGER(i_std),PARAMETER :: ileaf = 1
77  INTEGER(i_std),PARAMETER :: isapabove = 2
78  INTEGER(i_std),PARAMETER :: isapbelow = 3
79  INTEGER(i_std),PARAMETER :: iheartabove = 4
80  INTEGER(i_std),PARAMETER :: iheartbelow = 5
81  INTEGER(i_std),PARAMETER :: iroot = 6
82  INTEGER(i_std),PARAMETER :: ifruit = 7
83  INTEGER(i_std),PARAMETER :: icarbres = 8
84  INTEGER(i_std),PARAMETER :: nparts = 8
85!-
86! transformation between types of surface
87  INTEGER(i_std),PARAMETER :: ito_natagri = 1
88  INTEGER(i_std),PARAMETER :: ito_total = 2
89!-
90! leaf age discretisation ( 1 = no discretisation )
91  INTEGER(i_std),PARAMETER :: nleafages = 4
92!-
93! alpha's : ?
94  REAL(r_std),PARAMETER :: alpha_grass = .5
95  REAL(r_std),PARAMETER :: alpha_tree = 1.
96!-
97! type declaration for photosynthesis
98  TYPE t_photo_type
99    REAL(r_std), DIMENSION(nvm)                  :: t_max_a
100    REAL(r_std), DIMENSION(nvm)                  :: t_max_b
101    REAL(r_std), DIMENSION(nvm)                  :: t_max_c
102    REAL(r_std), DIMENSION(nvm)                  :: t_opt_a
103    REAL(r_std), DIMENSION(nvm)                  :: t_opt_b
104    REAL(r_std), DIMENSION(nvm)                  :: t_opt_c
105    REAL(r_std), DIMENSION(nvm)                  :: t_min_a
106    REAL(r_std), DIMENSION(nvm)                  :: t_min_b
107    REAL(r_std), DIMENSION(nvm)                  :: t_min_c
108  END TYPE t_photo_type
109!-
110! type declaration for phenology
111  TYPE pheno_type
112    REAL(r_std), DIMENSION(nvm,3)                :: gdd
113    REAL(r_std), DIMENSION(nvm)                  :: ngd
114    REAL(r_std), DIMENSION(nvm)                  :: ncdgdd_temp
115    REAL(r_std), DIMENSION(nvm)                  :: hum_frac
116    REAL(r_std), DIMENSION(nvm)                  :: lowgpp_time
117    REAL(r_std), DIMENSION(nvm)                  :: leaffall
118    REAL(r_std), DIMENSION(nvm)                  :: leafagecrit
119    REAL(r_std)                       :: tau_hum_month
120    REAL(r_std)                       :: tau_hum_week
121    REAL(r_std)                       :: tau_t2m_month
122    REAL(r_std)                       :: tau_t2m_week
123    REAL(r_std)                       :: tau_tsoil_month
124    REAL(r_std)                       :: tau_soilhum_month
125    REAL(r_std)                       :: tau_gpp_week
126    REAL(r_std)                       :: tau_gdd
127    REAL(r_std)                       :: tau_ngd
128    REAL(r_std)                       :: tau_longterm
129    REAL(r_std), DIMENSION(nvm)                  :: lai_initmin
130    CHARACTER(len=6), DIMENSION(nvm)            :: pheno_model
131    CHARACTER(len=6), DIMENSION(nvm)            :: senescence_type
132    REAL(r_std), DIMENSION(nvm,3)                :: senescence_temp
133    REAL(r_std), DIMENSION(nvm)                  :: senescence_hum
134    REAL(r_std), DIMENSION(nvm)                  :: nosenescence_hum
135    REAL(r_std), DIMENSION(nvm)                  :: max_turnover_time
136    REAL(r_std), DIMENSION(nvm)                  :: min_leaf_age_for_senescence
137    REAL(r_std), DIMENSION(nvm)                  :: min_turnover_time
138!-
139    REAL(r_std), DIMENSION(nvm)                  :: hum_min_time
140  END TYPE pheno_type
141!-
142! parameters for the pipe model
143!-
144! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory)
145  REAL(r_std),PARAMETER :: pipe_tune1 = 100.0
146! height=pipe_tune2 * diameter**pipe_tune3
147  REAL(r_std),PARAMETER :: pipe_tune2 = 40.0
148  REAL(r_std),PARAMETER :: pipe_tune3 = 0.5
149! needed for stem diameter
150  REAL(r_std),PARAMETER :: pipe_tune4 = 0.3
151! Density
152  REAL(r_std),PARAMETER :: pipe_density = 2.e5
153! one more parameter
154  REAL(r_std),PARAMETER :: pipe_k1 = 8.e3
155!-
156! Maximum tree establishment rate
157  REAL(r_std),PARAMETER :: estab_max_tree = 0.12
158! Maximum grass establishment rate
159  REAL(r_std),PARAMETER :: estab_max_grass = 0.12
160! initial density of individuals
161  REAL(r_std),PARAMETER :: ind_0 = 0.02
162!-
163! Do we treat PFT expansion across a grid point after introduction?
164! default = .FALSE.
165  LOGICAL,SAVE :: treat_expansion = .FALSE.
166!-
167! herbivores?
168  LOGICAL,SAVE :: ok_herbivores = .FALSE.
169!-
170! harvesting ?
171  LOGICAL,SAVE :: harvest_agri = .TRUE.
172!-
173! For trees, minimum fraction of crown area occupied
174! (due to its branches etc.)
175! This means that only a small fraction of its crown area
176! can be invaded by other trees.
177  REAL(r_std),PARAMETER :: min_cover = 0.05
178!-
179! climatic parameters
180!-
181! minimum precip, in mm/year
182  REAL(r_std),PARAMETER :: precip_crit = 100.
183! minimum gdd for establishment of saplings
184  REAL(r_std),PARAMETER :: gdd_crit = 150.
185! critical fpc, needed for light competition and establishment
186  REAL(r_std),PARAMETER :: fpc_crit = 0.95
187!-
188! critical value for being adapted (1-1/e)
189  REAL(r_std),PARAMETER :: adapted_crit = 1. - ( 1. / euler )
190! critical value for being regenerative (1/e)
191  REAL(r_std),PARAMETER :: regenerate_crit = 1. / euler
192!-
193! fraction of GPP which is lost as growth respiration
194  REAL(r_std),PARAMETER :: frac_growthresp = 0.28
195!-
196! description of the PFT
197  CHARACTER(len=34), SAVE, DIMENSION(nvm)              :: PFT_name = &
198 & (/ 'bared ground                      ', &          !  1
199 &    'tropical  broad-leaved evergreen  ', &          !  2
200 &    'tropical  broad-leaved raingreen  ', &          !  3
201 &    'temperate needleleaf   evergreen  ', &          !  4
202 &    'temperate broad-leaved evergreen  ', &          !  5
203 &    'temperate broad-leaved summergreen', &          !  6
204 &    'boreal    needleleaf   evergreen  ', &          !  7
205 &    'boreal    broad-leaved summergreen', &          !  8
206 &    'boreal    needleleaf   summergreen', &          !  9
207 &    '          C3           grass      ', &          ! 10
208 &    '          C4           grass      ', &          ! 11
209 &    '          C3           agriculture', &          ! 12
210 &    '          C4           agriculture'  /)         ! 13
211! extinction coefficient of the Monsi&Seaki (53) relationship
212  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ext_coeff
213! is pft a tree
214  LOGICAL, SAVE, DIMENSION(nvm)                        :: tree
215! leaf type
216! 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bared ground
217  INTEGER(i_std), SAVE, DIMENSION(nvm)                  :: leaf_tab = &
218 & (/      4,       1,       1,       2,       1,       1,       2,   &
219 &                  1,       2,       3,       3,       3,       3 /)
220! natural?
221  LOGICAL, SAVE, DIMENSION(nvm)                        :: natural =    &
222 & (/  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,   &
223 &              .TRUE.,  .TRUE.,  .TRUE.,  .TRUE., .FALSE., .FALSE. /)
224! flamability: critical fraction of water holding capacity
225  REAL(r_std), SAVE, DIMENSION(nvm)                     :: flam
226! fire resistance
227  REAL(r_std), SAVE, DIMENSION(nvm)                     :: resist 
228! specific leaf area (m**2/gC)
229  REAL(r_std), SAVE, DIMENSION(nvm)                     :: sla
230! sapling biomass (gC/ind)
231  REAL(r_std), SAVE, DIMENSION(nvm,nparts)              :: bm_sapl
232! migration speed (m/year)
233  REAL(r_std), SAVE, DIMENSION(nvm)                     :: migrate
234! maximum stem diameter from which on crown area no longer increases (m)
235  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maxdia
236! crown of tree when sapling (m**2)
237  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cn_sapl
238! critical minimum temperature (K)
239  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tmin_crit
240! critical temperature of the coldest month (K)
241  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tcm_crit
242! critical values for phenology
243  TYPE(pheno_type),SAVE :: pheno_crit
244! time constant for leaf age discretisation (d)
245  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leaf_timecst
246  ! maximum LAI, PFT-specific
247  REAL(r_std), SAVE, DIMENSION (nvm)                    :: lai_max 
248
249  ! maintenance respiration coefficient (g/g/day) at 0 deg C
250  REAL(r_std), SAVE, DIMENSION(nvm,nparts)              :: coeff_maint_zero
251  ! slope of maintenance respiration coefficient (1/K, 1/K^2, 1/K^3)
252  REAL(r_std), SAVE, DIMENSION(nvm,3)                   :: maint_resp_slope
253
254  ! residence time (y) of trees
255  REAL(r_std), SAVE, DIMENSION(nvm)                     :: residence_time 
256
257  ! leaf lifetime, tabulated
258  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leaflife_tab 
259
260  ! type of phenology
261  ! 0=bared ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
262  ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols nu comme "evergreen"
263  INTEGER(i_std), SAVE, DIMENSION(nvm)                  :: pheno_type_tab 
264
265  ! critical tmin, tabulated (C)
266  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tmin_crit_tab 
267
268  ! critical tcm, tabulated (C)
269  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tcm_crit_tab 
270
271  ! critical gdd, tabulated (C), constant c of aT^2+bT+c
272  REAL(r_std), SAVE, DIMENSION(nvm)                     :: gdd_crit1_tab 
273
274  ! critical gdd, tabulated (C), constant b of aT^2+bT+c
275  REAL(r_std), SAVE, DIMENSION(nvm)                     :: gdd_crit2_tab 
276
277  ! critical gdd, tabulated (C), constant a of aT^2+bT+c
278  REAL(r_std), SAVE, DIMENSION(nvm)                     :: gdd_crit3_tab 
279
280  ! critical ngd, tabulated. Threshold -5 degrees
281  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ngd_crit_tab 
282
283  ! critical temperature for the ncd vs. gdd function in phenology
284  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ncdgdd_temp_tab 
285
286  ! critical humidity (relative to min/max) for phenology
287  REAL(r_std), SAVE, DIMENSION(nvm)                     :: hum_frac_tab 
288
289  ! minimum duration of dormance (d) for phenology
290  REAL(r_std), SAVE, DIMENSION(nvm)                     :: lowgpp_time_tab 
291
292  ! minimum time elapsed since moisture minimum (d)
293  REAL(r_std), SAVE, DIMENSION(nvm)                     :: hum_min_time_tab 
294
295  ! sapwood -> heartwood conversion time (d)
296  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tau_sap 
297
298  ! fruit lifetime (d)
299  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tau_fruit 
300
301  ! fraction of primary leaf and root allocation put into reserve
302  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ecureuil 
303
304  ! Maximum rate of carboxylation
305  REAL(r_std), SAVE, DIMENSION(nvm)                     :: vcmax_opt 
306
307  ! Maximum rate of RUbp regeneration
308  REAL(r_std), SAVE, DIMENSION(nvm)                     :: vjmax_opt 
309
310!-
311  ! constants needed for photosynthesis temperatures
312  TYPE(t_photo_type), SAVE                              :: t_photo
313  ! lenth of death of leaves, tabulated (d)
314  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leaffall_tab 
315
316  ! critical leaf age, tabulated (d)
317  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leafagecrit_tab 
318
319  ! which phenology model is used? (tabulated)
320  CHARACTER(len=6), SAVE, DIMENSION(nvm)               :: pheno_model_tab
321! List of avaible phenology models :
322! 'hum   ', 'moi   ', 'ncdgdd', 'ngd   ', 'humgdd', 'moigdd', 'none  '
323
324  ! type of senescence, tabulated
325  CHARACTER(len=6), SAVE, DIMENSION(nvm)               :: senescence_type_tab
326!-
327! List of avaible types of senescence :
328! 'cold  ', 'dry   ', 'mixed ', 'none  '
329
330  ! critical temperature for senescence (C),
331  ! constant c of aT^2+bT+c , tabulated
332  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_temp1_tab 
333
334  ! critical temperature for senescence (C),
335  ! constant b of aT^2+bT+c , tabulated
336  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_temp2_tab 
337
338  ! critical temperature for senescence (C),
339  ! constant a of aT^2+bT+c , tabulated
340  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_temp3_tab 
341
342  ! critical relative moisture availability for senescence
343  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_hum_tab 
344
345  ! relative moisture availability above which
346  ! there is no humidity-related senescence
347  REAL(r_std), SAVE, DIMENSION(nvm)                     :: nosenescence_hum_tab 
348
349 ! maximum turnover time for grasse
350  REAL(r_std), SAVE, DIMENSION(nvm)                     :: max_turnover_time_tab 
351
352 ! minimum turnover time for grasse
353  REAL(r_std), SAVE, DIMENSION(nvm)                     :: min_turnover_time_tab 
354
355  ! minimum leaf age to allow senescence g
356  REAL(r_std), SAVE, DIMENSION(nvm)  :: min_leaf_age_for_senescence_tab 
357
358!-
359  ! slope of maintenance respiration coefficient (1/K),
360  ! constant c of aT^2+bT+c , tabulated
361  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maint_resp_slope1_tab 
362
363  ! slope of maintenance respiration coefficient (1/K),
364  ! constant b of aT^2+bT+c , tabulated
365  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maint_resp_slope2_tab 
366
367  ! slope of maintenance respiration coefficient (1/K),
368  ! constant a of aT^2+bT+c , tabulated
369  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maint_resp_slope3_tab 
370
371  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
372  ! for leaves, tabulated
373  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_leaf_tab 
374
375  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
376  ! for sapwood above, tabulated
377  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_sapabove_tab 
378
379  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
380  ! for sapwood below, tabulated
381  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_sapbelow_tab 
382
383  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
384  ! for heartwood above, tabulated
385  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_heartabove_tab 
386  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
387  ! for heartwood below, tabulated
388  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_heartbelow_tab 
389
390  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
391  ! for roots, tabulated
392  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_root_tab 
393
394  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
395  ! for fruits, tabulated
396  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_fruit_tab 
397
398  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
399  ! for carbohydrate reserve, tabulated
400  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_carbres_tab 
401
402!-
403  ! minimum photosynthesis temperature,
404  ! constant a of ax^2+bx+c (deg C), tabulated
405  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_min_a_tab 
406
407  ! minimum photosynthesis temperature,
408  ! constant b of ax^2+bx+c (deg C), tabulated
409  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_min_b_tab 
410
411  ! minimum photosynthesis temperature,
412  ! constant c of ax^2+bx+c (deg C), tabulated
413  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_min_c_tab 
414
415!-
416  ! optimum photosynthesis temperature,
417  ! constant a of ax^2+bx+c (deg C), tabulated
418
419  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_opt_a_tab 
420
421  ! optimum photosynthesis temperature,
422  ! constant b of ax^2+bx+c (deg C), tabulated
423  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_opt_b_tab 
424
425  ! optimum photosynthesis temperature,
426  ! constant c of ax^2+bx+c (deg C), tabulated
427  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_opt_c_tab 
428
429!-
430  ! maximum photosynthesis temperature,
431  ! constant a of ax^2+bx+c (deg C), tabulated
432  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_max_a_tab 
433
434  ! maximum photosynthesis temperature,
435  ! constant b of ax^2+bx+c (deg C), tabulated
436  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_max_b_tab 
437
438  ! maximum photosynthesis temperature,
439  ! constant c of ax^2+bx+c (deg C), tabulated
440  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_max_c_tab 
441
442  ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
443  REAL(r_std), SAVE, DIMENSION(nvm)                  :: alloc_min 
444  REAL(r_std), SAVE, DIMENSION(nvm)                  :: alloc_max 
445  REAL(r_std), SAVE, DIMENSION(nvm)                  :: demi_alloc 
446
447  ! Coeff of biomass export for the year
448  REAL(r_std), SAVE, DIMENSION(nvm)                  :: coeff_lcchange_1 
449
450  ! Coeff of biomass export for the decade
451  REAL(r_std), SAVE, DIMENSION(nvm)                  :: coeff_lcchange_10 
452
453  ! Coeff of biomass export for the century
454  REAL(r_std), SAVE, DIMENSION(nvm)                  :: coeff_lcchange_100 
455
456CONTAINS
457  SUBROUTINE stomate_constants_init ()
458  ! flamability: critical fraction of water holding capacity
459  flam(2:nvm) =       &
460 & (/      .15,     .25,     .25,     .25,     .25,     .25,   &
461           .25,     .25,     .25,     .25,     .35,     .35 /)
462!!$  flam(2:nvm) =       &
463!!$ & (/        .25,     .25,     .25,     .25,     .25,     .25,   &
464!!$                   .25,     .25,     .30,     .30,     .35,     .35 /)
465!  flam =       &
466! & (/        .15,     .15,     .15,     .15,     .15,     .15,   &
467! &                 .15,     .15,     .15,     .15,     .15,     .15 /)
468  ! fire resistance
469  resist(2:nvm) =     &
470 & (/     .95,     .90,     .12,     .50,     .12,     .12,   &
471 &        .12,     .12,      .0,      .0,      .0,      .0 /)
472!!$  resist(2:nvm) =     &
473!!$ & (/        .12,     .50,     .12,     .50,     .12,     .12,   &
474!!$ &                 .12,     .12,      .0,      .0,      .0,      .0 /)
475! maximum LAI, PFT-specific
476  lai_max(:) =   &
477 & (/     undef, &
478 &          7.,     7.,      5.,      5.,      5.,     4.5, &
479 &        4.5,    3.0,     2.5,     2.5,     5.,     5.  /)
480! residence time (y) of trees
481  residence_time(2:nvm) =    &
482 & (/    30.0,    30.0,    40.0,    40.0,    40.0,    80.0, &
483 &       80.0,    80.0,     0.0,     0.0,     0.0,     0.0 /)
484! leaf lifetime, tabulated
485!SZ modif to LPJ values
486  leaflife_tab(2:nvm) =      &
487 & (/        .5,      2.,     .33,      1.,     2.,      .33,   &
488 &           2.,      2.,      2.,      2.,     2.,        2. /)
489!!$  leaflife_tab(2:nvm) =      &
490!!$ & (/      .5,      1.,      .5,      .5,      1.,      .5, &
491!!$ &        1.,       1.,      1.,      1.,      1.,     1.  /)
492! type of phenology
493  ! 0=bared ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
494  ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols nu comme "evergreen"
495  pheno_type_tab(2:nvm) =    &
496 & (/      1,        3,       1,       1,       2,       1, &
497 &         2,        2,       4,       4,       2,       3 /)
498! critical tmin, tabulated (C)
499  tmin_crit_tab(2:nvm) =    &
500 & (/     0.0,     0.0,   -45.0,   -10.0,   -45.0,   -60.0, &
501 &      -60.0,   undef,   undef,   undef,   undef,   undef /)
502! critical tcm, tabulated (C)
503  tcm_crit_tab(2:nvm) =     &
504 & (/   undef,   undef,     5.0,    15.5,    15.5,    -2.0, &
505 &        5.0,    -2.0,   undef,   undef,   undef,   undef /)
506! critical gdd, tabulated (C), constant c of aT^2+bT+c
507  gdd_crit1_tab(2:nvm) =    &
508 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
509 &      undef,   undef,     270.,   400.,    125.,    400. /)
510!!$ gdd_crit1_tab(2:nvm) = &
511!!$ & (/   undef,   undef,   undef,   undef,   undef,   undef, &
512!!$ &      undef,   undef, 184.375,    400.,    125.,    400. /)
513! critical gdd, tabulated (C), constant b of aT^2+bT+c
514  gdd_crit2_tab(2:nvm) =    &
515 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
516 &      undef,   undef,    6.25,      0.,      0.,       0. /)
517! critical gdd, tabulated (C), constant a of aT^2+bT+c
518  gdd_crit3_tab(2:nvm) =    &
519 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
520 &      undef,   undef, 0.03125,      0.,      0.,       0. /)
521! critical ngd, tabulated. Threshold -5 degrees
522  ngd_crit_tab(2:nvm)  =    &
523 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
524 &      undef,     17.,   undef,   undef,   undef,   undef /)
525! critical temperature for the ncd vs. gdd function in phenology
526  ncdgdd_temp_tab(2:nvm) =  &
527 & (/   undef,   undef,   undef,   undef,      5.,   undef, &
528 &         0.,   undef,   undef,   undef,   undef,   undef /)
529! critical humidity (relative to min/max) for phenology
530  hum_frac_tab(2:nvm) =     &
531 & (/      undef,      .5,   undef,   undef,   undef,   undef,         &
532 &         undef,   undef,      .5,      .5,      .5,      .5         /)
533! minimum duration of dormance (d) for phenology
534  lowgpp_time_tab(2:nvm) =  &
535 & (/      undef,     30.,   undef,   undef,     30.,   undef,   &
536 &           30.,     30.,     30.,     30.,     30.,     30. /)
537! minimum time elapsed since moisture minimum (d)
538  hum_min_time_tab(2:nvm) =   &
539 & (/      undef,     50.,   undef,   undef,   undef,   undef,           &
540 &         undef,   undef,     35.,     35.,     75.,     75.           /)
541! sapwood -> heartwood conversion time (d)
542  tau_sap(2:nvm) =       &
543 & (/       730.,    730.,    730.,    730.,    730.,    730.,      &
544 &          730.,    730.,   undef,   undef,   undef,   undef      /)
545! fruit lifetime (d)
546  tau_fruit(2:nvm) =     &
547 & (/        90.,     90.,     90.,     90.,     90.,     90.,      &
548 &           90.,     90.,   undef,   undef,   undef,   undef      /)
549! fraction of primary leaf and root allocation put into reserve
550  ecureuil(2:nvm) =      &
551 & (/         .0,      1.,      .0,      .0,      1.,      .0,      &
552 &            1.,      1.,      1.,      1.,      1.,      1.      /)
553! Maximum rate of carboxylation
554!Shilong
555  vcmax_opt(:) =     &
556 & (/      undef, &
557 &         65.,     65.,     35.,     45.,     55.,     35.,      &
558 &         45.,     35.,     70.,     70.,    70.,    70.      /)
559  CALL getin_p("vcmax_opt", vcmax_opt)
560! 1.9.3
561!!$  vcmax_opt(2:nvm) =     &
562!!$ & (/     65.,     65.,     35.,     40.,     55.,     35.,   &
563!!$ &        45.,     35.,     70.,     70.,     70.,     70. /
564! OLD HEAD before 1.9.3
565!!$  vcmax_opt(2:nvm) =     &
566!!$ & (/        65.,     65.,     35.,     40.,     55.,     35.,      &
567!!$ &                 45.,     35.,     80.,     80.,    100.,    100.      /)
568!modif jerome carbofor
569! vcmax_opt = &
570! & (/        65.,     65.,     50.,     40.,     75.,     35.,   &
571! &           45.,     35.,     80.,     80.,    100.,    100. /)
572  !DATA vcmax_opt_tab          /      0.,     65.,     65.,    37.5,     45.,     60.,    37.5,   &
573  !                                  50.,     40.,    100.,    100.,    100.,    100. /
574!-
575! Maximum rate of RUbp regeneration
576  vjmax_opt(2:nvm) =     &
577 & (/       130.,    130.,     70.,     80.,    110.,     70.,      &
578 &           90.,     70.,    160.,    160.,    200.,    200.      /)
579!-
580  !DATA vjmax_opt_tab          /      0.,    130.,    130.,     75.,     90.,    120.,     75.,   &
581  !                                 100.,     80.,    200.,    200.,    200.,    200. /
582!-
583! length of death of leaves, tabulated (d)
584  leaffall_tab(2:nvm) =    &
585 & (/      undef,     10.,   undef,   undef,     10.,   undef,        &
586 &           10.,     10.,     10.,     10.,     10.,     10.        /)
587! critical leaf age, tabulated (d)
588! Shilong modification
589  leafagecrit_tab(2:nvm) =     &
590 & (/       730.,    180.,    910.,    730.,    180.,    910.,            &
591 &          180.,    180.,    120.,    120.,    90.,    90.            /)
592! OLD HEAD
593!!$  DATA leafagecrit_tab        /    730.,    180.,    910.,    730.,    180.,    910.,   &
594!!$                                   180.,    180.,    120.,    120.,    120.,    120. /
595!NEW SHILONG
596! & (/     730.,    180.,    910.,    730.,    180.,    910.,            &
597! &        180.,    180.,    120.,    120.,     70.,     70.            /)
598!-
599  ! which phenology model is used? (tabulated)
600  pheno_model_tab(1:nvm) =   &
601 & (/  'none  ',   'none  ',   'moi   ',   'none  ',   'none  ',   &
602 &     'ncdgdd',   'none  ',   'ncdgdd',   'ngd   ',   'moigdd',   &
603 &     'moigdd',   'moigdd',   'moigdd'           /) 
604! List of avaible phenology models :
605! 'hum   ', 'moi   ', 'ncdgdd', 'ngd   ', 'humgdd', 'moigdd', 'none  '
606!-
607  ! type of senescence, tabulated
608  senescence_type_tab(1:nvm) =   &
609 & (/  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ',   &
610 &     'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ',   &
611 &     'mixed ',  'mixed ',   'mixed '            /)
612!-
613! List of avaible types of senescence :
614! 'cold  ', 'dry   ', 'mixed ', 'none  '
615!-
616! critical temperature for senescence (C),
617! constant c of aT^2+bT+c , tabulated
618  senescence_temp1_tab(2:nvm) =   &
619 & (/      undef,   undef,   undef,   undef,     12.,   undef,               &
620 &            7.,      2.,  -1.375,      5.,      5.,     10.               /)
621! critical temperature for senescence (C),
622! constant b of aT^2+bT+c , tabulated
623  senescence_temp2_tab(2:nvm) =   &
624 & (/      undef,   undef,   undef,   undef,      0.,   undef,               &
625 &            0.,      0.,      .1,      0.,      0.,      0.               /)
626! critical temperature for senescence (C),
627! constant a of aT^2+bT+c , tabulated
628  senescence_temp3_tab(2:nvm) =   &
629 & (/      undef,   undef,   undef,   undef,      0.,   undef,               &
630 &            0.,      0.,  .00375,      0.,      0.,      0.               /)
631! critical relative moisture availability for senescence
632!SZ 080806, reparameterisation of TrBR: reduce criticial moisture from .6 to .3
633! to mimic a leaf dropping at -1.49 MPa, buffered to account for sechiba
634  senescence_hum_tab(2:nvm) =  &
635 & (/      undef,      .3,   undef,   undef,   undef,   undef,            &
636 &         undef,   undef,      .2,      .2,      .3,      .2            /)
637! 1.9.3
638!!$  senescence_hum_tab(2:nvm) =  &
639!!$ & (/      undef,      .6,   undef,   undef,   undef,   undef,            &
640!!$ &         undef,   undef,      .2,      .2,      .3,      .2            /)
641! relative moisture availability above which
642! there is no humidity-related senescence
643!SZ 080806, reparameterisation of TrBR: reduce nosenencemoisture to avoid leaf dropping
644! when phenology routine would give new flushing of leaves: 1.0 to 0.8
645  nosenescence_hum_tab(2:nvm) =  &
646 & (/      undef,      .8,   undef,   undef,   undef,   undef,              &
647 &               undef,   undef,      .3,      .3,      .3,      .3              /)
648! 1.9.3
649!!$  nosenescence_hum_tab(2:nvm) =  &
650!!$ & (/      undef,      1.,   undef,   undef,   undef,   undef,              &
651!!$ &               undef,   undef,      .3,      .3,      .3,      .3              /)
652
653! maximum turnover time for grasse
654  max_turnover_time_tab(2:nvm) =   &
655 & (/      undef,   undef,    undef,   undef,   undef,   undef,                &
656 &         undef,   undef,      80.,     80.,     80.,     80.                /)
657! minimum turnover time for grasse
658  min_turnover_time_tab(2:nvm) =   &
659 & (/      undef,    undef,    undef,    undef,   undef,   undef,              &
660 &         undef,   undef,      10.,      10.,      10.,      10.             /)
661! minimum leaf age to allow senescence g
662  min_leaf_age_for_senescence_tab(:) =   &
663 & (/    undef, &
664 &       undef,    90.,   undef,   undef,    90.,    undef,          &
665 &         60.,    60.,     30.,     30.,    30.,      30.          /)
666!-
667! slope of maintenance respiration coefficient (1/K),
668! constant c of aT^2+bT+c , tabulated
669!SZ - 1.9.3
670  maint_resp_slope1_tab(2:nvm) =   &
671 & (/        .12,     .12,     .16,     .16,     .16,     .16,                &
672 &           .16,     .16,     .16,     .12,     .16,     .12                /)
673!OLD MERGE
674!!$  maint_resp_slope1_tab(2:nvm) =   &
675!!$ & (/        .16,     .16,     .16,     .16,     .16,     .16,                &
676!!$ &                 .16,     .16,     .16,     .12,     .16,     .16                /)
677!Shilong
678!!$  maint_resp_slope1_tab(2:nvm) =   &
679!!$ & (/      .12,     .12,     .16,     .16,     .16,     .16,                &
680!!$ &         .16,     .16,     .16,     .16,     .16,     .16                /)
681!-
682! slope of maintenance respiration coefficient (1/K),
683! constant b of aT^2+bT+c , tabulated
684  maint_resp_slope2_tab(2:nvm) =   &
685 & (/         .0,      .0,      .0,      .0,      .0,      .0,                &
686 &            .0,      .0, -.00133,      .0, -.00133,      .0                /)
687  ! DATA maint_resp_slope2_tab  /      .0,      .0,      .0,      .0,      .0,      .0,      .0,   &
688  !                                    .0,      .0,      .0,      .0,      .0,      .0 /
689! slope of maintenance respiration coefficient (1/K),
690! constant a of aT^2+bT+c , tabulated
691  maint_resp_slope3_tab(2:nvm) =   &
692 & (/         .0,      .0,      .0,      .0,      .0,      .0,                &
693 &            .0,      .0,      .0,      .0,      .0,      .0                /)
694!-
695! maintenance respiration coefficient (g/g/day) at 0 deg C,
696! for leaves, tabulated
697  cm_zero_leaf_tab(2:nvm) =    &
698 & (/    2.35E-3, 2.62E-3, 1.01E-3, 2.35E-3, 2.62E-3, 1.01E-3,            &
699 &       2.62E-3, 2.05E-3, 2.62E-3, 2.62E-3, 2.62E-3, 2.62E-3            /)
700!-
701! maintenance respiration coefficient (g/g/day) at 0 deg C,
702! for sapwood above, tabulated
703  cm_zero_sapabove_tab(2:nvm) =    &
704 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,                &
705 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4                /)
706!-
707! maintenance respiration coefficient (g/g/day) at 0 deg C,
708! for sapwood below, tabulated
709  cm_zero_sapbelow_tab(2:nvm) =    &
710 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,                &
711 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4                /)
712!-
713! maintenance respiration coefficient (g/g/day) at 0 deg C,
714! for heartwood above, tabulated
715  cm_zero_heartabove_tab(2:nvm) =  &
716 & (/         0.,      0.,      0.,      0.,      0.,      0.,                &
717 &            0.,      0.,      0.,      0.,      0.,      0.                /)
718!-
719! maintenance respiration coefficient (g/g/day) at 0 deg C,
720! for heartwood below, tabulated
721  cm_zero_heartbelow_tab(2:nvm) =  &
722 & (/         0.,      0.,      0.,      0.,      0.,      0.,                &
723 &            0.,      0.,      0.,      0.,      0.,      0.                /)
724!-
725! maintenance respiration coefficient (g/g/day) at 0 deg C,
726! for roots, tabulated
727  cm_zero_root_tab(2:nvm) =    &
728 & (/    1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3,            &
729 &       1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3            /)
730!-
731! maintenance respiration coefficient (g/g/day) at 0 deg C,
732! for fruits, tabulated
733  cm_zero_fruit_tab(2:nvm) =   &
734 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,            &
735 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4            /)
736!-
737! maintenance respiration coefficient (g/g/day) at 0 deg C,
738! for carbohydrate reserve, tabulated
739  cm_zero_carbres_tab(2:nvm) =    &
740 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,               &
741 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4               /)
742!-
743! minimum photosynthesis temperature,
744! constant a of ax^2+bx+c (deg C), tabulated
745  tphoto_min_a_tab(2:nvm) =   &
746 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
747 &            0.,      0.,  0.0025,      0.,      0.,      0.           /)
748!-
749! minimum photosynthesis temperature,
750! constant b of ax^2+bx+c (deg C), tabulated
751  tphoto_min_b_tab(2:nvm) =   &
752 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
753 &            0.,      0.,     0.1,      0.,      0.,      0.           /)
754!-
755! minimum photosynthesis temperature,
756! constant c of ax^2+bx+c (deg C), tabulated
757  tphoto_min_c_tab(2:nvm) =   &
758 & (/         2.,      2.,     -4.,     -3.,     -2.,     -4.,           &
759 &           -4.,     -4.,   -3.25,     13.,     -5.,     13.           /)
760!-
761! optimum photosynthesis temperature,
762! constant a of ax^2+bx+c (deg C), tabulated
763  tphoto_opt_a_tab(2:nvm) =   &
764 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
765              0.,      0.,  0.0025,      0.,      0.,      0.           /)
766! optimum photosynthesis temperature,
767! constant b of ax^2+bx+c (deg C), tabulated
768  tphoto_opt_b_tab(2:nvm) =   &
769 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
770 &            0.,      0.,    0.25,      0.,      0.,      0.           /)
771!-
772! optimum photosynthesis temperature,
773! constant c of ax^2+bx+c (deg C), tabulated
774  tphoto_opt_c_tab(2:nvm) =    &
775 & (/        37.,     37.,     25.,     32.,     26.,     25.,           &
776 &           25.,     25.,   27.25,     36.,     30.,     36.           /)
777!-
778! maximum photosynthesis temperature,
779! constant a of ax^2+bx+c (deg C), tabulated
780  tphoto_max_a_tab(2:nvm) =    &
781 & (/         0.,      0.,      0.,      0.,      0.,      0.,             &
782 &            0.,      0., 0.00375,      0.,      0.,      0.            /)
783!-
784! maximum photosynthesis temperature,
785! constant b of ax^2+bx+c (deg C), tabulated
786  tphoto_max_b_tab(2:nvm) =    &
787 & (/         0.,      0.,      0.,      0.,      0.,      0.,            &
788 &            0.,      0.,    0.35,      0.,      0.,      0.            /)
789!-
790! maximum photosynthesis temperature,
791! constant c of ax^2+bx+c (deg C), tabulated
792  tphoto_max_c_tab(2:nvm) =    &
793 & (/        55.,     55.,     38.,     48.,     38.,     38.,            &
794 &           38.,     38.,  41.125,     55.,     45.,     55.            /)
795!-
796  ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
797  alloc_min(2:nvm) =               &
798 & (/          0.2,       0.2,       0.2,       0.2,     0.2,     0.2,   &
799 &             0.2,       0.2,     undef,     undef,   undef,   undef   /)
800  alloc_max(2:nvm) =               &
801 & (/          0.8,       0.8,       0.8,       0.8,     0.8,     0.8,   &
802 &             0.8,       0.8,     undef,     undef,   undef,   undef   /)
803  demi_alloc(2:nvm) =              &
804 & (/           5.,        5.,       5.,        5.,       5.,      5.,   &
805 &              5.,        5.,    undef,     undef,    undef,   undef   /)
806
807  ! Coeff of biomass export for the year
808  coeff_lcchange_1(2:nvm) = &
809 & (/        0.597,     0.597,    0.597,     0.597,    0.597,   0.597,   &
810 &           0.597,     0.597,    0.597,     0.597,    0.597,   0.597   /)
811  ! Coeff of biomass export for the decade
812  coeff_lcchange_10(2:nvm) = &
813 & (/        0.403,     0.403,    0.299,     0.299,    0.299,   0.299,   &
814 &           0.299,     0.299,    0.299,     0.403,    0.299,   0.403   /)
815  ! Coeff of biomass export for the century
816  coeff_lcchange_100(2:nvm) = &
817 & (/           0.,        0.,    0.104,     0.104,    0.104,   0.104,   &
818 &           0.104,     0.104,    0.104,        0.,    0.104,      0.   /)
819
820  END SUBROUTINE stomate_constants_init
821
822!---------------------------
823END MODULE stomate_constants
Note: See TracBrowser for help on using the repository browser.