source: tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_stomate/stomate_constants.f90 @ 3627

Last change on this file since 3627 was 316, checked in by martial.mancip, 13 years ago

Adjustment in stomate_constants of tmin_crit and tcm_crit
used to calculate adaptation and regeneration of PFT
for a better discrimination between boreal and temperate PFTs.

File size: 36.8 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  ! min npp to test competition between grass
163  REAL(r_std), PARAMETER :: npp_min = 100.
164!-
165! Do we treat PFT expansion across a grid point after introduction?
166! default = .FALSE.
167  LOGICAL,SAVE :: treat_expansion = .FALSE.
168! Do we treat calculate constant mortality if vegetation is static?
169! default = .TRUE.
170  LOGICAL, SAVE :: lpj_gap_const_mort = .TRUE.
171!-
172! herbivores?
173  LOGICAL,SAVE :: ok_herbivores = .FALSE.
174!-
175! harvesting ?
176  LOGICAL,SAVE :: harvest_agri = .TRUE.
177!-
178! For trees, minimum fraction of crown area occupied
179! (due to its branches etc.)
180! This means that only a small fraction of its crown area
181! can be invaded by other trees.
182  REAL(r_std),PARAMETER :: min_cover = 0.05
183!-
184! climatic parameters
185!-
186! minimum precip, in mm/year
187  REAL(r_std),PARAMETER :: precip_crit = 100.
188! minimum gdd for establishment of saplings
189  REAL(r_std),PARAMETER :: gdd_crit = 150.
190! critical fpc, needed for light competition and establishment
191  REAL(r_std),PARAMETER :: fpc_crit = 0.95
192!-
193! critical value for being adapted (1-1/e)
194  REAL(r_std),PARAMETER :: adapted_crit = 1. - ( 1. / euler )
195! critical value for being regenerative (1/e)
196  REAL(r_std),PARAMETER :: regenerate_crit = 1. / euler
197!-
198! fraction of GPP which is lost as growth respiration
199  REAL(r_std),PARAMETER :: frac_growthresp = 0.28
200!-
201! minimum availability to calculate mortality
202  REAL(r_std),PARAMETER :: min_avail = 0.02
203!-
204! description of the PFT
205  CHARACTER(len=34), SAVE, DIMENSION(nvm)              :: PFT_name = &
206 & (/ 'bared ground                      ', &          !  1
207 &    'tropical  broad-leaved evergreen  ', &          !  2
208 &    'tropical  broad-leaved raingreen  ', &          !  3
209 &    'temperate needleleaf   evergreen  ', &          !  4
210 &    'temperate broad-leaved evergreen  ', &          !  5
211 &    'temperate broad-leaved summergreen', &          !  6
212 &    'boreal    needleleaf   evergreen  ', &          !  7
213 &    'boreal    broad-leaved summergreen', &          !  8
214 &    'boreal    needleleaf   summergreen', &          !  9
215 &    '          C3           grass      ', &          ! 10
216 &    '          C4           grass      ', &          ! 11
217 &    '          C3           agriculture', &          ! 12
218 &    '          C4           agriculture'  /)         ! 13
219! extinction coefficient of the Monsi&Seaki (53) relationship
220  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ext_coeff
221! is pft a tree
222  LOGICAL, SAVE, DIMENSION(nvm)                        :: tree
223! leaf type
224! 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bared ground
225  INTEGER(i_std), SAVE, DIMENSION(nvm)                  :: leaf_tab = &
226 & (/      4,       1,       1,       2,       1,       1,       2,   &
227 &                  1,       2,       3,       3,       3,       3 /)
228! natural?
229  LOGICAL, SAVE, DIMENSION(nvm)                        :: natural =    &
230 & (/  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,  .TRUE.,   &
231 &              .TRUE.,  .TRUE.,  .TRUE.,  .TRUE., .FALSE., .FALSE. /)
232! flamability: critical fraction of water holding capacity
233  REAL(r_std), SAVE, DIMENSION(nvm)                     :: flam
234! fire resistance
235  REAL(r_std), SAVE, DIMENSION(nvm)                     :: resist 
236! specific leaf area (m**2/gC)
237  REAL(r_std), SAVE, DIMENSION(nvm)                     :: sla
238! sapling biomass (gC/ind)
239  REAL(r_std), SAVE, DIMENSION(nvm,nparts)              :: bm_sapl
240! migration speed (m/year)
241  REAL(r_std), SAVE, DIMENSION(nvm)                     :: migrate
242! maximum stem diameter from which on crown area no longer increases (m)
243  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maxdia
244! crown of tree when sapling (m**2)
245  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cn_sapl
246! critical minimum temperature (K)
247  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tmin_crit
248! critical temperature of the coldest month (K)
249  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tcm_crit
250! critical values for phenology
251  TYPE(pheno_type),SAVE :: pheno_crit
252! time constant for leaf age discretisation (d)
253  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leaf_timecst
254  ! maximum LAI, PFT-specific
255  REAL(r_std), SAVE, DIMENSION (nvm)                    :: lai_max 
256
257  ! maintenance respiration coefficient (g/g/day) at 0 deg C
258  REAL(r_std), SAVE, DIMENSION(nvm,nparts)              :: coeff_maint_zero
259  ! slope of maintenance respiration coefficient (1/K, 1/K^2, 1/K^3)
260  REAL(r_std), SAVE, DIMENSION(nvm,3)                   :: maint_resp_slope
261
262  ! residence time (y) of trees
263  REAL(r_std), SAVE, DIMENSION(nvm)                     :: residence_time 
264
265  ! leaf lifetime, tabulated
266  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leaflife_tab 
267
268  ! type of phenology
269  ! 0=bared ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
270  ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols nu comme "evergreen"
271  INTEGER(i_std), SAVE, DIMENSION(nvm)                  :: pheno_type_tab 
272
273  ! critical tmin, tabulated (C)
274  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tmin_crit_tab 
275
276  ! critical tcm, tabulated (C)
277  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tcm_crit_tab 
278
279  ! critical gdd, tabulated (C), constant c of aT^2+bT+c
280  REAL(r_std), SAVE, DIMENSION(nvm)                     :: gdd_crit1_tab 
281
282  ! critical gdd, tabulated (C), constant b of aT^2+bT+c
283  REAL(r_std), SAVE, DIMENSION(nvm)                     :: gdd_crit2_tab 
284
285  ! critical gdd, tabulated (C), constant a of aT^2+bT+c
286  REAL(r_std), SAVE, DIMENSION(nvm)                     :: gdd_crit3_tab 
287
288  ! critical ngd, tabulated. Threshold -5 degrees
289  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ngd_crit_tab 
290
291  ! critical temperature for the ncd vs. gdd function in phenology
292  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ncdgdd_temp_tab 
293
294  ! critical humidity (relative to min/max) for phenology
295  REAL(r_std), SAVE, DIMENSION(nvm)                     :: hum_frac_tab 
296
297  ! minimum duration of dormance (d) for phenology
298  REAL(r_std), SAVE, DIMENSION(nvm)                     :: lowgpp_time_tab 
299
300  ! minimum time elapsed since moisture minimum (d)
301  REAL(r_std), SAVE, DIMENSION(nvm)                     :: hum_min_time_tab 
302
303  ! sapwood -> heartwood conversion time (d)
304  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tau_sap 
305
306  ! fruit lifetime (d)
307  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tau_fruit 
308
309  ! fraction of primary leaf and root allocation put into reserve
310  REAL(r_std), SAVE, DIMENSION(nvm)                     :: ecureuil 
311
312  ! Maximum rate of carboxylation
313  REAL(r_std), SAVE, DIMENSION(nvm)                     :: vcmax_opt 
314
315  ! Maximum rate of RUbp regeneration
316  REAL(r_std), SAVE, DIMENSION(nvm)                     :: vjmax_opt 
317
318!-
319  ! constants needed for photosynthesis temperatures
320  TYPE(t_photo_type), SAVE                              :: t_photo
321  ! lenth of death of leaves, tabulated (d)
322  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leaffall_tab 
323
324  ! critical leaf age, tabulated (d)
325  REAL(r_std), SAVE, DIMENSION(nvm)                     :: leafagecrit_tab 
326
327  ! which phenology model is used? (tabulated)
328  CHARACTER(len=6), SAVE, DIMENSION(nvm)               :: pheno_model_tab
329! List of avaible phenology models :
330! 'hum   ', 'moi   ', 'ncdgdd', 'ngd   ', 'humgdd', 'moigdd', 'none  '
331
332  ! type of senescence, tabulated
333  CHARACTER(len=6), SAVE, DIMENSION(nvm)               :: senescence_type_tab
334!-
335! List of avaible types of senescence :
336! 'cold  ', 'dry   ', 'mixed ', 'none  '
337
338  ! critical temperature for senescence (C),
339  ! constant c of aT^2+bT+c , tabulated
340  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_temp1_tab 
341
342  ! critical temperature for senescence (C),
343  ! constant b of aT^2+bT+c , tabulated
344  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_temp2_tab 
345
346  ! critical temperature for senescence (C),
347  ! constant a of aT^2+bT+c , tabulated
348  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_temp3_tab 
349
350  ! critical relative moisture availability for senescence
351  REAL(r_std), SAVE, DIMENSION(nvm)                     :: senescence_hum_tab 
352
353  ! relative moisture availability above which
354  ! there is no humidity-related senescence
355  REAL(r_std), SAVE, DIMENSION(nvm)                     :: nosenescence_hum_tab 
356
357 ! maximum turnover time for grasse
358  REAL(r_std), SAVE, DIMENSION(nvm)                     :: max_turnover_time_tab 
359
360 ! minimum turnover time for grasse
361  REAL(r_std), SAVE, DIMENSION(nvm)                     :: min_turnover_time_tab 
362
363  ! minimum leaf age to allow senescence g
364  REAL(r_std), SAVE, DIMENSION(nvm)  :: min_leaf_age_for_senescence_tab 
365
366!-
367  ! slope of maintenance respiration coefficient (1/K),
368  ! constant c of aT^2+bT+c , tabulated
369  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maint_resp_slope1_tab 
370
371  ! slope of maintenance respiration coefficient (1/K),
372  ! constant b of aT^2+bT+c , tabulated
373  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maint_resp_slope2_tab 
374
375  ! slope of maintenance respiration coefficient (1/K),
376  ! constant a of aT^2+bT+c , tabulated
377  REAL(r_std), SAVE, DIMENSION(nvm)                     :: maint_resp_slope3_tab 
378
379  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
380  ! for leaves, tabulated
381  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_leaf_tab 
382
383  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
384  ! for sapwood above, tabulated
385  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_sapabove_tab 
386
387  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
388  ! for sapwood below, tabulated
389  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_sapbelow_tab 
390
391  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
392  ! for heartwood above, tabulated
393  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_heartabove_tab 
394  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
395  ! for heartwood below, tabulated
396  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_heartbelow_tab 
397
398  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
399  ! for roots, tabulated
400  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_root_tab 
401
402  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
403  ! for fruits, tabulated
404  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_fruit_tab 
405
406  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
407  ! for carbohydrate reserve, tabulated
408  REAL(r_std), SAVE, DIMENSION(nvm)                     :: cm_zero_carbres_tab 
409
410!-
411  ! minimum photosynthesis temperature,
412  ! constant a of ax^2+bx+c (deg C), tabulated
413  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_min_a_tab 
414
415  ! minimum photosynthesis temperature,
416  ! constant b of ax^2+bx+c (deg C), tabulated
417  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_min_b_tab 
418
419  ! minimum photosynthesis temperature,
420  ! constant c of ax^2+bx+c (deg C), tabulated
421  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_min_c_tab 
422
423!-
424  ! optimum photosynthesis temperature,
425  ! constant a of ax^2+bx+c (deg C), tabulated
426
427  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_opt_a_tab 
428
429  ! optimum photosynthesis temperature,
430  ! constant b of ax^2+bx+c (deg C), tabulated
431  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_opt_b_tab 
432
433  ! optimum photosynthesis temperature,
434  ! constant c of ax^2+bx+c (deg C), tabulated
435  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_opt_c_tab 
436
437!-
438  ! maximum photosynthesis temperature,
439  ! constant a of ax^2+bx+c (deg C), tabulated
440  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_max_a_tab 
441
442  ! maximum photosynthesis temperature,
443  ! constant b of ax^2+bx+c (deg C), tabulated
444  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_max_b_tab 
445
446  ! maximum photosynthesis temperature,
447  ! constant c of ax^2+bx+c (deg C), tabulated
448  REAL(r_std), SAVE, DIMENSION(nvm)                     :: tphoto_max_c_tab 
449
450  ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
451  REAL(r_std), SAVE, DIMENSION(nvm)                  :: alloc_min 
452  REAL(r_std), SAVE, DIMENSION(nvm)                  :: alloc_max 
453  REAL(r_std), SAVE, DIMENSION(nvm)                  :: demi_alloc 
454
455  ! Coeff of biomass export for the year
456  REAL(r_std), SAVE, DIMENSION(nvm)                  :: coeff_lcchange_1 
457
458  ! Coeff of biomass export for the decade
459  REAL(r_std), SAVE, DIMENSION(nvm)                  :: coeff_lcchange_10 
460
461  ! Coeff of biomass export for the century
462  REAL(r_std), SAVE, DIMENSION(nvm)                  :: coeff_lcchange_100 
463
464CONTAINS
465  SUBROUTINE stomate_constants_init ()
466  ! flamability: critical fraction of water holding capacity
467  flam(2:nvm) =       &
468 & (/      .15,     .25,     .25,     .25,     .25,     .25,   &
469           .25,     .25,     .25,     .25,     .35,     .35 /)
470!!$  flam(2:nvm) =       &
471!!$ & (/        .25,     .25,     .25,     .25,     .25,     .25,   &
472!!$                   .25,     .25,     .30,     .30,     .35,     .35 /)
473!  flam =       &
474! & (/        .15,     .15,     .15,     .15,     .15,     .15,   &
475! &                 .15,     .15,     .15,     .15,     .15,     .15 /)
476  ! fire resistance
477  resist(2:nvm) =     &
478 & (/     .95,     .90,     .12,     .50,     .12,     .12,   &
479 &        .12,     .12,      .0,      .0,      .0,      .0 /)
480!!$  resist(2:nvm) =     &
481!!$ & (/        .12,     .50,     .12,     .50,     .12,     .12,   &
482!!$ &                 .12,     .12,      .0,      .0,      .0,      .0 /)
483! maximum LAI, PFT-specific
484  lai_max(:) =   &
485 & (/     undef, &
486 &          7.,     7.,      5.,      5.,      5.,     4.5, &
487 &        4.5,    3.0,     2.5,     2.5,     5.,     5.  /)
488! residence time (y) of trees
489  residence_time(2:nvm) =    &
490 & (/    30.0,    30.0,    40.0,    40.0,    40.0,    80.0, &
491 &       80.0,    80.0,     0.0,     0.0,     0.0,     0.0 /)
492! leaf lifetime, tabulated
493!SZ modif to LPJ values
494  leaflife_tab(2:nvm) =      &
495 & (/        .5,      2.,     .33,      1.,     2.,      .33,   &
496 &           2.,      2.,      2.,      2.,     2.,        2. /)
497!!$  leaflife_tab(2:nvm) =      &
498!!$ & (/      .5,      1.,      .5,      .5,      1.,      .5, &
499!!$ &        1.,       1.,      1.,      1.,      1.,     1.  /)
500! type of phenology
501  ! 0=bared ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
502  ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols nu comme "evergreen"
503  pheno_type_tab(2:nvm) =    &
504 & (/      1,        3,       1,       1,       2,       1, &
505 &         2,        2,       4,       4,       2,       3 /)
506! critical tmin, tabulated (C)
507  tmin_crit_tab(2:nvm) =    &
508 & (/     0.0,     0.0,   -30.0,   -14.0,   -30.0,   -45.0, &
509 &      -45.0,   undef,   undef,   undef,   undef,   undef /)
510! critical tcm, tabulated (C)
511  tcm_crit_tab(2:nvm) =     &
512 & (/   undef,   undef,     5.0,    15.5,    15.5,    -8.0, &
513 &        -8.0,    -8.0,   undef,   undef,   undef,   undef /)
514! critical gdd, tabulated (C), constant c of aT^2+bT+c
515  gdd_crit1_tab(2:nvm) =    &
516 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
517 &      undef,   undef,     270.,   400.,    125.,    400. /)
518!!$ gdd_crit1_tab(2:nvm) = &
519!!$ & (/   undef,   undef,   undef,   undef,   undef,   undef, &
520!!$ &      undef,   undef, 184.375,    400.,    125.,    400. /)
521! critical gdd, tabulated (C), constant b of aT^2+bT+c
522  gdd_crit2_tab(2:nvm) =    &
523 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
524 &      undef,   undef,    6.25,      0.,      0.,       0. /)
525! critical gdd, tabulated (C), constant a of aT^2+bT+c
526  gdd_crit3_tab(2:nvm) =    &
527 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
528 &      undef,   undef, 0.03125,      0.,      0.,       0. /)
529! critical ngd, tabulated. Threshold -5 degrees
530  ngd_crit_tab(2:nvm)  =    &
531 & (/   undef,   undef,   undef,   undef,   undef,   undef, &
532 &      undef,     17.,   undef,   undef,   undef,   undef /)
533! critical temperature for the ncd vs. gdd function in phenology
534  ncdgdd_temp_tab(2:nvm) =  &
535 & (/   undef,   undef,   undef,   undef,      5.,   undef, &
536 &         0.,   undef,   undef,   undef,   undef,   undef /)
537! critical humidity (relative to min/max) for phenology
538  hum_frac_tab(2:nvm) =     &
539 & (/      undef,      .5,   undef,   undef,   undef,   undef,         &
540 &         undef,   undef,      .5,      .5,      .5,      .5         /)
541! minimum duration of dormance (d) for phenology
542  lowgpp_time_tab(2:nvm) =  &
543 & (/      undef,     30.,   undef,   undef,     30.,   undef,   &
544 &           30.,     30.,     30.,     30.,     30.,     30. /)
545! minimum time elapsed since moisture minimum (d)
546  hum_min_time_tab(2:nvm) =   &
547 & (/      undef,     50.,   undef,   undef,   undef,   undef,           &
548 &         undef,   undef,     35.,     35.,     75.,     75.           /)
549! sapwood -> heartwood conversion time (d)
550  tau_sap(2:nvm) =       &
551 & (/       730.,    730.,    730.,    730.,    730.,    730.,      &
552 &          730.,    730.,   undef,   undef,   undef,   undef      /)
553! fruit lifetime (d)
554  tau_fruit(2:nvm) =     &
555 & (/        90.,     90.,     90.,     90.,     90.,     90.,      &
556 &           90.,     90.,   undef,   undef,   undef,   undef      /)
557! fraction of primary leaf and root allocation put into reserve
558  ecureuil(2:nvm) =      &
559 & (/         .0,      1.,      .0,      .0,      1.,      .0,      &
560 &            1.,      1.,      1.,      1.,      1.,      1.      /)
561! Maximum rate of carboxylation
562  !Config Key  = vcmax_opt
563  !Config Desc = Maximum rate of carboxylation
564  !Config Def  = undef, 65., 65., 35., 45., 55., 35., 45., 35., 70., 70., 70., 70.
565  !Config Help =
566  !
567!Shilong
568  vcmax_opt(:) =     &
569 & (/      undef, &
570 &         65.,     65.,     35.,     45.,     55.,     35.,      &
571 &         45.,     35.,     70.,     70.,    70.,    70.      /)
572  CALL getin_p("vcmax_opt", vcmax_opt)
573! 1.9.3
574!!$  vcmax_opt(2:nvm) =     &
575!!$ & (/     65.,     65.,     35.,     40.,     55.,     35.,   &
576!!$ &        45.,     35.,     70.,     70.,     70.,     70. /
577! OLD HEAD before 1.9.3
578!!$  vcmax_opt(2:nvm) =     &
579!!$ & (/        65.,     65.,     35.,     40.,     55.,     35.,      &
580!!$ &                 45.,     35.,     80.,     80.,    100.,    100.      /)
581!modif jerome carbofor
582! vcmax_opt = &
583! & (/        65.,     65.,     50.,     40.,     75.,     35.,   &
584! &           45.,     35.,     80.,     80.,    100.,    100. /)
585  !DATA vcmax_opt_tab          /      0.,     65.,     65.,    37.5,     45.,     60.,    37.5,   &
586  !                                  50.,     40.,    100.,    100.,    100.,    100. /
587!-
588! Maximum rate of RUbp regeneration
589  vjmax_opt(2:nvm) =     &
590 & (/       130.,    130.,     70.,     80.,    110.,     70.,      &
591 &           90.,     70.,    160.,    160.,    200.,    200.      /)
592!-
593  !DATA vjmax_opt_tab          /      0.,    130.,    130.,     75.,     90.,    120.,     75.,   &
594  !                                 100.,     80.,    200.,    200.,    200.,    200. /
595!-
596! length of death of leaves, tabulated (d)
597  leaffall_tab(2:nvm) =    &
598 & (/      undef,     10.,   undef,   undef,     10.,   undef,        &
599 &           10.,     10.,     10.,     10.,     10.,     10.        /)
600! critical leaf age, tabulated (d)
601! Shilong modification
602  leafagecrit_tab(2:nvm) =     &
603 & (/       730.,    180.,    910.,    730.,    180.,    910.,            &
604 &          180.,    180.,    120.,    120.,    90.,    90.            /)
605! OLD HEAD
606!!$  DATA leafagecrit_tab        /    730.,    180.,    910.,    730.,    180.,    910.,   &
607!!$                                   180.,    180.,    120.,    120.,    120.,    120. /
608!NEW SHILONG
609! & (/     730.,    180.,    910.,    730.,    180.,    910.,            &
610! &        180.,    180.,    120.,    120.,     70.,     70.            /)
611!-
612  ! which phenology model is used? (tabulated)
613  pheno_model_tab(1:nvm) =   &
614 & (/  'none  ',   'none  ',   'moi   ',   'none  ',   'none  ',   &
615 &     'ncdgdd',   'none  ',   'ncdgdd',   'ngd   ',   'moigdd',   &
616 &     'moigdd',   'moigdd',   'moigdd'           /) 
617! List of avaible phenology models :
618! 'hum   ', 'moi   ', 'ncdgdd', 'ngd   ', 'humgdd', 'moigdd', 'none  '
619!-
620  ! type of senescence, tabulated
621  senescence_type_tab(1:nvm) =   &
622 & (/  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ',   &
623 &     'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ',   &
624 &     'mixed ',  'mixed ',   'mixed '            /)
625!-
626! List of avaible types of senescence :
627! 'cold  ', 'dry   ', 'mixed ', 'none  '
628!-
629! critical temperature for senescence (C),
630! constant c of aT^2+bT+c , tabulated
631  senescence_temp1_tab(2:nvm) =   &
632 & (/      undef,   undef,   undef,   undef,     12.,   undef,               &
633 &            7.,      2.,  -1.375,      5.,      5.,     10.               /)
634! critical temperature for senescence (C),
635! constant b of aT^2+bT+c , tabulated
636  senescence_temp2_tab(2:nvm) =   &
637 & (/      undef,   undef,   undef,   undef,      0.,   undef,               &
638 &            0.,      0.,      .1,      0.,      0.,      0.               /)
639! critical temperature for senescence (C),
640! constant a of aT^2+bT+c , tabulated
641  senescence_temp3_tab(2:nvm) =   &
642 & (/      undef,   undef,   undef,   undef,      0.,   undef,               &
643 &            0.,      0.,  .00375,      0.,      0.,      0.               /)
644! critical relative moisture availability for senescence
645!SZ 080806, reparameterisation of TrBR: reduce criticial moisture from .6 to .3
646! to mimic a leaf dropping at -1.49 MPa, buffered to account for sechiba
647  senescence_hum_tab(2:nvm) =  &
648 & (/      undef,      .3,   undef,   undef,   undef,   undef,            &
649 &         undef,   undef,      .2,      .2,      .3,      .2            /)
650! 1.9.3
651!!$  senescence_hum_tab(2:nvm) =  &
652!!$ & (/      undef,      .6,   undef,   undef,   undef,   undef,            &
653!!$ &         undef,   undef,      .2,      .2,      .3,      .2            /)
654! relative moisture availability above which
655! there is no humidity-related senescence
656!SZ 080806, reparameterisation of TrBR: reduce nosenencemoisture to avoid leaf dropping
657! when phenology routine would give new flushing of leaves: 1.0 to 0.8
658  nosenescence_hum_tab(2:nvm) =  &
659 & (/      undef,      .8,   undef,   undef,   undef,   undef,              &
660 &               undef,   undef,      .3,      .3,      .3,      .3              /)
661! 1.9.3
662!!$  nosenescence_hum_tab(2:nvm) =  &
663!!$ & (/      undef,      1.,   undef,   undef,   undef,   undef,              &
664!!$ &               undef,   undef,      .3,      .3,      .3,      .3              /)
665
666! maximum turnover time for grasse
667  max_turnover_time_tab(2:nvm) =   &
668 & (/      undef,   undef,    undef,   undef,   undef,   undef,                &
669 &         undef,   undef,      80.,     80.,     80.,     80.                /)
670! minimum turnover time for grasse
671  min_turnover_time_tab(2:nvm) =   &
672 & (/      undef,    undef,    undef,    undef,   undef,   undef,              &
673 &         undef,   undef,      10.,      10.,      10.,      10.             /)
674! minimum leaf age to allow senescence g
675  min_leaf_age_for_senescence_tab(:) =   &
676 & (/    undef, &
677 &       undef,    90.,   undef,   undef,    90.,    undef,          &
678 &         60.,    60.,     30.,     30.,    30.,      30.          /)
679!-
680! slope of maintenance respiration coefficient (1/K),
681! constant c of aT^2+bT+c , tabulated
682!SZ - 1.9.3
683  maint_resp_slope1_tab(2:nvm) =   &
684 & (/        .12,     .12,     .16,     .16,     .16,     .16,                &
685 &           .16,     .16,     .16,     .12,     .16,     .12                /)
686!OLD MERGE
687!!$  maint_resp_slope1_tab(2:nvm) =   &
688!!$ & (/        .16,     .16,     .16,     .16,     .16,     .16,                &
689!!$ &                 .16,     .16,     .16,     .12,     .16,     .16                /)
690!Shilong
691!!$  maint_resp_slope1_tab(2:nvm) =   &
692!!$ & (/      .12,     .12,     .16,     .16,     .16,     .16,                &
693!!$ &         .16,     .16,     .16,     .16,     .16,     .16                /)
694!-
695! slope of maintenance respiration coefficient (1/K),
696! constant b of aT^2+bT+c , tabulated
697  maint_resp_slope2_tab(2:nvm) =   &
698 & (/         .0,      .0,      .0,      .0,      .0,      .0,                &
699 &            .0,      .0, -.00133,      .0, -.00133,      .0                /)
700  ! DATA maint_resp_slope2_tab  /      .0,      .0,      .0,      .0,      .0,      .0,      .0,   &
701  !                                    .0,      .0,      .0,      .0,      .0,      .0 /
702! slope of maintenance respiration coefficient (1/K),
703! constant a of aT^2+bT+c , tabulated
704  maint_resp_slope3_tab(2:nvm) =   &
705 & (/         .0,      .0,      .0,      .0,      .0,      .0,                &
706 &            .0,      .0,      .0,      .0,      .0,      .0                /)
707!-
708! maintenance respiration coefficient (g/g/day) at 0 deg C,
709! for leaves, tabulated
710  cm_zero_leaf_tab(2:nvm) =    &
711 & (/    2.35E-3, 2.62E-3, 1.01E-3, 2.35E-3, 2.62E-3, 1.01E-3,            &
712 &       2.62E-3, 2.05E-3, 2.62E-3, 2.62E-3, 2.62E-3, 2.62E-3            /)
713!-
714! maintenance respiration coefficient (g/g/day) at 0 deg C,
715! for sapwood above, tabulated
716  cm_zero_sapabove_tab(2:nvm) =    &
717 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,                &
718 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4                /)
719!-
720! maintenance respiration coefficient (g/g/day) at 0 deg C,
721! for sapwood below, tabulated
722  cm_zero_sapbelow_tab(2:nvm) =    &
723 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,                &
724 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4                /)
725!-
726! maintenance respiration coefficient (g/g/day) at 0 deg C,
727! for heartwood above, tabulated
728  cm_zero_heartabove_tab(2:nvm) =  &
729 & (/         0.,      0.,      0.,      0.,      0.,      0.,                &
730 &            0.,      0.,      0.,      0.,      0.,      0.                /)
731!-
732! maintenance respiration coefficient (g/g/day) at 0 deg C,
733! for heartwood below, tabulated
734  cm_zero_heartbelow_tab(2:nvm) =  &
735 & (/         0.,      0.,      0.,      0.,      0.,      0.,                &
736 &            0.,      0.,      0.,      0.,      0.,      0.                /)
737!-
738! maintenance respiration coefficient (g/g/day) at 0 deg C,
739! for roots, tabulated
740  cm_zero_root_tab(2:nvm) =    &
741 & (/    1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3,            &
742 &       1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3            /)
743!-
744! maintenance respiration coefficient (g/g/day) at 0 deg C,
745! for fruits, tabulated
746  cm_zero_fruit_tab(2:nvm) =   &
747 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,            &
748 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4            /)
749!-
750! maintenance respiration coefficient (g/g/day) at 0 deg C,
751! for carbohydrate reserve, tabulated
752  cm_zero_carbres_tab(2:nvm) =    &
753 & (/    1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,               &
754 &       1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4               /)
755!-
756! minimum photosynthesis temperature,
757! constant a of ax^2+bx+c (deg C), tabulated
758  tphoto_min_a_tab(2:nvm) =   &
759 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
760 &            0.,      0.,  0.0025,      0.,      0.,      0.           /)
761!-
762! minimum photosynthesis temperature,
763! constant b of ax^2+bx+c (deg C), tabulated
764  tphoto_min_b_tab(2:nvm) =   &
765 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
766 &            0.,      0.,     0.1,      0.,      0.,      0.           /)
767!-
768! minimum photosynthesis temperature,
769! constant c of ax^2+bx+c (deg C), tabulated
770  tphoto_min_c_tab(2:nvm) =   &
771 & (/         2.,      2.,     -4.,     -3.,     -2.,     -4.,           &
772 &           -4.,     -4.,   -3.25,     13.,     -5.,     13.           /)
773!-
774! optimum photosynthesis temperature,
775! constant a of ax^2+bx+c (deg C), tabulated
776  tphoto_opt_a_tab(2:nvm) =   &
777 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
778              0.,      0.,  0.0025,      0.,      0.,      0.           /)
779! optimum photosynthesis temperature,
780! constant b of ax^2+bx+c (deg C), tabulated
781  tphoto_opt_b_tab(2:nvm) =   &
782 & (/         0.,      0.,      0.,      0.,      0.,      0.,           &
783 &            0.,      0.,    0.25,      0.,      0.,      0.           /)
784!-
785! optimum photosynthesis temperature,
786! constant c of ax^2+bx+c (deg C), tabulated
787  tphoto_opt_c_tab(2:nvm) =    &
788 & (/        37.,     37.,     25.,     32.,     26.,     25.,           &
789 &           25.,     25.,   27.25,     36.,     30.,     36.           /)
790!-
791! maximum photosynthesis temperature,
792! constant a of ax^2+bx+c (deg C), tabulated
793  tphoto_max_a_tab(2:nvm) =    &
794 & (/         0.,      0.,      0.,      0.,      0.,      0.,             &
795 &            0.,      0., 0.00375,      0.,      0.,      0.            /)
796!-
797! maximum photosynthesis temperature,
798! constant b of ax^2+bx+c (deg C), tabulated
799  tphoto_max_b_tab(2:nvm) =    &
800 & (/         0.,      0.,      0.,      0.,      0.,      0.,            &
801 &            0.,      0.,    0.35,      0.,      0.,      0.            /)
802!-
803! maximum photosynthesis temperature,
804! constant c of ax^2+bx+c (deg C), tabulated
805  tphoto_max_c_tab(2:nvm) =    &
806 & (/        55.,     55.,     38.,     48.,     38.,     38.,            &
807 &           38.,     38.,  41.125,     55.,     45.,     55.            /)
808!-
809  ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
810  alloc_min(2:nvm) =               &
811 & (/          0.2,       0.2,       0.2,       0.2,     0.2,     0.2,   &
812 &             0.2,       0.2,     undef,     undef,   undef,   undef   /)
813  alloc_max(2:nvm) =               &
814 & (/          0.8,       0.8,       0.8,       0.8,     0.8,     0.8,   &
815 &             0.8,       0.8,     undef,     undef,   undef,   undef   /)
816  demi_alloc(2:nvm) =              &
817 & (/           5.,        5.,       5.,        5.,       5.,      5.,   &
818 &              5.,        5.,    undef,     undef,    undef,   undef   /)
819
820  ! Coeff of biomass export for the year
821  coeff_lcchange_1(2:nvm) = &
822 & (/        0.597,     0.597,    0.597,     0.597,    0.597,   0.597,   &
823 &           0.597,     0.597,    0.597,     0.597,    0.597,   0.597   /)
824  ! Coeff of biomass export for the decade
825  coeff_lcchange_10(2:nvm) = &
826 & (/        0.403,     0.403,    0.299,     0.299,    0.299,   0.299,   &
827 &           0.299,     0.299,    0.299,     0.403,    0.299,   0.403   /)
828  ! Coeff of biomass export for the century
829  coeff_lcchange_100(2:nvm) = &
830 & (/           0.,        0.,    0.104,     0.104,    0.104,   0.104,   &
831 &           0.104,     0.104,    0.104,        0.,    0.104,      0.   /)
832
833  END SUBROUTINE stomate_constants_init
834
835!---------------------------
836END MODULE stomate_constants
Note: See TracBrowser for help on using the repository browser.