source: tags/ORCHIDEE_1_9_6/ORCHIDEE/src_parameters/constantes_mtc.f90 @ 3663

Last change on this file since 3663 was 733, checked in by didier.solyga, 12 years ago

Improve documentation of the new modules.

  • Property svn:keywords set to Date Revision
File size: 29.5 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_mtc
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         This module contains the standard values of the paramters for the 13 metaclasses of vegetation used by ORCHIDEE.
10!!
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S): Didier Solyga : replace default values for humscte at 2 meters soil depth by default values for humcste
14!!                   at 4 meters (used for the CMIP simulations). The standard values for 2 meters soil depth are :
15!!                   REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_mtc  =  &
16!!                   & (/ 5.0,   0.8,   0.8,   1.0,   0.8,   0.8,   1.0,  &
17!!                   &    1.0,   0.8,   4.0,   4.0,   4.0,   4.0  /)
18!!
19!! REFERENCE(S) : None
20!!
21!! SVN          :
22!! $HeadURL: $
23!! $Date$
24!! $Revision$
25!! \n
26!_ ================================================================================================================================
27
28MODULE constantes_mtc
29
30  USE defprec
31  USE constantes
32
33  IMPLICIT NONE
34
35  !
36  ! METACLASSES CHARACTERISTICS
37  !
38
39  INTEGER(i_std), PARAMETER :: nvmc = 13                         !! Number of MTCS fixed in the code (unitless)
40
41  CHARACTER(len=34), PARAMETER, DIMENSION(nvmc) :: MTC_name = &  !! description of the MTC (unitless)
42  & (/ 'bare ground                       ', &          !  1
43  &    'tropical  broad-leaved evergreen  ', &          !  2
44  &    'tropical  broad-leaved raingreen  ', &          !  3
45  &    'temperate needleleaf   evergreen  ', &          !  4
46  &    'temperate broad-leaved evergreen  ', &          !  5
47  &    'temperate broad-leaved summergreen', &          !  6
48  &    'boreal    needleleaf   evergreen  ', &          !  7
49  &    'boreal    broad-leaved summergreen', &          !  8
50  &    'boreal    needleleaf   summergreen', &          !  9
51  &    '          C3           grass      ', &          ! 10
52  &    '          C4           grass      ', &          ! 11
53  &    '          C3           agriculture', &          ! 12
54  &    '          C4           agriculture'  /)         ! 13
55
56
57  !
58  ! VEGETATION STRUCTURE
59  !
60  !-
61  !  1. Sechiba
62  !
63  !   1.1 Labels - Characteristics
64  !-
65  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_tree_mtc  =  &                          !! Is the vegetation type a tree ?
66  & (/  .FALSE.,   .TRUE.,   .TRUE.,    .TRUE.,    .TRUE.,    .TRUE.,   .TRUE., &   !! (true/false)
67  &     .TRUE.,    .TRUE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.  /)
68
69  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_deciduous_mtc  =  &                     !! is PFT deciduous ? (true/false)
70  & (/ .FALSE.,   .FALSE.,   .TRUE. ,   .FALSE.,   .FALSE.,   .TRUE.,   .FALSE.,  &
71  &    .TRUE. ,   .TRUE. ,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.  /)
72
73  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_evergreen_mtc  =  &                     !! is PFT evergreen ? (true/false)
74  & (/ .FALSE.,   .TRUE.,    .FALSE.,   .TRUE.,    .TRUE.,    .FALSE.,   .TRUE.,  &
75  &    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE. /)       
76
77  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c3_mtc  =  &                            !! is PFT C3 ? (true/false)
78  & (/ .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  .FALSE.,  & 
79  &    .FALSE.,   .FALSE.,   .TRUE.,    .FALSE.,   .TRUE.,    .FALSE.  /)
80
81  CHARACTER(LEN=5), PARAMETER, DIMENSION(nvmc) :: type_of_lai_mtc  =  &  !! Type of behaviour of the LAI evolution algorithm
82  & (/ 'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! for each vegetation type. (unitless)
83  &    'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! Value of type_of_lai : mean or interp
84  &    'inter', 'inter', 'inter' /)
85
86  !-
87  !  1.2 Prescribed Values
88  !-
89  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: veget_ori_fixed_mtc  =  &  !! Value for veget_ori for tests in
90  & (/ 0.2,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                !! 0-dim simulations (0-1, unitless)
91  &    0.0,   0.0,   0.8,   0.0,   0.0,   0.0  /)
92
93  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimax_mtc  =  &          !! laimax for maximum
94  & (/ 0.0,   8.0,   8.0,   4.0,   4.5,   4.5,   4.0,  &                !! See also type of lai interpolation (m^2.m^{-2})
95  &    4.5,   4.0,   2.0,   2.0,   2.0,   2.0  /)
96
97  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimin_mtc  = &           !! laimin for minimum lai
98  & (/ 0.0,   8.0,   0.0,   4.0,   4.5,   0.0,   4.0,  &                !! See also type of lai interpolation (m^2.m^{-2})
99  &    0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)
100
101  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_presc_mtc  =  &     !! prescribed height of vegetation (m)
102  & (/  0.0,   30.0,   30.0,   20.0,   20.0,   20.0,   15.0,  &         !! Value for height_presc : one for each vegetation type
103  &    15.0,   15.0,    0.5,    0.6,    1.0,    1.0  /)
104
105  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rveg_mtc  =  &   
106  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &
107  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0   /)
108
109  !-
110  !  2. Stomate
111  !
112  !   2.1 Labels - Characteristics
113  !
114  LOGICAL, PARAMETER, DIMENSION(nvmc) :: natural_mtc =  &                         !! natural?  (true/false)
115  & (/ .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,    .TRUE.,   .TRUE.,  &
116  &    .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .FALSE.,   .FALSE.  /)
117
118  INTEGER(i_std),PARAMETER, DIMENSION(nvmc) :: leaf_tab_mtc  =  &                 !! leaf type (1-4, unitless)
119  & (/  4,   1,   1,   2,   1,   1,   2,   &                                      !! 1=broad leaved tree, 2=needle leaved tree
120  &     1,   2,   3,   3,   3,   3   /)                                           !! 3=grass 4=bare ground
121  !-
122  !   2.2 Prescribed Values
123  !-
124   REAL(r_std), PARAMETER, DIMENSION(nvmc) :: sla_mtc  =  &                       !! specif leaf area (m^2.gC^{-1})
125  & (/ 1.5E-2,   1.53E-2,   2.6E-2,   9.26E-3,     2E-2,   2.6E-2,   9.26E-3,  &
126  &    2.6E-2,    1.9E-2,   2.6E-2,    2.6E-2,   2.6E-2,   2.6E-2  /) 
127
128
129  !
130  ! EVAPOTRANSPIRATION (sechiba)
131  !
132  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rstruct_const_mtc  =  &  !! Structural resistance. (s.m^{-1})
133  & (/ 0.0,   25.0,   25.0,   25.0,   25.0,   25.0,   25.0,  &        !! Value for rstruct_const : one for each vegetation type
134  &   25.0,   25.0,    2.5,    2.0,    2.0,    2.0   /)
135
136  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kzero_mtc  =  &                  !! A vegetation dependent constant used in the
137  & (/    0.0,   12.E-5,   12.E-5,   12.E-5,   12.E-5,   25.E-5,   12.E-5,  & !! calculation  of the surface resistance. (kg.m^2.s^{-1})
138  &    25.E-5,   25.E-5,   30.E-5,   30.E-5,   30.E-5,   30.E-5  /)           !! Value for kzero one for each vegetation type
139
140
141  !
142  ! WATER (sechiba)
143  !
144  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wmax_veg_mtc  =  &        !! Maximum field capacity for each of the
145  & (/ 150.0,   150.0,   150.0,   150.0,   150.0,   150.0,   150.0,  & !! vegetations types (Temporary). (kg.m^{-3})
146  &    150.0,   150.0,   150.0,   150.0,   150.0,   150.0  /)          !! Value of wmax_veg : max quantity of water :
147                                                                       !! one for each vegetation type
148
149  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_mtc  =  &         !! Root profile description for the different
150  & (/ 5.0,   0.4,   0.4,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types. (m^{-1})
151  &    1.0,   0.8,   4.0,   1.0,   4.0,   1.0  /)                      !! These are the factor in the exponential which gets       
152                                                                       !! the root density as a function of depth
153
154  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: throughfall_by_mtc  =  &  !! Fraction of rain intercepted by the canopy
155  & (/ 30.0,   30.0,   30.0,   30.0,   30.0,   30.0,   30.0,  &        !! (0-100, unitless)
156  &    30.0,   30.0,   30.0,   30.0,   30.0,   30.0  /)
157
158
159  !
160  ! ALBEDO (sechiba)
161  !
162  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_ini_mtc  =  &     !! Initial snow albedo value for each vegetation type
163  & (/ 0.35,    0.0,    0.0,   0.14,   0.14,   0.14,   0.14,  &      !! as it will be used in condveg_snow (unitless)
164  &    0.14,   0.14,   0.18,   0.18,   0.18,   0.18  /)              !! Source : Values are from the Thesis of S. Chalita (1992)
165
166  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_mtc  =  &     !! Decay rate of snow albedo value for each vegetation type
167  & (/ 0.45,    0.0,    0.0,   0.06,   0.06,   0.11,   0.06,  &      !! as it will be used in condveg_snow (unitless)
168  &    0.11,   0.11,   0.52,   0.52,   0.52,   0.52  /)              !! Source : Values are from the Thesis of S. Chalita (1992)
169
170  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_vis_mtc  =  &  !! leaf albedo of vegetation type, visible albedo
171  & (/ 0.00,   0.04,   0.06,   0.06,   0.06,   0.06,   0.06,  &      !! (unitless)
172  &    0.06,   0.06,   0.10,   0.10,   0.10,   0.10  /) 
173
174  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_nir_mtc  =  &  !! leaf albedo of vegetation type, near infrared albedo
175  & (/ 0.00,   0.20,   0.22,   0.22,   0.22,   0.22,   0.22,  &      !! (unitless)
176  &    0.22,   0.22,   0.30,   0.30,   0.30,   0.30  /)
177
178
179  !
180  ! SOIL - VEGETATION
181  !
182  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_sand_mtc  =  &  !! Prefered soil type for the first layer
183  & (/ 1,   3,   3,   2,   2,   2,   2,  &                                    !! of the soil. (1-3, unitless)
184  &    2,   2,   2,   2,   2,   2  /)                                         !! 1=sand, 2=loan, 3=clay
185
186  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_loan_mtc  =  &  !! Prefered soil type for the second layer
187  & (/ 2,   2,   3,   3,   3,   3,   3,  &                                    !! of the soil. (1-3, unitless)
188  &    3,   3,   3,   3,   3,   3  /)                                         !! 1=sand, 2=loan, 3=clay
189
190  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_clay_mtc  =  &  !! Prefered soil type for the third layer
191  & (/ 3,   1,   1,   1,   1,   1,   1,  &                                    !! of the soil. (1-3, unitless)
192  &    1,   1,   1,   1,   1,   1  /)                                         !! 1=sand, 2=loan, 3=clay
193
194
195  !
196  ! PHOTOSYNTHESIS
197  !
198  !-
199  ! 1 .CO2
200  !-
201  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c4_mtc  =  &                            !! flag for C4 vegetation types (true/false)
202  & (/ .FALSE.,  .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  &
203  &    .FALSE.,  .FALSE.,   .FALSE.,   .TRUE.,    .FALSE.,   .TRUE.  /)
204
205  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gsslope_mtc  =  &       !! Slope of the gs/A relation (Ball & al.) (unitless)
206  & (/ 0.0,   9.0,   9.0,   9.0,   9.0,   9.0,   9.0,  & 
207  &    9.0,   9.0,   9.0,   3.0,   9.0,   3.0  /)
208
209  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gsoffset_mtc  =  &      !! intercept of the gs/A relation (Ball & al.)(unitless)
210  & (/  0.0,   0.01,   0.01,   0.01,   0.01,   0.01,   0.01,  &
211  &    0.01,   0.01,   0.01,   0.03,   0.01,   0.03  /)
212
213  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_fix_mtc  =  &     !! values used for vcmax when STOMATE is not
214  & (/  0.0,   40.0,   50.0,   30.0,   35.0,   40.0,   30.0,  &      !! activated (µmol.m^{-2}.s^{-1})
215  &    40.0,   35.0,   60.0,   60.0,   70.0,   70.0  /)
216
217  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vjmax_fix_mtc  =  &     !! values used for vjmax when STOMATE is no
218  & (/  0.0,   80.0,   100.0,    60.0,    70.0,    80.0,   60.0,  &  !! activated (µmol.m^{-2}.s^{-1})
219  &    80.0,   70.0,   120.0,   120.0,   140.0,   140.0  /)
220
221  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: co2_tmin_fix_mtc  =  &  !! values used for photosynthesis tmin
222  & (/ 0.0,    2.0,    2.0,   -4.0,   -3.0,   -2.0,   -4.0,  &       !! when STOMATE is not activated (C)
223  &   -4.0,   -4.0,   -5.0,    6.0,   -5.0,    6.0  /)
224
225  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: co2_topt_fix_mtc  =  &  !! values used for photosynthesis tpopt
226  & (/  0.0,   27.5,   27.5,   17.5,   25.0,   20.0,   17.5,  &      !! when STOMATE is not activated (C)
227  &    17.5,   17.5,   20.0,   32.5,   20.0,   32.5  /)
228
229  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: co2_tmax_fix_mtc  =  &  !! values used for photosynthesis tmax
230  & (/  0.0,   55.0,   55.0,   38.0,   48.0,   38.0,   38.0,  &      !! when STOMATE is not activated (C)
231  &    38.0,   38.0,   45.0,   55.0,   45.0,   55.0  /)
232  !-
233  ! 2 .Stomate
234  !-
235  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_mtc  =  &     !! extinction coefficient of the Monsi&Saeki
236  & (/ 0.5,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &             !! relationship (1953) (unitless)
237  &    0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
238
239  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_opt_mtc  =  &     !! Maximum rate of carboxylation (µmol.m^{-2}.s^{-1})
240  & (/ undef,   65.0,    65.0,    35.0,   45.0,   55.0,   35.0,  &
241  &     45.0,   35.0,    70.0,    70.0,   70.0,   70.0  /)
242
243  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vjmax_opt_mtc  =  &     !! Maximum rate of RUbp regeneration (µmol.m^{-2}.s^{-1})
244  & (/  undef,   130.0,   130.0,    70.0,    80.0,   110.0,   70.0,  &
245  &      90.0,    70.0,   160.0,   160.0,   200.0,   200.0  /)
246
247  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_a_mtc  =  &  !! minimum photosynthesis temperature,
248  & (/  undef,   0.0,      0.0,   0.0,   0.0,   0.0,   0.0,  &       !! constant a of ax^2+bx+c (deg C), tabulated
249  &       0.0,   0.0,   0.0025,   0.0,   0.0,   0.0  /)
250
251  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_b_mtc  =  &  !! minimum photosynthesis temperature,
252  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &          !! constant b of ax^2+bx+c (deg C), tabulated
253  &       0.0,   0.0,   0.1,   0.0,   0.0,   0.0  /)
254
255  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_c_mtc  =  &  !! minimum photosynthesis temperature,
256  & (/  undef,    2.0,     2.0,   -4.0,   -3.0,   -2.0,   -4.0,  &   !! constant b of ax^2+bx+c (deg C), tabulated
257  &      -4.0,   -4.0,   -3.25,   13.0,   -5.0,   13.0  /)
258
259  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_opt_a_mtc  =  &  !! optimum photosynthesis temperature,
260  & (/  undef,   0.0,      0.0,   0.0,   0.0,   0.0,   0.0,  &       !! constant a of ax^2+bx+c (deg C), tabulated
261  &       0.0,   0.0,   0.0025,   0.0,   0.0,   0.0  /)
262
263  REAL(r_std),  PARAMETER, DIMENSION(nvmc) :: tphoto_opt_b_mtc  =  & !! optimum photosynthesis temperature,
264  & (/  undef,   0.0,    0.0,   0.0,   0.0,   0.0,   0.0,  &         !! constant b of ax^2+bx+c (deg C), tabulated
265  &       0.0,   0.0,   0.25,   0.0,   0.0,   0.0  /)
266
267  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_opt_c_mtc  =  &  !! optimum photosynthesis temperature,
268  & (/  undef,   37.0,    37.0,   25.0,   32.0,   26.0,   25.0,  &   !! constant c of ax^2+bx+c (deg C), tabulated
269  &      25.0,   25.0,   27.25,   36.0,   30.0,   36.0  /)
270
271  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_a_mtc  =  &  !! maximum photosynthesis temperature,
272  & (/  undef,   0.0,       0.0,   0.0,   0.0,   0.0,   0.0,  &      !! constant a of ax^2+bx+c (deg C), tabulated
273  &       0.0,   0.0,   0.00375,   0.0,   0.0,   0.0  /)
274
275  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_b_mtc  =  &  !! maximum photosynthesis temperature,
276  & (/  undef,   0.0,    0.0,   0.0,   0.0,   0.0,   0.0,  &         !! constant b of ax^2+bx+c (deg C), tabulated
277  &       0.0,   0.0,   0.35,   0.0,   0.0,   0.0  /)
278
279  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_c_mtc  =  &  !! maximum photosynthesis temperature,
280  & (/  undef,   55.0,     55.0,   38.0,   48.0,   38.0,   38.0,  &  !! constant c of ax^2+bx+c (deg C), tabulated
281  &      38.0,   38.0,   41.125,   55.0,   45.0,   55.0  /)
282
283
284  !
285  ! RESPIRATION (stomate)
286  !
287  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_c_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
288  & (/  undef,   0.12,   0.12,   0.16,   0.16,   0.16,   0.16,  &          !! constant c of aT^2+bT+c, tabulated
289  &      0.16,   0.16,   0.16,   0.12,   0.16,   0.12  /)
290
291  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_b_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
292  & (/  undef,   0.0,        0.0,   0.0,        0.0,   0.0,   0.0,  &      !! constant b of aT^2+bT+c, tabulated
293  &       0.0,   0.0,   -0.00133,   0.0,   -0.00133,   0.0  /)
294
295  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_a_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
296  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                !! constant a of aT^2+bT+c, tabulated
297  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)
298
299  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_leaf_mtc  =   &                  !! maintenance respiration coefficient
300  & (/   undef,   2.35E-3,   2.62E-3,   1.01E-3,   2.35E-3,   2.62E-3,   1.01E-3,  &  !! at 0 deg C,for leaves, tabulated,
301  &    2.62E-3,   2.05E-3,   2.62E-3,   2.62E-3,   2.62E-3,   2.62E-3  /)             !! (gC.gC^{-1}.day^{-1})
302
303  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapabove_mtc =  &                !! maintenance respiration coefficient
304  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for sapwood above,
305  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, (gC.gC^{-1}.day^{-1})
306
307  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapbelow_mtc  =  &               !! maintenance respiration coefficient
308  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for sapwood below,
309  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, (gC.gC^{-1}.day^{-1}) 
310
311  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartabove_mtc  =  &             !! maintenance respiration coefficient
312  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                           !! at 0 deg C, for heartwood above,
313  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                                  !! tabulated, (gC.gC^{-1}.day^{-1})
314
315  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartbelow_mtc  =  &             !! maintenance respiration coefficient
316  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                           !! at 0 deg C, for heartwood below,
317  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                                  !! tabulated, (gC.gC^{-1}.day^{-1}) 
318
319  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_root_mtc  =  &                   !! maintenance respiration coefficient
320  & (/   undef,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,  &  !! at 0 deg C, for roots, tabulated,
321  &    1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3  /)             !! (gC.gC^{-1}.day^{-1}) 
322
323  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_fruit_mtc  =  &                  !! maintenance respiration coefficient
324  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for fruits, tabulated,
325  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! (gC.gC^{-1}.day^{-1})
326
327  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_carbres_mtc  =  &                !! maintenance respiration coefficient
328  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for carbohydrate reserve,
329  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, (gC.gC^{-1}.day^{-1})   
330
331
332  !
333  ! FIRE (stomate)
334  !
335  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: flam_mtc  =  &         !! flamability: critical fraction of water
336  & (/  undef,   0.15,   0.25,   0.25,   0.25,   0.25,   0.25,  &  !! holding capacity (0-1, unitless)
337  &      0.25,   0.25,   0.25,   0.25,   0.35,   0.35  /)
338
339  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: resist_mtc  =  &       !! fire resistance (0-1, unitless)
340  & (/ undef,   0.95,   0.90,   0.12,   0.50,   0.12,   0.12,  &
341  &    0.12,    0.12,    0.0,    0.0,    0.0,    0.0 /) 
342
343
344  !
345  ! FLUX - LUC
346  !
347  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_1_mtc  =  &   !! Coeff of biomass export for the year
348  & (/  undef,   0.597,   0.597,   0.597,   0.597,   0.597,   0.597,  &   !! (0-1, unitless)
349  &     0.597,   0.597,   0.597,   0.597,   0.597,   0.597  /)
350
351  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_10_mtc  =  &  !! Coeff of biomass export for the decade
352  & (/  undef,   0.403,   0.403,   0.299,   0.299,   0.299,   0.299,  &   !! (0-1, unitless)
353  &     0.299,   0.299,   0.299,   0.403,   0.299,   0.403  /) 
354
355  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_100_mtc  =  & !! Coeff of biomass export for the century
356  & (/  undef,     0.0,     0.0,   0.104,   0.104,   0.104,   0.104,  &   !! (0-1, unitless)
357  &     0.104,   0.104,   0.104,     0.0,   0.104,     0.0  /)
358
359
360  !
361  ! PHENOLOGY
362  !
363  !-
364  ! 1. Stomate
365  !-
366  REAL(r_std), PARAMETER, DIMENSION (nvmc) :: lai_max_mtc  =  &          !! maximum LAI, PFT-specific (m^2.m^{-2})
367  & (/ undef,   7.0,   7.0,   5.0,   5.0,   5.0,   4.5,  &
368  &      4.5,   3.0,   2.5,   2.5,   5.0,   5.0  /)
369
370  CHARACTER(len=6), PARAMETER, DIMENSION(nvmc) :: pheno_model_mtc  =  &  !! which phenology model is used? (tabulated)
371  & (/  'none  ',   'none  ',   'moi   ',   'none  ',   'none  ',  &
372  &     'ncdgdd',   'none  ',   'ncdgdd',   'ngd   ',   'moigdd',  &
373  &     'moigdd',   'moigdd',   'moigdd'  /) 
374
375  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pheno_type_mtc  =  &     !! type of phenology (0-4, unitless)
376  & (/  0,   1,   3,   1,   1,   2,   1,  &                              !! 0=bare ground 1=evergreen,  2=summergreen,
377  &     2,   2,   4,   4,   2,   3  /)                                   !! 3=raingreen,  4=perennial
378  !-
379  ! 2. Leaf Onset
380  !-
381  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_c_mtc  =  &    !! critical gdd, tabulated (C),
382  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant c of aT^2+bT+c
383  &     undef,   undef,   270.0,   400.0,   125.0,   400.0  /)
384
385  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_b_mtc  =  &    !! critical gdd, tabulated (C),
386  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant b of aT^2+bT+c
387  &     undef,   undef,    6.25,     0.0,     0.0,     0.0  /)
388
389  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_a_mtc  =  &    !! critical gdd, tabulated (C),
390  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  &  !! constant a of aT^2+bT+c
391  &     undef,   undef,   0.03125,     0.0,     0.0,     0.0  /)
392
393  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ngd_crit_mtc  =  &            !! critical ngd, tabulated.
394  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! Threshold -5 degrees (days)
395  &     undef,    17.0,   undef,   undef,   undef,   undef  /)
396
397  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ncdgdd_temp_mtc  =  &         !! critical temperature for the ncd vs. gdd
398  & (/  undef,   undef,   undef,   undef,   undef,     5.0,   undef,  &    !! function in phenology (C)
399  &       0.0,   undef,   undef,   undef,   undef,   undef  /)
400
401  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_frac_mtc  =  &            !! critical humidity (relative to min/max)
402  & (/  undef,   undef,   0.5,   undef,   undef,   undef,   undef, &       !! for phenology (unitless)
403  &     undef,   undef,   0.5,     0.5,     0.5,     0.5  /)
404
405  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lowgpp_time_mtc  =  &         !! minimum duration of dormance
406  & (/  undef,   undef,   30.0,   undef,   undef,   30.0,   undef,  &      !! for phenology (days)
407  &      30.0,    30.0,   30.0,    30.0,    30.0,   30.0  /) 
408
409  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_min_time_mtc  =  &        !! minimum time elapsed since
410  & (/  undef,   undef,   50.0,   undef,   undef,   undef,   undef,  &     !! moisture minimum (days)
411  &     undef,   undef,   35.0,    35.0,    75.0,    75.0  /) 
412
413  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_sap_mtc  =  &             !! time (days) 
414  & (/  undef,   730.0,   730.0,   730.0,   730.0,   730.0,   730.0,  &
415  &     730.0,   730.0,   undef,   undef,   undef,   undef  /)
416
417  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_fruit_mtc  =  &           !! fruit lifetime (days)
418  & (/  undef,  90.0,    90.0,    90.0,    90.0,   90.0,   90.0,  &
419  &      90.0,  90.0,   undef,   undef,   undef,   undef  /)
420
421  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ecureuil_mtc  =  &            !! fraction of primary leaf and root allocation
422  & (/  undef,   0.0,   1.0,   0.0,   0.0,   1.0,   0.0,  &                !! put into reserve (0-1, unitless)
423  &       1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
424
425  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_min_mtc  =  &           !! NEW - allocation above/below = f(age)
426  & (/  undef,   0.2,     0.2,     0.2,     0.2,    0.2,   0.2,  &         !! - 30/01/04 NV/JO/PF
427  &       0.2,   0.2,   undef,   undef,   undef,   undef  /)
428
429  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_max_mtc  =  &           !! NEW - allocation above/below = f(age)
430  & (/  undef,   0.8,     0.8,     0.8,     0.8,    0.8,   0.8,  &         !! - 30/01/04 NV/JO/PF
431  &       0.8,   0.8,   undef,   undef,   undef,   undef  /)
432
433  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: demi_alloc_mtc  =  &          !! NEW - allocation above/below = f(age)
434  & (/  undef,   5.0,     5.0,     5.0,     5.0,    5.0,   5.0,  &         !! - 30/01/04 NV/JO/PF
435  &       5.0,   5.0,   undef,   undef,   undef,   undef  /)
436
437  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaflife_mtc  =  &            !! leaf longevity, tabulated (??units??)
438  & (/  undef,   0.5,   2.0,   0.33,   1.0,   2.0,   0.33,  &
439  &       2.0,   2.0,   2.0,   2.0,    2.0,   2.0  /)
440  !-
441  ! 3. Senescence
442  !-
443  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaffall_mtc  =  &             !! length of death of leaves, tabulated (days)
444  & (/  undef,   undef,   10.0,   undef,   undef,   10.0,   undef,  &
445  &      10.0,    10.0,   10.0,    10.0,    10.0,   10.0  /)
446
447  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leafagecrit_mtc  =  &          !! critical leaf age, tabulated (days)
448  & (/  undef,   730.0,   180.0,   910.0,   730.0,   180.0,   910.0,  &
449  &     180.0,   180.0,   120.0,   120.0,    90.0,    90.0  /)
450
451  CHARACTER(LEN=6), PARAMETER, DIMENSION(nvmc) :: senescence_type_mtc  =  & !! type of senescence, tabulated (unitless)
452  & (/  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ',  &
453  &     'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ',  &
454  &     'mixed ',  'mixed ',   'mixed '            /)
455
456  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_hum_mtc  =  &       !! critical relative moisture availability
457  & (/  undef,   undef,   0.3,   undef,   undef,   undef,   undef,  &       !! for senescence (0-1, unitless)
458  &     undef,   undef,   0.2,     0.2,     0.3,     0.2  /)
459
460  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nosenescence_hum_mtc  =  &     !! relative moisture availability above which
461  & (/  undef,   undef,   0.8,   undef,   undef,   undef,   undef,  &       !! there is no humidity-related senescence
462  &     undef,   undef,   0.3,     0.3,     0.3,     0.3  /)                !! (0-1, unitless)
463
464  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_turnover_time_mtc  =  &    !! maximum turnover time for grasses (days)
465  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
466  &     undef,   undef,    80.0,    80.0,    80.0,    80.0  /)
467
468  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_turnover_time_mtc  =  &    !! minimum turnover time for grasses (days)
469  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
470  &     undef,   undef,    10.0,    10.0,    10.0,    10.0  /)
471 
472  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_leaf_age_for_senescence_mtc  =  &  !! minimum leaf age to allow
473  & (/  undef,   undef,   90.0,   undef,   undef,   90.0,   undef,  &               !! senescence g (days)
474  &      60.0,    60.0,   30.0,    30.0,    30.0,   30.0  /)
475
476  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_c_mtc  =  &    !! critical temperature for senescence (C)
477  & (/  undef,   undef,    undef,   undef,   undef,   12.0,   undef,  &     !! constant c of aT^2+bT+c, tabulated
478  &       7.0,     2.0,   -1.375,     5.0,    5.0,    10.0  /)              !! (unitless)
479
480  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_b_mtc  =  &    !! critical temperature for senescence (C),
481  & (/  undef,   undef,   undef,   undef,   undef,   0.0,   undef,  &       !! constant b of aT^2+bT+c, tabulated
482  &       0.0,     0.0,     0.1,     0.0,     0.0,   0.0  /)                !! (unitless)
483
484  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_a_mtc  =  &    !! critical temperature for senescence (C),
485  & (/  undef,   undef,     undef,   undef,   undef,   0.0,   undef,  &     !! constant a of aT^2+bT+c, tabulated
486  &       0.0,     0.0,   0.00375,     0.0,     0.0,   0.0  /)              !! (unitless)
487
488
489  !
490  ! DGVM
491  !
492  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: residence_time_mtc  =  &    !! residence time of trees (years)
493  & (/  undef,   30.0,   30.0,   40.0,   40.0,   40.0,   80.0,  &
494  &      80.0,   80.0,    0.0,    0.0,    0.0,    0.0  /) 
495
496  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_crit_mtc  =  &
497  & (/  undef,     0.0,     0.0,   -30.0,   -14.0,   -30.0,   -45.0,  &  !! critical tmin, tabulated (C)
498  &     -45.0,   undef,   undef,   undef,   undef,   undef  /)
499
500  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tcm_crit_mtc  =  &
501  & (/  undef,   undef,   undef,     5.0,    15.5,    15.5,   -8.0,  &   !! critical tcm, tabulated (C)
502  &      -8.0,    -8.0,   undef,   undef,   undef,   undef  /)
503
504
505END MODULE constantes_mtc
Note: See TracBrowser for help on using the repository browser.