1 | ! 23/09/2010 |
---|
2 | ! In this file we define the standard values of the parameters we |
---|
3 | ! want to externalise. For the moment, we test with lai_max |
---|
4 | ! author : D.Solyga |
---|
5 | |
---|
6 | MODULE constantes_mtc |
---|
7 | |
---|
8 | USE defprec |
---|
9 | USE constantes |
---|
10 | |
---|
11 | IMPLICIT NONE |
---|
12 | |
---|
13 | |
---|
14 | |
---|
15 | !---------------------- |
---|
16 | ! Metaclasses global |
---|
17 | !---------------------- |
---|
18 | ! |
---|
19 | ! Number of MTCS fixed in the code |
---|
20 | INTEGER(i_std), PARAMETER :: nvmc = 13 |
---|
21 | |
---|
22 | ! description of the MTC |
---|
23 | CHARACTER(len=34), SAVE, DIMENSION(nvmc) :: MTC_name = & |
---|
24 | & (/ 'bared ground ', & ! 1 |
---|
25 | & 'tropical broad-leaved evergreen ', & ! 2 |
---|
26 | & 'tropical broad-leaved raingreen ', & ! 3 |
---|
27 | & 'temperate needleleaf evergreen ', & ! 4 |
---|
28 | & 'temperate broad-leaved evergreen ', & ! 5 |
---|
29 | & 'temperate broad-leaved summergreen', & ! 6 |
---|
30 | & 'boreal needleleaf evergreen ', & ! 7 |
---|
31 | & 'boreal broad-leaved summergreen', & ! 8 |
---|
32 | & 'boreal needleleaf summergreen', & ! 9 |
---|
33 | & ' C3 grass ', & ! 10 |
---|
34 | & ' C4 grass ', & ! 11 |
---|
35 | & ' C3 agriculture', & ! 12 |
---|
36 | & ' C4 agriculture' /) ! 13 |
---|
37 | |
---|
38 | |
---|
39 | !---------------------- |
---|
40 | ! Vegetation structure |
---|
41 | !---------------------- |
---|
42 | !- |
---|
43 | ! 1 .Sechiba |
---|
44 | !- |
---|
45 | ! Value for veget_ori for tests in 0-dim simulations |
---|
46 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: veget_ori_fixed_mtc = & |
---|
47 | & (/ 0.2, 0.0, 0.0, 0.0, 0.0, & |
---|
48 | & 0.0, 0.0, 0.0, 0.0, 0.8, & |
---|
49 | & 0.0, 0.0, 0.0 /) |
---|
50 | !- |
---|
51 | ! laimax for maximum lai see also type of lai interpolation |
---|
52 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimax_mtc = & |
---|
53 | & (/ 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2./) |
---|
54 | !- |
---|
55 | ! laimin for minimum lai see also type of lai interpolation |
---|
56 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimin_mtc = & |
---|
57 | & (/ 0., 8., 0., 4., 4.5, 0., 4., 0., 0., 0., 0., 0., 0./) |
---|
58 | !- |
---|
59 | ! prescribed height of vegetation. |
---|
60 | ! Value for height_presc : one for each vegetation type |
---|
61 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_presc_mtc = & |
---|
62 | & (/ 0.,30.,30.,20.,20.,20.,15.,15.,15.,.5,.6,1.,1./) |
---|
63 | !- |
---|
64 | ! Type of behaviour of the LAI evolution algorithm |
---|
65 | ! for each vegetation type. |
---|
66 | ! Value of type_of_lai, one for each vegetation type : mean or interp |
---|
67 | CHARACTER(len=5),PARAMETER, DIMENSION(nvmc) :: type_of_lai_mtc = & |
---|
68 | & (/ 'inter', 'inter', 'inter', 'inter', 'inter', & |
---|
69 | & 'inter', 'inter', 'inter', 'inter', 'inter', & |
---|
70 | & 'inter', 'inter', 'inter' /) |
---|
71 | !- |
---|
72 | ! Is the vegetation type a tree ? |
---|
73 | LOGICAL,PARAMETER, DIMENSION(nvmc) :: is_tree_mtc = & |
---|
74 | & (/ .FALSE., .TRUE., .TRUE., .TRUE., .TRUE., & |
---|
75 | & .TRUE., .TRUE., .TRUE., .TRUE., .FALSE., & |
---|
76 | & .FALSE., .FALSE., .FALSE. /) |
---|
77 | ! used in diffuco |
---|
78 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rveg_mtc = & |
---|
79 | & (/ 1., 1., 1., 1., 1., 1. ,1. ,1. ,1. ,1. ,1. ,1., 1. /) |
---|
80 | ! |
---|
81 | !- |
---|
82 | ! 2 .Stomate |
---|
83 | !- |
---|
84 | ! leaf type |
---|
85 | ! 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bared ground |
---|
86 | INTEGER(i_std),PARAMETER, DIMENSION(nvmc) :: leaf_tab_mtc = & |
---|
87 | & (/ 4, 1, 1, 2, 1, 1, 2, & |
---|
88 | & 1, 2, 3, 3, 3, 3 /) |
---|
89 | !- |
---|
90 | ! specif leaf area (m**2/gC) |
---|
91 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: sla_mtc = & |
---|
92 | & (/ 1.5E-2, 1.53E-2, 2.6E-2, 9.26E-3, 2E-2, 2.6E-2, 9.26E-3, & |
---|
93 | & 2.6E-2, 1.9E-2, 2.6E-2, 2.6E-2, 2.6E-2, 2.6E-2 /) |
---|
94 | !- |
---|
95 | ! natural? |
---|
96 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: natural_mtc = & |
---|
97 | & (/ .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., & |
---|
98 | & .TRUE., .TRUE., .TRUE., .TRUE., .FALSE., .FALSE. /) |
---|
99 | |
---|
100 | !>> DS new for merge in the trunk ! 15/06/2011 |
---|
101 | ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' |
---|
102 | ! is PFT deciduous ? |
---|
103 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_deciduous_mtc = & |
---|
104 | & (/ .FALSE., .FALSE., .TRUE., .FALSE., .FALSE., .TRUE., .FALSE., & |
---|
105 | & .TRUE., .TRUE., .FALSE., .FALSE., .FALSE., .FALSE. /) |
---|
106 | ! is PFT evergreen ? |
---|
107 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_evergreen_mtc = & |
---|
108 | & (/ .FALSE., .TRUE., .FALSE., .TRUE., .TRUE., .FALSE., .TRUE., & |
---|
109 | & .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /) |
---|
110 | ! is PFT C3 ? |
---|
111 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c3_mtc = & |
---|
112 | & (/.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE., & |
---|
113 | & .FALSE.,.FALSE.,.FALSE.,.TRUE.,.FALSE.,.TRUE.,.FALSE. /) |
---|
114 | |
---|
115 | !------------------------------- |
---|
116 | ! Evapotranspiration - sechiba |
---|
117 | !------------------------------- |
---|
118 | ! |
---|
119 | ! Structural resistance. |
---|
120 | ! Value for rstruct_const : one for each vegetation type |
---|
121 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rstruct_const_mtc = & |
---|
122 | & (/ 0.0, 25.0, 25.0, 25.0, 25.0, 25.0, 25.0, & |
---|
123 | & 25.0, 25.0, 2.5, 2.0, 2.0, 2.0 /) |
---|
124 | !- |
---|
125 | ! A vegetation dependent constant used in the calculation |
---|
126 | ! of the surface resistance. |
---|
127 | ! Value for kzero one for each vegetation type |
---|
128 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kzero_mtc = & |
---|
129 | & (/0.0, 12.E-5, 12.E-5, 12.e-5, 12.e-5, 25.e-5, 12.e-5,& |
---|
130 | & 25.e-5, 25.e-5, 30.e-5, 30.e-5, 30.e-5, 30.e-5 /) |
---|
131 | |
---|
132 | |
---|
133 | !------------------- |
---|
134 | ! Water - sechiba |
---|
135 | !------------------- |
---|
136 | ! |
---|
137 | ! Maximum field capacity for each of the vegetations (Temporary). |
---|
138 | ! Value of wmax_veg : max quantity of water : |
---|
139 | ! one for each vegetation type en Kg/M3 |
---|
140 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wmax_veg_mtc = & |
---|
141 | & (/ 150., 150., 150., 150., 150., 150., 150., & |
---|
142 | & 150., 150., 150., 150., 150., 150. /) |
---|
143 | !- |
---|
144 | ! Root profile description for the different vegetation types. |
---|
145 | ! These are the factor in the exponential which gets |
---|
146 | ! the root density as a function of depth |
---|
147 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_mtc = & |
---|
148 | & (/5., .8, .8, 1., .8, .8, 1., 1., .8, 4., 4., 4., 4./) |
---|
149 | ! used in both hydrology modules |
---|
150 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: throughfall_by_mtc = & |
---|
151 | & (/ 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30. /) |
---|
152 | |
---|
153 | !------------------ |
---|
154 | ! Albedo - sechiba |
---|
155 | !------------------ |
---|
156 | ! |
---|
157 | ! Initial snow albedo value for each vegetation type |
---|
158 | ! as it will be used in condveg_snow |
---|
159 | ! Values are from the Thesis of S. Chalita (1992) |
---|
160 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_ini_mtc = & |
---|
161 | & (/ 0.35, 0., 0., 0.14, 0.14, & |
---|
162 | & 0.14, 0.14, 0.14, 0.14, 0.18, & |
---|
163 | & 0.18, 0.18, 0.18 /) |
---|
164 | !- |
---|
165 | ! Decay rate of snow albedo value for each vegetation type |
---|
166 | ! as it will be used in condveg_snow |
---|
167 | ! Values are from the Thesis of S. Chalita (1992) |
---|
168 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_mtc = & |
---|
169 | & (/ 0.45, 0., 0., 0.06, 0.06, & |
---|
170 | & 0.11, 0.06, 0.11, 0.11, 0.52, & |
---|
171 | & 0.52, 0.52, 0.52 /) |
---|
172 | !- |
---|
173 | ! leaf albedo of vegetation type, visible albedo |
---|
174 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_vis_mtc = & |
---|
175 | & (/ .00, .04, .06, .06, .06, & |
---|
176 | & .06, .06, .06, .06, .10, & |
---|
177 | & .10, .10, .10 /) |
---|
178 | ! leaf albedo of vegetation type, near infrared albedo |
---|
179 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_nir_mtc = & |
---|
180 | & (/ .00, .20, .22, .22, .22, & |
---|
181 | & .22, .22, .22, .22, .30, & |
---|
182 | & .30, .30, .30 /) |
---|
183 | |
---|
184 | |
---|
185 | !------------------------ |
---|
186 | ! Soil - vegetation |
---|
187 | !------------------------ |
---|
188 | ! |
---|
189 | ! Table which contains the correlation between the soil types |
---|
190 | ! and vegetation type. Two modes exist : |
---|
191 | ! 1) pref_soil_veg = 0 then we have an equidistribution |
---|
192 | ! of vegetation on soil types |
---|
193 | ! 2) Else for each pft the prefered soil type is given : |
---|
194 | ! 1=sand, 2=loan, 3=clay |
---|
195 | ! The variable is initialized in slowproc. |
---|
196 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_sand_mtc = & |
---|
197 | & (/ 1, 3, 3, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2 /) |
---|
198 | |
---|
199 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_loan_mtc = & |
---|
200 | & (/ 2, 2, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3 /) |
---|
201 | |
---|
202 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_clay_mtc = & |
---|
203 | & (/ 3, 1, 1, 1, 1, 1 ,1 ,1 ,1 ,1 ,1 ,1, 1 /) |
---|
204 | |
---|
205 | !---------------- |
---|
206 | ! Photosynthesis |
---|
207 | !---------------- |
---|
208 | !- |
---|
209 | ! 1 .CO2 |
---|
210 | !- |
---|
211 | ! flag for C4 vegetation types |
---|
212 | LOGICAL,PARAMETER, DIMENSION(nvmc) :: is_c4_mtc = & |
---|
213 | & (/.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE., & |
---|
214 | & .FALSE.,.FALSE.,.FALSE.,.FALSE.,.TRUE.,.FALSE.,.TRUE. /) |
---|
215 | !- |
---|
216 | ! Slope of the gs/A relation (Ball & al.) |
---|
217 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: gsslope_mtc = & |
---|
218 | & (/0., 9., 9., 9., 9., 9., 9., 9., 9., 9., 3., 9., 3./) |
---|
219 | !- |
---|
220 | ! intercept of the gs/A relation (Ball & al.) |
---|
221 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: gsoffset_mtc = & |
---|
222 | & (/ 0.0, 0.01, 0.01, 0.01, 0.01, 0.01, & |
---|
223 | & 0.01, 0.01, 0.01, 0.01, 0.03, 0.01, 0.03 /) |
---|
224 | !- |
---|
225 | ! values used for vcmax when STOMATE is not activated |
---|
226 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: vcmax_fix_mtc = & |
---|
227 | & (/ 0., 40., 50., 30., 35., 40., & |
---|
228 | & 30., 40., 35., 60., 60., 70., 70. /) |
---|
229 | !- |
---|
230 | ! values used for vjmax when STOMATE is not activated |
---|
231 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: vjmax_fix_mtc = & |
---|
232 | & (/ 0., 80., 100., 60., 70., 80., & |
---|
233 | & 60., 80., 70., 120., 120., 140., 140. /) |
---|
234 | !- |
---|
235 | ! values used for photosynthesis tmin when STOMATE is not activated |
---|
236 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: co2_tmin_fix_mtc = & |
---|
237 | & (/ 0., 2., 2., -4., -3., -2., & |
---|
238 | & -4., -4., -4., -5., 6., -5., 6. /) |
---|
239 | !- |
---|
240 | ! values used for photosynthesis topt when STOMATE is not activated |
---|
241 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: co2_topt_fix_mtc = & |
---|
242 | & (/ 0., 27.5, 27.5, 17.5, 25., 20., & |
---|
243 | & 17.5, 17.5, 17.5, 20., 32.5, 20., 32.5 /) |
---|
244 | !- |
---|
245 | ! values used for photosynthesis tmax when STOMATE is not activated |
---|
246 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: co2_tmax_fix_mtc = & |
---|
247 | & (/ 0., 55., 55., 38., 48., 38., & |
---|
248 | & 38., 38., 38., 45., 55., 45., 55. /) |
---|
249 | !- |
---|
250 | ! 2 .Stomate |
---|
251 | !- |
---|
252 | ! extinction coefficient of the Monsi&Seaki relationship (1953) |
---|
253 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: ext_coeff_mtc = & |
---|
254 | & (/.5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5/) |
---|
255 | !- |
---|
256 | ! Maximum rate of carboxylation |
---|
257 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_opt_mtc = & |
---|
258 | & (/ undef, 65., 65., 35., 45., 55., 35., & |
---|
259 | & 45., 35., 70., 70., 70., 70. /) |
---|
260 | !- |
---|
261 | ! Maximum rate of RUbp regeneration |
---|
262 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vjmax_opt_mtc = & |
---|
263 | & (/ undef, 130., 130., 70., 80., 110., 70., & |
---|
264 | & 90., 70., 160., 160., 200., 200. /) |
---|
265 | !-! |
---|
266 | ! minimum photosynthesis temperature, |
---|
267 | ! constant a of ax^2+bx+c (deg C), tabulated |
---|
268 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_a_mtc = & |
---|
269 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
270 | & 0., 0., 0.0025, 0., 0., 0. /) |
---|
271 | !- |
---|
272 | ! minimum photosynthesis temperature, |
---|
273 | ! constant b of ax^2+bx+c (deg C), tabulated |
---|
274 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_b_mtc = & |
---|
275 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
276 | & 0., 0., 0.1, 0., 0., 0. /) |
---|
277 | !- |
---|
278 | ! minimum photosynthesis temperature, |
---|
279 | ! constant c of ax^2+bx+c (deg C), tabulated |
---|
280 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_c_mtc = & |
---|
281 | & (/ undef, 2., 2., -4., -3., -2., -4., & |
---|
282 | & -4., -4., -3.25, 13., -5., 13. /) |
---|
283 | !-! |
---|
284 | ! optimum photosynthesis temperature, |
---|
285 | ! constant a of ax^2+bx+c (deg C), tabulated |
---|
286 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_opt_a_mtc = & |
---|
287 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
288 | & 0., 0., 0.0025, 0., 0., 0. /) |
---|
289 | !- |
---|
290 | ! optimum photosynthesis temperature, |
---|
291 | ! constant b of ax^2+bx+c (deg C), tabulated |
---|
292 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_opt_b_mtc = & |
---|
293 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
294 | & 0., 0., 0.25, 0., 0., 0. /) |
---|
295 | ! optimum photosynthesis temperature, |
---|
296 | ! constant c of ax^2+bx+c (deg C), tabulated |
---|
297 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_opt_c_mtc = & |
---|
298 | & (/ undef, 37., 37., 25., 32., 26., 25., & |
---|
299 | & 25., 25., 27.25, 36., 30., 36. /) |
---|
300 | !-! |
---|
301 | ! maximum photosynthesis temperature, |
---|
302 | ! constant a of ax^2+bx+c (deg C), tabulated |
---|
303 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_a_mtc = & |
---|
304 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
305 | & 0., 0., 0.00375, 0., 0., 0. /) |
---|
306 | !- |
---|
307 | ! maximum photosynthesis temperature, |
---|
308 | ! constant b of ax^2+bx+c (deg C), tabulated |
---|
309 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_b_mtc = & |
---|
310 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
311 | & 0., 0., 0.35, 0., 0., 0. /) |
---|
312 | !- |
---|
313 | ! maximum photosynthesis temperature, |
---|
314 | ! constant c of ax^2+bx+c (deg C), tabulated |
---|
315 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_c_mtc = & |
---|
316 | & (/ undef, 55., 55., 38., 48., 38., 38., & |
---|
317 | & 38., 38., 41.125, 55., 45., 55. /) |
---|
318 | |
---|
319 | |
---|
320 | !---------------------- |
---|
321 | ! Respiration - stomate |
---|
322 | !---------------------- |
---|
323 | ! |
---|
324 | !-! slope of maintenance respiration coefficient (1/K), |
---|
325 | ! constant c of aT^2+bT+c , tabulated |
---|
326 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_c_mtc = & |
---|
327 | & (/ undef, .12, .12, .16, .16, .16, .16, & |
---|
328 | & .16, .16, .16, .12, .16, .12 /) |
---|
329 | !- |
---|
330 | ! slope of maintenance respiration coefficient (1/K), |
---|
331 | ! constant b of aT^2+bT+c , tabulated |
---|
332 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_b_mtc = & |
---|
333 | & (/ undef, .0, .0, .0, .0, .0, .0, & |
---|
334 | & .0, .0, -.00133, .0, -.00133, .0 /) |
---|
335 | !- |
---|
336 | ! slope of maintenance respiration coefficient (1/K), |
---|
337 | ! constant a of aT^2+bT+c , tabulated |
---|
338 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_a_mtc = & |
---|
339 | & (/ undef, .0, .0, .0, .0, .0, .0, & |
---|
340 | & .0, .0, .0, .0, .0, .0 /) |
---|
341 | !-! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
342 | ! for leaves, tabulated |
---|
343 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_leaf_mtc = & |
---|
344 | & (/ undef, 2.35E-3, 2.62E-3, 1.01E-3, 2.35E-3, 2.62E-3, 1.01E-3, & |
---|
345 | & 2.62E-3, 2.05E-3, 2.62E-3, 2.62E-3, 2.62E-3, 2.62E-3 /) |
---|
346 | !- |
---|
347 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
348 | ! for sapwood above, tabulated |
---|
349 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapabove_mtc = & |
---|
350 | & (/ undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & |
---|
351 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) |
---|
352 | !- |
---|
353 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
354 | ! for sapwood below, tabulated |
---|
355 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapbelow_mtc = & |
---|
356 | & (/ undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & |
---|
357 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) |
---|
358 | !- |
---|
359 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
360 | ! for heartwood above, tabulated |
---|
361 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartabove_mtc = & |
---|
362 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
363 | & 0., 0., 0., 0., 0., 0. /) |
---|
364 | !- |
---|
365 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
366 | ! for heartwood below, tabulated |
---|
367 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartbelow_mtc = & |
---|
368 | & (/ undef, 0., 0., 0., 0., 0., 0., & |
---|
369 | & 0., 0., 0., 0., 0., 0. /) |
---|
370 | !- |
---|
371 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
372 | ! for roots, tabulated |
---|
373 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_root_mtc = & |
---|
374 | & (/ undef, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, & |
---|
375 | & 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3 /) |
---|
376 | !- |
---|
377 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
378 | ! for fruits, tabulated |
---|
379 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_fruit_mtc = & |
---|
380 | & (/ undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & |
---|
381 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) |
---|
382 | !- |
---|
383 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
384 | ! for carbohydrate reserve, tabulated |
---|
385 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_carbres_mtc = & |
---|
386 | & (/ undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & |
---|
387 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) |
---|
388 | |
---|
389 | |
---|
390 | !---------------- |
---|
391 | ! Fire - stomate |
---|
392 | !--------------- |
---|
393 | ! |
---|
394 | ! flamability: critical fraction of water holding capacity |
---|
395 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: flam_mtc = & |
---|
396 | & (/ undef, .15, .25, .25, .25, .25, .25, & |
---|
397 | & .25, .25, .25, .25, .35, .35 /) |
---|
398 | !- |
---|
399 | ! fire resistance |
---|
400 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: resist_mtc = & |
---|
401 | & (/ undef, .95, .90, .12, .50, .12, .12, & |
---|
402 | & .12, .12, .0, .0, .0, .0 /) |
---|
403 | |
---|
404 | |
---|
405 | !---------------- |
---|
406 | ! Flux - LUC |
---|
407 | !--------------- |
---|
408 | ! |
---|
409 | ! Coeff of biomass export for the year |
---|
410 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_1_mtc = & |
---|
411 | & (/ undef, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597, & |
---|
412 | & 0.597, 0.597, 0.597, 0.597, 0.597, 0.597 /) |
---|
413 | !- |
---|
414 | ! Coeff of biomass export for the decade |
---|
415 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_10_mtc = & |
---|
416 | & (/ undef, 0.403, 0.403, 0.299, 0.299, 0.299, 0.299, & |
---|
417 | & 0.299, 0.299, 0.299, 0.403, 0.299, 0.403 /) |
---|
418 | !- |
---|
419 | ! Coeff of biomass export for the century |
---|
420 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_100_mtc = & |
---|
421 | & (/ undef, 0., 0., 0.104, 0.104, 0.104, 0.104, & |
---|
422 | & 0.104, 0.104, 0.104, 0., 0.104, 0. /) |
---|
423 | |
---|
424 | |
---|
425 | !----------- |
---|
426 | ! Phenology |
---|
427 | !----------- |
---|
428 | !- |
---|
429 | ! 1 .Stomate |
---|
430 | !- |
---|
431 | ! maximum LAI, PFT-specific |
---|
432 | REAL(r_std), PARAMETER, DIMENSION (nvmc) :: lai_max_mtc = & |
---|
433 | & (/ undef, 7., 7., 5., 5., 5., 4.5, & |
---|
434 | & 4.5, 3.0, 2.5, 2.5, 5., 5. /) |
---|
435 | !- |
---|
436 | ! which phenology model is used? (tabulated) |
---|
437 | CHARACTER(len=6), PARAMETER, DIMENSION(nvmc) :: pheno_model_mtc = & |
---|
438 | & (/ 'none ', 'none ', 'moi ', 'none ', 'none ', & |
---|
439 | & 'ncdgdd', 'none ', 'ncdgdd', 'ngd ', 'moigdd', & |
---|
440 | & 'moigdd', 'moigdd', 'moigdd' /) |
---|
441 | !- |
---|
442 | ! type of phenology |
---|
443 | ! 0=bared ground 1=evergreen, 2=summergreen, 3=raingreen, 4=perennial |
---|
444 | ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols nu comme "evergreen" |
---|
445 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pheno_type_mtc = & |
---|
446 | & (/ 0, 1, 3, 1, 1, 2, 1, & |
---|
447 | & 2, 2, 4, 4, 2, 3 /) |
---|
448 | !- |
---|
449 | ! 2. Leaf Onset |
---|
450 | !- |
---|
451 | !-! critical gdd, tabulated (C), constant c of aT^2+bT+c |
---|
452 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_c_mtc = & |
---|
453 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
454 | & undef, undef, 270., 400., 125., 400. /) |
---|
455 | !- |
---|
456 | ! critical gdd, tabulated (C), constant b of aT^2+bT+c |
---|
457 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_b_mtc = & |
---|
458 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
459 | & undef, undef, 6.25, 0., 0., 0. /) |
---|
460 | !- |
---|
461 | ! critical gdd, tabulated (C), constant a of aT^2+bT+c |
---|
462 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_a_mtc = & |
---|
463 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
464 | & undef, undef, 0.03125, 0., 0., 0. /) |
---|
465 | !- |
---|
466 | ! critical ngd, tabulated. Threshold -5 degrees |
---|
467 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ngd_crit_mtc = & |
---|
468 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
469 | & undef, 17., undef, undef, undef, undef /) |
---|
470 | !- |
---|
471 | ! critical temperature for the ncd vs. gdd function in phenology |
---|
472 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ncdgdd_temp_mtc = & |
---|
473 | & (/ undef, undef, undef, undef, undef, 5., undef, & |
---|
474 | & 0., undef, undef, undef, undef, undef /) |
---|
475 | !- |
---|
476 | ! critical humidity (relative to min/max) for phenology |
---|
477 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_frac_mtc = & |
---|
478 | & (/ undef, undef, .5, undef, undef, undef, undef, & |
---|
479 | & undef, undef, .5, .5, .5, .5 /) |
---|
480 | !- |
---|
481 | ! minimum duration of dormance (d) for phenology |
---|
482 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lowgpp_time_mtc = & |
---|
483 | & (/ undef, undef, 30., undef, undef, 30., undef, & |
---|
484 | & 30., 30., 30., 30., 30., 30. /) |
---|
485 | !- |
---|
486 | ! minimum time elapsed since moisture minimum (d) |
---|
487 | REAL(r_std),PARAMETER , DIMENSION(nvmc) :: hum_min_time_mtc = & |
---|
488 | & (/ undef, undef, 50., undef, undef, undef, undef, & |
---|
489 | & undef, undef, 35., 35., 75., 75. /) |
---|
490 | !- |
---|
491 | ! sapwood -> heartwood conversion time (d) |
---|
492 | REAL(r_std) ,PARAMETER , DIMENSION(nvmc) :: tau_sap_mtc = & |
---|
493 | & (/ undef, 730., 730., 730., 730., 730., 730., & |
---|
494 | & 730., 730., undef, undef, undef, undef /) |
---|
495 | !- |
---|
496 | ! fruit lifetime (d) |
---|
497 | REAL(r_std) ,PARAMETER , DIMENSION(nvmc) :: tau_fruit_mtc = & |
---|
498 | & (/ undef, 90., 90., 90., 90., 90., 90., & |
---|
499 | & 90., 90., undef, undef, undef, undef /) |
---|
500 | !- |
---|
501 | ! fraction of primary leaf and root allocation put into reserve |
---|
502 | REAL(r_std) ,PARAMETER , DIMENSION(nvmc) :: ecureuil_mtc = & |
---|
503 | & (/ undef, .0, 1., .0, .0, 1., .0, & |
---|
504 | & 1., 1., 1., 1., 1., 1. /) |
---|
505 | !- |
---|
506 | ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
507 | REAL(r_std) ,PARAMETER , DIMENSION(nvmc) :: alloc_min_mtc = & |
---|
508 | & (/ undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, & |
---|
509 | & 0.2, 0.2, undef, undef, undef, undef /) |
---|
510 | !- |
---|
511 | REAL(r_std) ,PARAMETER , DIMENSION(nvmc) :: alloc_max_mtc = & |
---|
512 | & (/ undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, & |
---|
513 | & 0.8, 0.8, undef, undef, undef, undef /) |
---|
514 | !- |
---|
515 | REAL(r_std) ,PARAMETER , DIMENSION(nvmc) :: demi_alloc_mtc = & |
---|
516 | & (/ undef, 5., 5., 5., 5., 5., 5., & |
---|
517 | & 5., 5., undef, undef, undef, undef /) |
---|
518 | |
---|
519 | !>> DS new for merge in the trunk |
---|
520 | ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla |
---|
521 | REAL(r_std) ,PARAMETER , DIMENSION(nvmc) :: leaflife_mtc = & |
---|
522 | & (/ undef, .5, 2., .33, 1., 2., .33, & |
---|
523 | & 2., 2., 2., 2., 2., 2. /) |
---|
524 | |
---|
525 | !- |
---|
526 | ! 3. Senescence |
---|
527 | !- |
---|
528 | ! length of death of leaves, tabulated (d) |
---|
529 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaffall_mtc = & |
---|
530 | & (/ undef, undef, 10., undef, undef, 10., undef, & |
---|
531 | & 10., 10., 10., 10., 10., 10. /) |
---|
532 | !- |
---|
533 | ! critical leaf age, tabulated (d) |
---|
534 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: leafagecrit_mtc = & |
---|
535 | & (/ undef, 730., 180., 910., 730., 180., 910., & |
---|
536 | & 180., 180., 120., 120., 90., 90. /) |
---|
537 | !- |
---|
538 | ! type of senescence, tabulated |
---|
539 | CHARACTER(len=6),PARAMETER, DIMENSION(nvmc) :: senescence_type_mtc = & |
---|
540 | & (/ 'none ', 'none ', 'dry ', 'none ', 'none ', & |
---|
541 | & 'cold ', 'none ', 'cold ', 'cold ', 'mixed ', & |
---|
542 | & 'mixed ', 'mixed ', 'mixed ' /) |
---|
543 | !- |
---|
544 | ! critical relative moisture availability for senescence |
---|
545 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: senescence_hum_mtc = & |
---|
546 | & (/ undef, undef, .3, undef, undef, undef, undef, & |
---|
547 | & undef, undef, .2, .2, .3, .2 /) |
---|
548 | !- |
---|
549 | ! relative moisture availability above which |
---|
550 | ! there is no humidity-related senescence |
---|
551 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: nosenescence_hum_mtc = & |
---|
552 | & (/ undef, undef, .8, undef, undef, undef, undef, & |
---|
553 | & undef, undef, .3, .3, .3, .3 /) |
---|
554 | !- |
---|
555 | ! maximum turnover time for grasse |
---|
556 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: max_turnover_time_mtc = & |
---|
557 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
558 | & undef, undef, 80., 80., 80., 80. /) |
---|
559 | !- |
---|
560 | ! minimum turnover time for grasse |
---|
561 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: min_turnover_time_mtc = & |
---|
562 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
563 | & undef, undef, 10., 10., 10., 10. /) |
---|
564 | !- |
---|
565 | ! minimum leaf age to allow senescence g |
---|
566 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: min_leaf_age_for_senescence_mtc = & |
---|
567 | & (/ undef, undef, 90., undef, undef, 90., undef, & |
---|
568 | & 60., 60., 30., 30., 30., 30. /) |
---|
569 | !-!- |
---|
570 | ! critical temperature for senescence (C), |
---|
571 | ! constant c of aT^2+bT+c , tabulated |
---|
572 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: senescence_temp_c_mtc = & |
---|
573 | & (/ undef, undef, undef, undef, undef, 12., undef, & |
---|
574 | & 7., 2., -1.375, 5., 5., 10. /) |
---|
575 | !- |
---|
576 | ! critical temperature for senescence (C), |
---|
577 | ! constant b of aT^2+bT+c , tabulated |
---|
578 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_b_mtc = & |
---|
579 | & (/ undef, undef, undef, undef, undef, 0., undef, & |
---|
580 | & 0., 0., .1, 0., 0., 0. /) |
---|
581 | !- |
---|
582 | ! critical temperature for senescence (C), |
---|
583 | ! constant a of aT^2+bT+c , tabulated |
---|
584 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: senescence_temp_a_mtc = & |
---|
585 | & (/ undef, undef, undef, undef, undef, 0., undef, & |
---|
586 | & 0., 0., .00375, 0., 0., 0. /) |
---|
587 | |
---|
588 | |
---|
589 | !----------- |
---|
590 | ! DGVM |
---|
591 | !----------- |
---|
592 | ! |
---|
593 | ! residence time (y) of trees |
---|
594 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: residence_time_mtc = & |
---|
595 | & (/ undef, 30.0, 30.0, 40.0, 40.0, 40.0, 80.0, & |
---|
596 | & 80.0, 80.0, 0.0, 0.0, 0.0, 0.0 /) |
---|
597 | !- |
---|
598 | ! critical tmin, tabulated (C) |
---|
599 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_crit_mtc = & |
---|
600 | & (/ undef, 0.0, 0.0, -45.0, -10.0, -45.0, -60.0, & |
---|
601 | & -60.0, undef, undef, undef, undef, undef /) |
---|
602 | !- |
---|
603 | ! critical tcm, tabulated (C) |
---|
604 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tcm_crit_mtc = & |
---|
605 | & (/ undef, undef, undef, 5.0, 15.5, 15.5, -2.0, & |
---|
606 | & 5.0, -2.0, undef, undef, undef, undef /) |
---|
607 | |
---|
608 | |
---|
609 | !------------------------ |
---|
610 | END MODULE constantes_mtc |
---|