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 parameters 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) : |
---|
20 | !! - Kuppel, S. (2012): Doctoral Thesis, Assimilation de mesures de flux turbulents d'eau et de carbone dans un modÚle de la biosphÚre |
---|
21 | !! continentale |
---|
22 | !! - McDowell, N., Barnard, H., Bond, B.J., Hinckley, T., Hubbard, R.M., Ishii, H., Köstner, B., |
---|
23 | !! Magnani, F. Marshall, J.D., Meinzer, F.C., Phillips, N., Ryan, M.G., Whitehead D. 2002. The |
---|
24 | !! relationship between tree height and leaf area: sapwood area ratio. Oecologia, 132:12â20 |
---|
25 | !! - Kuppel, S., Peylin, P., Chevallier, F., Bacour, C., Maignan, F., and Richardson, A. D. (2012). Constraining a global ecosystem |
---|
26 | !! model with multi-site eddy-covariance data, Biogeosciences, 9, 3757-3776, DOI 10.5194/bg-9-3757-2012. |
---|
27 | !! - Wohlfahrt, G., M. Bahn, E. Haubner, I. Horak, W. Michaeler, K.Rottmar, U. Tappeiner, and A. Cemusca, 1999: Inter-specific |
---|
28 | !! variation of the biochemical limitation to photosynthesis and related leaf traits of 30 species from mountain grassland |
---|
29 | !! ecosystems under different land use. Plant Cell Environ., 22, 12811296. |
---|
30 | !! - Malhi, Y., Doughty, C., and Galbraith, D. (2011). The allocation of ecosystem net primary productivity in tropical forests, |
---|
31 | !! Philosophical Transactions of the Royal Society B-Biological Sciences, 366, 3225-3245, DOI 10.1098/rstb.2011.0062. |
---|
32 | !! - Earles, J. M., Yeh, S., and Skog, K. E. (2012). Timing of carbon emissions from global forest clearance, Nature Climate Change, 2, |
---|
33 | !! 682-685, Doi 10.1038/Nclimate1535. |
---|
34 | !! - Piao, S. L., Luyssaert, S., Ciais, P., Janssens, I. A., Chen, A. P., Cao, C., Fang, J. Y., Friedlingstein, P., Luo, Y. Q., and |
---|
35 | !! Wang, S. P. (2010). Forest annual carbon cost: A global-scale analysis of autotrophic respiration, Ecology, 91, 652-661, |
---|
36 | !! Doi 10.1890/08-2176.1. |
---|
37 | !! - Verbeeck, H., Peylin, P., Bacour, C., Bonal, D., Steppe, K., and Ciais, P. (2011). Seasonal patterns of co2 fluxes in amazon |
---|
38 | !! forests: Fusion of eddy covariance data and the orchidee model, Journal of Geophysical Research-Biogeosciences, 116, |
---|
39 | !! Artn G02018, Doi 10.1029/2010jg001544. |
---|
40 | !! |
---|
41 | !! SVN : |
---|
42 | !! $HeadURL: $ |
---|
43 | !! $Date: 2015-02-22 16:18:16 +0100 (Sun, 22 Feb 2015) $ |
---|
44 | !! $Revision: 2555 $ |
---|
45 | !! \n |
---|
46 | !_ ================================================================================================================================ |
---|
47 | |
---|
48 | MODULE constantes_mtc |
---|
49 | |
---|
50 | USE defprec |
---|
51 | USE constantes |
---|
52 | |
---|
53 | IMPLICIT NONE |
---|
54 | |
---|
55 | ! |
---|
56 | ! METACLASSES CHARACTERISTICS |
---|
57 | ! |
---|
58 | |
---|
59 | INTEGER(i_std), PARAMETER :: nvmc = 13 !! Number of MTCS fixed in the code (unitless) |
---|
60 | |
---|
61 | CHARACTER(len=34), PARAMETER, DIMENSION(nvmc) :: MTC_name = & !! description of the MTC (unitless) |
---|
62 | & (/ 'bare ground ', & ! 1 |
---|
63 | & 'tropical broad-leaved evergreen ', & ! 2 |
---|
64 | & 'tropical broad-leaved raingreen ', & ! 3 |
---|
65 | & 'temperate needleleaf evergreen ', & ! 4 |
---|
66 | & 'temperate broad-leaved evergreen ', & ! 5 |
---|
67 | & 'temperate broad-leaved summergreen', & ! 6 |
---|
68 | & 'boreal needleleaf evergreen ', & ! 7 |
---|
69 | & 'boreal broad-leaved summergreen', & ! 8 |
---|
70 | & 'boreal needleleaf summergreen', & ! 9 |
---|
71 | & ' C3 grass ', & ! 10 |
---|
72 | & ' C4 grass ', & ! 11 |
---|
73 | & ' C3 agriculture', & ! 12 |
---|
74 | & ' C4 agriculture' /) ! 13 |
---|
75 | |
---|
76 | |
---|
77 | ! |
---|
78 | ! VEGETATION STRUCTURE |
---|
79 | ! |
---|
80 | INTEGER(i_std),PARAMETER, DIMENSION(nvmc) :: leaf_tab_mtc = & !! leaf type (1-4, unitless) |
---|
81 | & (/ 4, 1, 1, 2, 1, 1, 2, & !! 1=broad leaved tree, 2=needle leaved tree |
---|
82 | & 1, 2, 3, 3, 3, 3 /) !! 3=grass 4=bare ground |
---|
83 | |
---|
84 | CHARACTER(len=6), PARAMETER, DIMENSION(nvmc) :: pheno_model_mtc = & !! which phenology model is used? (tabulated) |
---|
85 | & (/ 'none ', 'none ', 'moi ', 'none ', 'none ', & |
---|
86 | & 'ncdgdd', 'none ', 'ncdgdd', 'ngd ', 'moigdd', & |
---|
87 | & 'moigdd', 'moigdd', 'moigdd' /) |
---|
88 | |
---|
89 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_tropical_mtc = & !! Is PFT tropical ? (true/false) |
---|
90 | & (/ .FALSE., .TRUE., .TRUE., .FALSE., .FALSE., .FALSE., .FALSE., & |
---|
91 | & .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /) |
---|
92 | |
---|
93 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_temperate_mtc = & !! Is PFT temperate ? (true/false) |
---|
94 | & (/ .FALSE., .FALSE., .FALSE., .TRUE., .TRUE., .TRUE., .FALSE., & |
---|
95 | & .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /) |
---|
96 | |
---|
97 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_boreal_mtc = & !! Is PFT boreal ? (true/false) |
---|
98 | & (/ .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .TRUE., & |
---|
99 | & .TRUE., .TRUE., .FALSE., .FALSE., .FALSE., .FALSE. /) |
---|
100 | |
---|
101 | |
---|
102 | CHARACTER(LEN=5), PARAMETER, DIMENSION(nvmc) :: type_of_lai_mtc = & !! Type of behaviour of the LAI evolution algorithm |
---|
103 | & (/ 'inter', 'inter', 'inter', 'inter', 'inter', & !! for each vegetation type. (unitless) |
---|
104 | & 'inter', 'inter', 'inter', 'inter', 'inter', & !! Value of type_of_lai : mean or interp |
---|
105 | & 'inter', 'inter', 'inter' /) |
---|
106 | |
---|
107 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: natural_mtc = & !! natural? (true/false) |
---|
108 | & (/ .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., & |
---|
109 | & .TRUE., .TRUE., .TRUE., .TRUE., .FALSE., .FALSE. /) |
---|
110 | |
---|
111 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: veget_ori_fixed_mtc = & !! Value for veget_ori for tests in |
---|
112 | & (/ 0.2, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, & !! 0-dim simulations (0-1, unitless) |
---|
113 | & 0.0, 0.0, 0.8, 0.0, 0.0, 0.0 /) |
---|
114 | |
---|
115 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimax_mtc = & !! laimax for maximum |
---|
116 | & (/ undef, 8.0, 8.0, 4.0, 4.5, 4.5, 4.0, & !! See also type of lai interpolation |
---|
117 | & 4.5, 4.0, 2.0, 2.0, 2.0, 2.0 /) !! @tex $(m^2.m^{-2})$ @endtex |
---|
118 | |
---|
119 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimin_mtc = & !! laimin for minimum lai |
---|
120 | & (/ undef, 8.0, 0.0, 4.0, 4.5, 0.0, 4.0, & !! See also type of lai interpolation (m^2.m^{-2}) |
---|
121 | & 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /) !! @tex $(m^2.m^{-2})$ @endtex |
---|
122 | |
---|
123 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_presc_mtc = & !! prescribed height of vegetation (m) ONLY used without |
---|
124 | & (/ 0.0, 30.0, 30.0, 20.0, 20.0, 20.0, 15.0, & !! stomate. Value for height_presc : one for each vegetation |
---|
125 | & 15.0, 15.0, 0.5, 0.6, 1.0, 1.0 /) !! type |
---|
126 | |
---|
127 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rveg_mtc = & !! Potentiometer to set vegetation resistance (unitless) |
---|
128 | & (/ 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, & !! Nathalie on March 28th, 2006 - from Fred Hourdin, |
---|
129 | & 1.0, 1.0, 1.0, 1.0, 1.0, 1.0 /) |
---|
130 | |
---|
131 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: sla_mtc = & !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex |
---|
132 | & (/ 1.5E-2, 1.53E-2, 2.6E-2, 9.26E-3, 2E-2, 2.6E-2, 9.26E-3, & |
---|
133 | & 2.6E-2, 1.9E-2, 2.6E-2, 2.6E-2, 2.6E-2, 2.6E-2 /) |
---|
134 | |
---|
135 | |
---|
136 | ! |
---|
137 | ! EVAPOTRANSPIRATION (sechiba) |
---|
138 | ! |
---|
139 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rstruct_const_mtc = & !! Structural resistance. |
---|
140 | & (/ 0.0, 25.0, 25.0, 25.0, 25.0, 25.0, 25.0, & !! @tex $(s.m^{-1})$ @endtex |
---|
141 | & 25.0, 25.0, 2.5, 2.0, 2.0, 2.0 /) |
---|
142 | |
---|
143 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kzero_mtc = & !! A vegetation dependent constant used in the |
---|
144 | & (/ 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. |
---|
145 | & 25.E-5, 25.E-5, 30.E-5, 30.E-5, 30.E-5, 30.E-5 /) !! @tex $(kg.m^2.s^{-1})$ @endtex |
---|
146 | |
---|
147 | |
---|
148 | ! |
---|
149 | ! WATER (sechiba) |
---|
150 | ! |
---|
151 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wmax_veg_mtc = & !! Volumetric available soil water capacity in each PFT |
---|
152 | & (/ 150.0, 150.0, 150.0, 150.0, 150.0, 150.0, 150.0, & !! @tex $(kg.m^{-3} of soil)$ @endtex |
---|
153 | & 150.0, 150.0, 150.0, 150.0, 150.0, 150.0 /) |
---|
154 | |
---|
155 | |
---|
156 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_mtc = & !! Root profile description for the different |
---|
157 | & (/ 5.0, 0.4, 0.4, 1.0, 0.8, 0.8, 1.0, & !! vegetations types. @tex $(m^{-1})$ @endtex |
---|
158 | & 1.0, 0.8, 4.0, 1.0, 4.0, 1.0 /) !! These are the factor in the exponential which gets |
---|
159 | !! the root density as a function of depth |
---|
160 | !! Values for zmaxh = 4.0 |
---|
161 | |
---|
162 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_cwrr = & !! Root profile description for the different |
---|
163 | & (/ 5.0, 0.8, 0.8, 1.0, 0.8, 0.8, 1.0, & !! vegetations types. @tex $(m^{-1})$ @endtex |
---|
164 | & 1.0, 0.8, 4.0, 4.0, 4.0, 4.0 /) !! These are the factor in the exponential which gets |
---|
165 | !! the root density as a function of depth |
---|
166 | !! Values for zmaxh = 2.0 |
---|
167 | !! (used by using 11 layers hydrology) |
---|
168 | |
---|
169 | |
---|
170 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: throughfall_by_mtc = & !! Fraction of rain intercepted by the canopy |
---|
171 | & (/ 30.0, 30.0, 30.0, 30.0, 30.0, 30.0, 30.0, & !! (0-100, unitless) |
---|
172 | & 30.0, 30.0, 30.0, 30.0, 30.0, 30.0 /) |
---|
173 | |
---|
174 | |
---|
175 | ! |
---|
176 | ! ALBEDO (sechiba) |
---|
177 | ! |
---|
178 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_mtc = & !! Minimum snow albedo value for each vegetation type |
---|
179 | & (/ 0.35, 0.0, 0.0, 0.14, 0.14, 0.14, 0.14, & !! after aging (dirty old snow) (unitless) |
---|
180 | & 0.14, 0.14, 0.18, 0.18, 0.18, 0.18 /) !! Source : Values are from the Thesis of S. Chalita (1992) |
---|
181 | |
---|
182 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_mtc = & !! Decay rate of snow albedo value for each vegetation type |
---|
183 | & (/ 0.45, 0.0, 0.0, 0.06, 0.06, 0.11, 0.06, & !! as it will be used in condveg_snow (unitless) |
---|
184 | & 0.11, 0.11, 0.52, 0.52, 0.52, 0.52 /) !! Source : Values are from the Thesis of S. Chalita (1992) |
---|
185 | ! |
---|
186 | ! albedo values for albedo type 'standard' |
---|
187 | ! |
---|
188 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_vis_mtc = & !! leaf albedo of vegetation type, visible albedo |
---|
189 | & (/ 0.00, 0.04, 0.06, 0.06, 0.06, 0.06, 0.06, & !! (unitless) |
---|
190 | & 0.06, 0.06, 0.10, 0.10, 0.10, 0.10 /) |
---|
191 | |
---|
192 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_nir_mtc = & !! leaf albedo of vegetation type, near infrared albedo |
---|
193 | & (/ 0.00, 0.10, 0.22, 0.22, 0.22, 0.22, 0.22, & !! (unitless) |
---|
194 | & 0.22, 0.22, 0.30, 0.30, 0.30, 0.30 /) |
---|
195 | |
---|
196 | ! |
---|
197 | ! albedo values for albedo type 'pinty' |
---|
198 | ! these next values were determined by fitting to global MODIS data and using the inversion scheme of |
---|
199 | ! Pinty et al (see Pinty B,Andredakis I, Clerici M, et al. (2011) ! 'Exploiting the MODIS albedos |
---|
200 | ! with the Two-stream Inversion Package (JRC-TIP): 1. Effective leaf area index, |
---|
201 | ! vegetation, and soil properties'. Journal of Geophysical Research. |
---|
202 | ! |
---|
203 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_ssa_vis_mtc = & !! leaf single scattering albedo, visible light (unitless) |
---|
204 | (/ 0.17192, 0.12560, 0.16230, 0.13838, 0.13202, 0.14720, & |
---|
205 | 0.14680, 0.14415, 0.15485, 0.17544, 0.17384, 0.17302, 0.17116 /) |
---|
206 | |
---|
207 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_ssa_nir_mtc = & !! leaf single scattering albedo, near infrared (unitless) |
---|
208 | (/ 0.70253, 0.68189, 0.69684, 0.68778, 0.68356, 0.69533, & |
---|
209 | 0.69520, 0.69195, 0.69180, 0.71236, 0.71904, 0.71220, 0.71190 /) |
---|
210 | |
---|
211 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_psd_vis_mtc = & !! leaf preferred scattering direction, visible light (unitless) |
---|
212 | (/ 1.00170, 0.96776, 0.99250, 0.97170, 0.97119, 0.98077, & |
---|
213 | 0.97672, 0.97810, 0.98605, 1.00490, 1.00360, 1.00320, 1.00130 /) |
---|
214 | |
---|
215 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_psd_nir_mtc = & !! leaf preferred scattering direction, NIR light (unitless) |
---|
216 | (/ 2.00520, 1.95120, 1.98990, 1.97020, 1.95900, 1.98190, & |
---|
217 | 1.98890, 1.97400, 1.97780, 2.02430, 2.03350, 2.02070, 2.02150 /) |
---|
218 | |
---|
219 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bgd_reflectance_vis_mtc = & !! background reflectance, visible light (unitless) |
---|
220 | (/ 0.13796, 0.08311, 0.08784, 0.04339, 0.07228, 0.06460, & |
---|
221 | 0.03170, 0.06029, 0.06403, 0.12459, 0.14366, 0.11012, 0.12245 /) |
---|
222 | |
---|
223 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bgd_reflectance_nir_mtc = & !! background reflectance, NIR light (unitless) |
---|
224 | (/ 0.26520, 0.14605, 0.14937, 0.06608, 0.12334, 0.10534, & |
---|
225 | 0.04443, 0.09455, 0.09770, 0.23034, 0.29221, 0.20508, 0.23339 /) |
---|
226 | |
---|
227 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tune_coupled_mtc = & !! tune factors for LAI coupled LAI, (unitless) |
---|
228 | (/ un, un, un, un, un, un, un, & |
---|
229 | un, un, un, un, un, un /) |
---|
230 | |
---|
231 | |
---|
232 | |
---|
233 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_to_shoot_clumping_mtc = & !! The clumping factor for leaves to shoots in the |
---|
234 | (/ un, un, un, un, un, un, un, & !! effective LAI calculation...notice this should be |
---|
235 | un, un, un, un, un, un /) !! equal to unity for grasslands/croplands |
---|
236 | |
---|
237 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_correction_factor_mtc = & !! see the note about this variable in pft_parameters |
---|
238 | (/ un, un, un, un, un, un, un, & |
---|
239 | un, un, un, un, un, un /) |
---|
240 | |
---|
241 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_level_sep_mtc = & !! The minimum level thickness for photosynthesis [m] |
---|
242 | (/ un, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, & !! This number is arbitrary at the moment. The idea |
---|
243 | 0.1, 0.1, 0.1, 0.1, 0.1, 0.1 /) !! is to have a small number to make as many levels |
---|
244 | !! as possible in the canopies, but not too small which |
---|
245 | !! results in too little LAI in all the levels. If all your |
---|
246 | !! levels have less than 0.1 LAI in them, that's probably |
---|
247 | !! too small. |
---|
248 | |
---|
249 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_top_mtc = & !! Diffuco.f90 calculates the stomatal conductance of the |
---|
250 | (/ un, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, & !! top layer of the canopy. Because the top layer can contain |
---|
251 | 0.1, 0.1, 0.1, 0.1, 0.1, 0.1 /) !! diiferent amounts of LAI depending on the crown diameter |
---|
252 | !! we had to define top layer in terms of the LAI it contains. |
---|
253 | !! stomatal conductance in the top layer contributes to the |
---|
254 | !! transpiration (m2 m-2). Arbitrary values. |
---|
255 | ! |
---|
256 | ! SOIL - VEGETATION |
---|
257 | ! |
---|
258 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_mtc = & !! The soil tile number for each vegetation |
---|
259 | & (/ 1, 2, 2, 2, 2, 2, 2, & |
---|
260 | & 2, 2, 3, 3, 3, 3 /) |
---|
261 | |
---|
262 | ! |
---|
263 | ! VEGETATION - AGE CLASSES |
---|
264 | ! |
---|
265 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: agec_group_mtc = & !! The age class group that each PFT belongs to. |
---|
266 | (/ 1, 2, 3, 4, 5, 6, 7, & |
---|
267 | 8, 9, 10, 11, 12, 13 /) |
---|
268 | |
---|
269 | |
---|
270 | ! |
---|
271 | ! PHOTOSYNTHESIS |
---|
272 | ! |
---|
273 | !- |
---|
274 | ! 1 .CO2 |
---|
275 | !- |
---|
276 | LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c4_mtc = & !! flag for C4 vegetation types (true/false) |
---|
277 | & (/ .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., & |
---|
278 | & .FALSE., .FALSE., .FALSE., .TRUE., .FALSE., .TRUE. /) |
---|
279 | |
---|
280 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_fix_mtc = & !! values used for vcmax when STOMATE is not |
---|
281 | & (/ 0.0, 40.0, 50.0, 30.0, 35.0, 40.0, 30.0, & !! activated @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex |
---|
282 | & 40.0, 35.0, 60.0, 60.0, 70.0, 70.0 /) |
---|
283 | |
---|
284 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmC_mtc = & !! Energy of activation for KmC (J mol-1) |
---|
285 | & (/undef, 79430., 79430., 79430., 79430., 79430., 79430., & !! See Medlyn et al. (2002) |
---|
286 | & 79430., 79430., 79430., 79430., 79430., 79430. /) !! from Bernacchi al. (2001) |
---|
287 | |
---|
288 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmO_mtc = & !! Energy of activation for KmO (J mol-1) |
---|
289 | & (/undef, 36380., 36380., 36380., 36380., 36380., 36380., & !! See Medlyn et al. (2002) |
---|
290 | & 36380., 36380., 36380., 36380., 36380., 36380. /) !! from Bernacchi al. (2001) |
---|
291 | |
---|
292 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gamma_star_mtc = & !! Energy of activation for gamma_star (J mol-1) |
---|
293 | & (/undef, 37830., 37830., 37830., 37830., 37830., 37830., & !! See Medlyn et al. (2002) from Bernacchi al. (2001) |
---|
294 | & 37830., 37830., 37830., 37830., 37830., 37830. /) !! for C3 plants - We use the same values for C4 plants |
---|
295 | |
---|
296 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Vcmax_mtc = & !! Energy of activation for Vcmax (J mol-1) |
---|
297 | & (/undef, 71513., 71513., 71513., 71513., 71513., 71513., & !! See Table 2 of Yin et al. (2009) for C4 plants |
---|
298 | & 71513., 71513., 71513., 67300., 71513., 67300. /) !! and Kattge & Knorr (2007) for C3 plants (table 3) |
---|
299 | |
---|
300 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Jmax_mtc = & !! Energy of activation for Jmax (J mol-1) |
---|
301 | & (/undef, 49884., 49884., 49884., 49884., 49884., 49884., & !! See Table 2 of Yin et al. (2009) for C4 plants |
---|
302 | & 49884., 49884., 49884., 77900., 49884., 77900. /) !! and Kattge & Knorr (2007) for C3 plants (table 3) |
---|
303 | |
---|
304 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: aSV_mtc = & !! a coefficient of the linear regression (a+bT) defining |
---|
305 | & (/undef, 668.39, 668.39, 668.39, 668.39, 668.39, 668.39, & !! the Entropy term for Vcmax (J K-1 mol-1) See Table 3 of |
---|
306 | & 668.39, 668.39, 668.39, 641.64, 668.39, 641.64 /) !! Kattge & Knorr (2007). For C4 plants, we assume that |
---|
307 | !! there is no acclimation and that at for a temperature |
---|
308 | !! of 25°C, aSV is the same for both C4 and C3 plants |
---|
309 | !! (no strong jusitification - need further parametrization) |
---|
310 | |
---|
311 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bSV_mtc = & !! b coefficient of the linear regression (a+bT) defining |
---|
312 | & (/undef, -1.07, -1.07, -1.07, -1.07, -1.07, -1.07, & !! the Entropy term for Vcmax (J K-1 mol-1 °C-1) See Table 3 |
---|
313 | & -1.07, -1.07, -1.07, 0., -1.07, 0. /) !! of Kattge & Knorr (2007). We assume No acclimation term for C4 plants |
---|
314 | |
---|
315 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_mtc = & !! minimum photosynthesis temperature (deg C) |
---|
316 | & (/ undef, -4.0, -4.0, -4.0, -4.0, -4.0, -4.0, & |
---|
317 | & -4.0, -4.0, -4.0, -4.0, -4.0, -4.0 /) |
---|
318 | |
---|
319 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_mtc = & !! maximum photosynthesis temperature (deg C) |
---|
320 | & (/ undef, 55.0, 55.0, 55.0, 55.0, 55.0, 55.0, & |
---|
321 | & 55.0, 55.0, 55.0, 55.0, 55.0, 55.0 /) |
---|
322 | |
---|
323 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: aSJ_mtc = & !! a coefficient of the linear regression (a+bT) defining the |
---|
324 | & (/undef, 659.70, 659.70, 659.70, 659.70, 659.70, 659.70, & !! Entropy term for Jmax (J K-1 mol-1) See Table 3 of |
---|
325 | & 659.70, 659.70, 659.70, 630., 659.70, 630. /) !! Kattge & Knorr (2007) and Table 2 of Yin et al. (2009) for C4 plants |
---|
326 | |
---|
327 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bSJ_mtc = & !! b coefficient of the linear regression (a+bT) defining the |
---|
328 | & (/undef, -0.75, -0.75, -0.75, -0.75, -0.75, -0.75, & !! Entropy term for Jmax (J K-1 mol-1 °C-1). See Table 3 of |
---|
329 | & -0.75, -0.75, -0.75, 0., -0.75, 0. /) !! Kattge & Knorr (2007) We assume no acclimation term for C4 plants |
---|
330 | |
---|
331 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Vcmax_mtc = & !! Energy of deactivation for Vcmax (J mol-1) |
---|
332 | & (/undef, 200000., 200000., 200000., 200000., 200000., 200000., & !! Medlyn et al. (2002) also uses 200000. for C3 plants (same value than D_Jmax) |
---|
333 | & 200000., 200000., 200000., 192000., 200000., 192000. /) !! 'Consequently', we use the value of D_Jmax for C4 plants |
---|
334 | |
---|
335 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Jmax_mtc = & !! Energy of deactivation for Jmax (J mol-1) |
---|
336 | & (/undef, 200000., 200000., 200000., 200000., 200000., 200000., & !! See Table 2 of Yin et al. (2009) |
---|
337 | & 200000., 200000., 200000., 192000., 200000., 192000. /) !! Medlyn et al. (2002) also uses 200000. for C3 plants |
---|
338 | |
---|
339 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Rd_mtc = & !! Energy of activation for Rd (J mol-1) |
---|
340 | & (/undef, 46390., 46390., 46390., 46390., 46390., 46390., & !! See Table 2 of Yin et al. (2009) |
---|
341 | & 46390., 46390., 46390., 46390., 46390., 46390. /) |
---|
342 | |
---|
343 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Vcmax25_mtc = & !! Maximum rate of Rubisco activity-limited carboxylation at 25°C |
---|
344 | & (/ undef, 65.0, 65.0, 35.0, 45.0, 55.0, 35.0, & !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex |
---|
345 | & 45.0, 35.0, 70.0, 70.0, 70.0, 70.0 /) |
---|
346 | |
---|
347 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: arJV_mtc = & !! a coefficient of the linear regression (a+bT) defining the |
---|
348 | & (/undef, 2.59, 2.59, 2.59, 2.59, 2.59, 2.59, & !! Jmax25/Vcmax25 ratio (mu mol e- (mu mol CO2)-1) See Table 3 of |
---|
349 | & 2.59, 2.59, 2.59, 1.715, 2.59, 1.715 /) !! Kattge & Knorr (2007). For C4 plants, we assume that there is no |
---|
350 | !! acclimation and that for a temperature of 25°C, aSV is the same |
---|
351 | !! for both C4 and C3 plants (no strong jusitification - need further |
---|
352 | !! parametrization) |
---|
353 | |
---|
354 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: brJV_mtc = & !! b coefficient of the linear regression (a+bT) defining the |
---|
355 | & (/undef, -0.035, -0.035, -0.035, -0.035, -0.035, -0.035, & !! Jmax25/Vcmax25 ratio ((mu mol e- (mu mol CO2)-1) (°C)-1) See |
---|
356 | & -0.035, -0.035, -0.035, 0., -0.035, 0. /) !! Table 3 of Kattge & Knorr (2007). We assume No acclimation term for C4 plants |
---|
357 | |
---|
358 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmC25_mtc = & !! MichaelisâMenten constant of Rubisco for CO2 at 25°C (ubar) |
---|
359 | & (/undef, 404.9, 404.9, 404.9, 404.9, 404.9, 404.9, & !! See Table 2 of Yin et al. (2009) for C4 |
---|
360 | & 404.9, 404.9, 404.9, 650., 404.9, 650. /) !! and Medlyn et al (2002) for C3 |
---|
361 | |
---|
362 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmO25_mtc = & !! MichaelisâMenten constant of Rubisco for O2 at 25°C (ubar) |
---|
363 | & (/undef, 278400., 278400., 278400., 278400., 278400., 278400., & !! See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 |
---|
364 | & 278400., 278400., 278400., 450000., 278400., 450000. /) |
---|
365 | |
---|
366 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gamma_star25_mtc = & !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar) |
---|
367 | & (/undef, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75, & !! See Medlyn et al. (2002) for C3 plants - For C4 plants, we use the |
---|
368 | & 42.75, 42.75, 42.75, 42.75, 42.75, 42.75 /) !! same value (probably uncorrect) |
---|
369 | |
---|
370 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a1_mtc = & !! Empirical factor involved in the calculation of fvpd (-) |
---|
371 | & (/undef, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, & !! See Table 2 of Yin et al. (2009) |
---|
372 | & 0.85, 0.85, 0.85, 0.85, 0.85, 0.85 /) |
---|
373 | |
---|
374 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b1_mtc = & !! Empirical factor involved in the calculation of fvpd (-) |
---|
375 | & (/undef, 0.14, 0.14, 0.14, 0.14, 0.14, 0.14, & !! See Table 2 of Yin et al. (2009) |
---|
376 | & 0.14, 0.14, 0.14, 0.20, 0.14, 0.20 /) |
---|
377 | |
---|
378 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: g0_mtc = & !! Residual stomatal conductance when irradiance approaches |
---|
379 | & (/undef, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, & !! zero (mol CO2 mâ2 sâ1 barâ1). Value from ORCHIDEE - No other reference. |
---|
380 | & 0.00625, 0.00625, 0.00625, 0.01875, 0.00625, 0.01875 /) !! modofy to account for the conversion for conductance to H2O to CO2 |
---|
381 | |
---|
382 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: h_protons_mtc = & !! Number of protons required to produce one ATP (mol mol-1) |
---|
383 | & (/undef, 4., 4., 4., 4., 4., 4., & !! See Table 2 of Yin et al. (2009) - h parameter |
---|
384 | & 4., 4., 4., 4., 4., 4. /) |
---|
385 | |
---|
386 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpsir_mtc = & !! Fraction of PSII eâ transport rate |
---|
387 | & (/undef, undef, undef, undef, undef, undef, undef, & !! partitioned to the C4 cycle (-) |
---|
388 | & undef, undef, undef, 0.4, undef, 0.4 /) !! See Table 2 of Yin et al. (2009) - x parameter |
---|
389 | |
---|
390 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fQ_mtc = & !! Fraction of electrons at reduced plastoquinone |
---|
391 | & (/undef, undef, undef, undef, undef, undef, undef, & !! that follow the Q-cycle (-) - Values for C3 platns are not used |
---|
392 | & undef, undef, undef, 1., undef, 1. /) !! See Table 2 of Yin et al. (2009) |
---|
393 | |
---|
394 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpseudo_mtc = & !! Fraction of electrons at PSI that follow |
---|
395 | & (/undef, undef, undef, undef, undef, undef, undef, & !! pseudocyclic transport (-) - Values for C3 platns are not used |
---|
396 | & undef, undef, undef, 0.1, undef, 0.1 /) !! See Table 2 of Yin et al. (2009) |
---|
397 | |
---|
398 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kp_mtc = & !! Initial carboxylation efficiency of the PEP carboxylase (mol mâ2 sâ1 barâ1) |
---|
399 | & (/undef, undef, undef, undef, undef, undef, undef, & !! See Table 2 of Yin et al. (2009) |
---|
400 | & undef, undef, undef, 0.7, undef, 0.7 /) |
---|
401 | |
---|
402 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_mtc = & !! Fraction of PSII activity in the bundle sheath (-) |
---|
403 | & (/undef, undef, undef, undef, undef, undef, undef, & !! See legend of Figure 6 of Yin et al. (2009) |
---|
404 | & undef, undef, undef, 0.1, undef, 0.1 /) |
---|
405 | |
---|
406 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gbs_mtc = & !! Bundle-sheath conductance (mol mâ2 sâ1 barâ1) |
---|
407 | & (/undef, undef, undef, undef, undef, undef, undef, & !! See legend of Figure 6 of Yin et al. (2009) |
---|
408 | & undef, undef, undef, 0.003, undef, 0.003 /) |
---|
409 | |
---|
410 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: theta_mtc = & !! Convexity factor for response of J to irradiance (-) |
---|
411 | & (/undef, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, & !! See Table 2 of Yin et al. (2009) |
---|
412 | & 0.7, 0.7, 0.7, 0.7, 0.7, 0.7 /) |
---|
413 | |
---|
414 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_LL_mtc = & !! Conversion efficiency of absorbed light into J at strictly |
---|
415 | & (/undef, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, & !! limiting light (mol eâ (mol photon)â1). See comment from |
---|
416 | & 0.3, 0.3, 0.3, 0.3, 0.3, 0.3 /) !! Yin et al. (2009) after eq. 4. alpha value from Medlyn et al. (2002) |
---|
417 | !! This is rather low, Yin et al. proposes 0.43 (text above eq.11) |
---|
418 | |
---|
419 | |
---|
420 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: downregulation_co2_coeff_mtc = & !! coefficient for CO2 downregulation |
---|
421 | & (/ 0.0, 0.38, 0.38, 0.28, 0.28, 0.28, 0.22, & |
---|
422 | & 0.22, 0.22, 0.26, 0.26, 0.26, 0.26 /) |
---|
423 | !- |
---|
424 | ! 2 .Stomate |
---|
425 | !- |
---|
426 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_mtc = & !! extinction coefficient of the Monsi&Saeki |
---|
427 | & (/ 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, & !! relationship (1953) (unitless) |
---|
428 | & 0.5, 0.5, 0.5, 0.5, 0.5, 0.5 /) |
---|
429 | |
---|
430 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_opt_fun_all_mtc = & !! Maximum rate of carboxylation |
---|
431 | & (/ undef, 65., 65., 35., 40., 55., 35., & !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex |
---|
432 | & 45., 35., 70., 70., 70., 70. /) |
---|
433 | |
---|
434 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vjmax_opt_fun_all_mtc = & !! Maximum rate of RUbp regeneration |
---|
435 | & vcmax_opt_fun_all_mtc(:)*2. !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex |
---|
436 | |
---|
437 | ! |
---|
438 | ! ALLOCATION (stomate) |
---|
439 | ! |
---|
440 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: S0_mtc = & !! Default sapwood allocation (0-1, unitless) |
---|
441 | & (/ undef, 0.25, 0.25, 0.30, 0.30, 0.30, 0.30, & |
---|
442 | & 0.30, 0.30, 0.30, 0.30, 0.30, 0.30 /) |
---|
443 | |
---|
444 | ! |
---|
445 | ! RESPIRATION (stomate) |
---|
446 | ! |
---|
447 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_c_mtc = & !! slope of maintenance respiration coefficient (1/K), |
---|
448 | & (/ undef, 0.20, 0.20, 0.16, 0.16, 0.16, 0.16, & !! constant c of aT^2+bT+c, tabulated |
---|
449 | & 0.16, 0.16, 0.16, 0.12, 0.16, 0.12 /) |
---|
450 | |
---|
451 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_b_mtc = & !! slope of maintenance respiration coefficient (1/K), |
---|
452 | & (/ undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, & !! constant b of aT^2+bT+c, tabulated |
---|
453 | & 0.0, 0.0, -0.00133, 0.0, -0.00133, 0.0 /) |
---|
454 | |
---|
455 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_a_mtc = & !! slope of maintenance respiration coefficient (1/K), |
---|
456 | & (/ undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, & !! constant a of aT^2+bT+c, tabulated |
---|
457 | & 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /) |
---|
458 | |
---|
459 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_leaf_mtc = & !! maintenance respiration coefficient |
---|
460 | & (/ 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, |
---|
461 | & 2.62E-3, 2.05E-3, 2.62E-3, 2.62E-3, 2.62E-3, 2.62E-3 /) !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
462 | |
---|
463 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapabove_mtc = & !! maintenance respiration coefficient |
---|
464 | & (/ 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, |
---|
465 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
466 | |
---|
467 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapbelow_mtc = & !! maintenance respiration coefficient |
---|
468 | & (/ 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, |
---|
469 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
470 | |
---|
471 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartabove_mtc = & !! maintenance respiration coefficient |
---|
472 | & (/ undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, & !! at 0 deg C, for heartwood above, |
---|
473 | & 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /) !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
474 | |
---|
475 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartbelow_mtc = & !! maintenance respiration coefficient |
---|
476 | & (/ undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, & !! at 0 deg C, for heartwood below, |
---|
477 | & 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 /) !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
478 | |
---|
479 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_root_mtc = & !! maintenance respiration coefficient |
---|
480 | & (/ 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, |
---|
481 | & 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3 /) !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
482 | |
---|
483 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_fruit_mtc = & !! maintenance respiration coefficient |
---|
484 | & (/ 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, |
---|
485 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
486 | |
---|
487 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_carbres_fun_all_mtc = & !! maintenance respiration coefficient |
---|
488 | & (/ undef, 0., 0., 0., 0., 0., 0., & !! at 0 deg C, for carbohydrate reserve, |
---|
489 | & 0., 0., 0., 0., 0., 0. /) !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
490 | |
---|
491 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_labile_fun_all_mtc = & !! maintenance respiration coefficient |
---|
492 | & (/ undef, 2.78E-3, 2.78E-3, 2.78E-3, 2.78E-3, 2.78E-3, 2.78E-3, & !! at 0 deg C, for labile carbon pool, |
---|
493 | & 2.78E-3, 2.78E-3, 2.78E-3, 2.78E-3, 2.78E-3, 2.78E-3 /)*12. !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
494 | |
---|
495 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_carbres_res_lim_mtc = & !! maintenance respiration coefficient |
---|
496 | & (/ 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, |
---|
497 | & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
498 | |
---|
499 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_labile_res_lim_mtc = & !! (not used) maintenance respiration coefficient |
---|
500 | & (/ undef, 0., 0., 0., 0., 0., 0., & !! at 0 deg C, for labile carbon pool, |
---|
501 | & 0., 0., 0., 0., 0., 0. /) !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
502 | |
---|
503 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_maint_init_mtc = & !! Initial values for maintenance respiration |
---|
504 | & (/ undef, 0.022, 0.022, 0.021, 0.033, 0.033, 0.033, & !! at 0 deg C, used in the functional allocation |
---|
505 | & 0.033, 0.033, 0.033, 0.033, 0.033, 0.033 /) !! scheme. The range of the values is given by |
---|
506 | !! Sitch et al 2003 but the values were tuned to |
---|
507 | !! obtain a NPP/GPP ratio of 0.5 in forests |
---|
508 | !! given a sufficient nutrient supply (see Vicca |
---|
509 | !! et al 2012 Ecology Letters) |
---|
510 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_res_lim_mtc = & !! Fraction of growth respiration expressed as |
---|
511 | &(/ 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, & !! share of the total C that is to be allocated |
---|
512 | & 0.28, 0.28, 0.28, 0.28, 0.28, 0.28 /) !! (0-1). Value for the resource limitation based |
---|
513 | !! allocation scheme |
---|
514 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_fun_all_mtc = & !! Fraction of growth respiration expressed as |
---|
515 | &(/ 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, & !! share of the total C that is to be allocated |
---|
516 | & 0.28, 0.28, 0.28, 0.28, 0.28, 0.28 /) !! (0-1). Value for the functional allocation |
---|
517 | !! approach |
---|
518 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gpp_to_labile_mtc = & !! The size of the labile pool as a fraction of the |
---|
519 | &(/ 1., 3., 1., 1., 3., 1., 3., & !! weekly gpp (-). For example, 3 indicates that the |
---|
520 | & 3., 3., 3., 3., 3., 3. /) !! labile pool is 3 times the weekly gpp. |
---|
521 | |
---|
522 | ! |
---|
523 | ! STAND STRUCTURE |
---|
524 | ! |
---|
525 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_density_mtc = & !! Wood density @tex $(gC.m^{-3})$ @endtex |
---|
526 | &(/ 0.0, 3.e5, 3.e5, 2.e5, 3.e5, 3.e5, 2.e5, & !! Current values are taken from the trunk. |
---|
527 | & 3.e5, 2.e5, 2.e5, 2.e5, 2.e5, 2.e5 /) !! forestry-branch has more realistic values |
---|
528 | !! in it. Source: AFOCEL 2006 |
---|
529 | |
---|
530 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune1_mtc = & !! cn_area = pipe_tune1*... |
---|
531 | &(/ undef, 100., 100., 100., 100., 100., 100., & !! stem diameter**pipe_tune_exp_coeff |
---|
532 | & 100., 100., undef, undef, undef, undef /) |
---|
533 | |
---|
534 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tree_ff_mtc = & !! Tree form factor to reduce |
---|
535 | &(/ undef, 0.6, 0.6, 0.6, 0.6, 0.6, 0.8, & !! the volume of a cylinder |
---|
536 | & 0.8, 0.8, undef, undef, undef, undef /) !! to the volume of the real tree shape |
---|
537 | |
---|
538 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune2_mtc = & !! height=pipe_tune2 * diameter**pipe_tune3 |
---|
539 | &(/ undef, 55., 55., 55., 55., 55., 55., & |
---|
540 | & 55., 55., undef, undef, undef, undef /) |
---|
541 | |
---|
542 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune3_mtc = & !! height=pipe_tune2 * diameter**pipe_tune3 |
---|
543 | &(/ undef, 0.65, 0.65, 0.65, 0.65, 0.65, 0.65, & |
---|
544 | & 0.65, 0.65, undef, undef, undef, undef /) |
---|
545 | |
---|
546 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune4_mtc = & !! CHECK - needed for stem diameter no longer used |
---|
547 | &(/ undef, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, & |
---|
548 | 0.3, 0.3, undef, undef, undef, undef /) |
---|
549 | |
---|
550 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_k1_mtc = & !! CHECK - no longer used |
---|
551 | &(/ undef, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, & |
---|
552 | & 8.e3, 8.e3, undef, undef, undef, undef /) |
---|
553 | |
---|
554 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune_exp_coeff_mtc = & !! cn_area = pipe_tune1*... |
---|
555 | &(/ undef, 1.6, 1.6, 1.6, 1.6, 1.6, 1.6, & !! stem diameter**pipe_tune_exp_coeff |
---|
556 | & 1.6, 1.6, undef, undef, undef, undef /) |
---|
557 | |
---|
558 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mass_ratio_heart_sap_mtc = & !! mass ratio (heartwood+sapwood)/heartwood |
---|
559 | &(/ undef, 3., 3., 3., 3., 3., 3., & |
---|
560 | & 3., 3., undef, undef, undef, undef /) |
---|
561 | |
---|
562 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_to_height_mtc = & !! Convertion from lai to height for grasses |
---|
563 | &(/ undef, undef, undef, undef, undef, undef, undef, & !! and cropland. Convert lai because that way a dynamic |
---|
564 | & undef, undef, 0.1, 0.2, 0.1, 0.2 /) !! sla is accounted for |
---|
565 | |
---|
566 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: canopy_cover_mtc = & !! Prescribed canopy cover (1-gap fraction) |
---|
567 | & (/ undef, 0.9, 0.9, 0.7, 0.7, 0.7, 0.6, & !! of a canopy (unitless) |
---|
568 | & 0.5, 0.5, 0.9, 0.9, 0.9, 0.9 /) |
---|
569 | |
---|
570 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: nmaxtrees_mtc = & !! Initial number of trees per ha. This parameter is |
---|
571 | & (/ 10000, 10000, 10000, 10000, 10000, 10000, 2000, & !! used at .firstcall. and after clearcuts |
---|
572 | & 2000, 2000, 10000, 10000, 10000, 10000 /) !! the value is used by the allometric allocation |
---|
573 | !! and forestry subroutines. |
---|
574 | |
---|
575 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_init_min_mtc = & !! The minimum height (m) of a tree sapling when a forest |
---|
576 | &(/ undef, 2., 2., 2., 2., 2., 3., & !! stand is established. Owing to the allometric |
---|
577 | & 3., 3., 0.1, 0.1, 0.1, 0.1 /) !! relationship this setting determines all |
---|
578 | !! biomass components of a newly establised stand |
---|
579 | |
---|
580 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_init_max_mtc = & !! The maximum height (m) of a tree sapling when a forest |
---|
581 | &(/ undef, 3., 3., 3., 3., 3., 4., & !! stand is established. |
---|
582 | & 4., 4., 0.2, 0.2, 0.2, 0.2 /) |
---|
583 | |
---|
584 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_self_thinning_mtc = & !! Coefficient of the self-thinning relationship D=alpha*N^beta |
---|
585 | &(/ undef, 3000., 3000., 1462., 2262., 1900., 960., & !! estimated from German, French, Spanish and Swedish |
---|
586 | & 939., 1046., undef, undef, undef, undef/) !! forest inventories |
---|
587 | |
---|
588 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: beta_self_thinning_mtc = & !! Exponent of the self-thinning relationship D=alpha*N^beta |
---|
589 | &(/ undef, -0.57, -0.57, -0.55, -0.61, -0.58, -0.55, & !! estimated from German, French, Spanish and Swedish |
---|
590 | & -0.56, -0.56, undef, undef, undef, undef/) !! forest inventories |
---|
591 | |
---|
592 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fuelwood_diameter_mtc = & !! Diameter below which the wood harvest is used as fuelwood (m) |
---|
593 | &(/ undef, 0.3, 0.3, 0.2, 0.3, 0.3, 0.2, & !! Affects the way the wood is used in the dim_product_use |
---|
594 | & 0.2, 0.2, undef, undef, undef, undef/) !! subroutine |
---|
595 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coppice_kill_be_wood_mtc = & !! The fraction of the belowground wood killed during coppicing. |
---|
596 | &(/ undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, & !! (unitless) |
---|
597 | & 0.0, 0.0, undef, undef, undef, undef/) |
---|
598 | |
---|
599 | ! |
---|
600 | ! GROWTH |
---|
601 | ! |
---|
602 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cn_leaf_prescribed_mtc = & !! C/N of leaves according to stich et al 2003 |
---|
603 | & (/ undef, 29., 29., 29., 29., 29., 29., & |
---|
604 | & 29., 29., 29., 29., 29., 29. /) |
---|
605 | |
---|
606 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fcn_wood_mtc = & !! C/N of "wood" for allocation relative to leaf C/N according |
---|
607 | & (/ undef, .087, .087, .087, .087, .087, .087, & !! to stich et al 2003 |
---|
608 | & .087, .087, 1., 1., 1., 1. /) |
---|
609 | |
---|
610 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fcn_root_mtc = & !! C/N of "root" for allocation relative to leaf C/N according |
---|
611 | & (/ undef, .86, .86, .86, .86, .86, .86, & !! to stich et al 2003 |
---|
612 | & .86, .86, .86, .86, .86, .86 /) |
---|
613 | |
---|
614 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_latosa_max_mtc = & !! Maximum leaf-to-sapwood area ratio as defined in McDowell et al |
---|
615 | & (/ undef, 5000., 5000., 5000., 3000., 5000., 5000., & !! 2002, Oecologia and compiled in Hickler et al 2006, Appendix S2 |
---|
616 | & 5000., 5000., 0.833, 0.833, 0.833, 0.833 /) !! The values for grasses and crops are tuned. More work is needed |
---|
617 | !! to fully justify this approach for the herbacuous PFTs (unitless) |
---|
618 | |
---|
619 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_latosa_min_mtc = & !! Minimum leaf-to-sapwood area ratio as defined in McDowell et al |
---|
620 | & (/ undef, 5000., 5000., 5000., 3000., 5000., 5000., & !! 2002, Oecologia and compiled in Hickler et al 2006, Appendix S2 |
---|
621 | & 5000., 5000., 0.833, 0.833, 0.833, 0.833 /) !! The values for grasses and crops are tuned. More work is needed |
---|
622 | !! to fully justify this approach for the herbacuous PFTs (unitless) |
---|
623 | |
---|
624 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fruit_alloc_mtc = & !! Fraction of biomass allocated to fruit production (0-1) |
---|
625 | & (/ undef, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, & !! currently only parameterized for forest PFTs |
---|
626 | & 0.1, 0.1, 0., 0., 0., 0. /) |
---|
627 | |
---|
628 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_max_to_happy_mtc = & !! Multiplicative factor of lai_max that determines |
---|
629 | & (/ undef, 0.5, 0.5, 0.5, 0.5, 0.4, 0.5, & !! the threshold value of LAI below which the carbohydrate |
---|
630 | & 0.36, 0.35, 0.35, 0.5, 0.5, 0.5 /) !! reserve is used |
---|
631 | |
---|
632 | ! |
---|
633 | ! HYDRAULIC ARCHITECTURE |
---|
634 | ! |
---|
635 | |
---|
636 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_root_mtc = & !! Fine root specific conductivity. Values compiled in T. Hickler |
---|
637 | & (/ undef, 4., 4., 4., 4., 4., 4., & !! et al. 2006. @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex |
---|
638 | & 4., 4., 50., 50., 50., 50. /)*1.e-7 |
---|
639 | |
---|
640 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_sap_mtc = & !! Maximal sapwood specific conductivity. Values compiled in T. Hickler |
---|
641 | & (/ undef, 50., 10., 8., 5., 30., 8., & !! et al. 2006. @tex $(m^{2} s^{-1} MPa^{-1})$ @endtex |
---|
642 | & 20., 8., undef, undef, undef, undef /)*1.e-4 |
---|
643 | |
---|
644 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_leaf_mtc = & !! Leaf conductivity. Values compiled in T. Hickler et al 2006 |
---|
645 | & (/ undef, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, & !! @tex $(m s^{-1} MPa^{-1})$ @endtex |
---|
646 | 1.5, 1.5, 1.5, 1.5, 1.5, 1.5 /)*1.e-7 |
---|
647 | |
---|
648 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: phi_leaf_mtc = & !! Minimal leaf water potential. Values in T. Hickler et al 2006 |
---|
649 | & (/ undef, -2.2, -2.2, -2.2, -3.5, -2.2, -2.2, & !! @tex $(MPa)$ @endtex |
---|
650 | -2.2, -2.2, -2.2, -2.2, -2.2, -2.2 /) |
---|
651 | |
---|
652 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: phi_50_mtc = & !! Sapwood leaf water potential that causes 50% loss of xylem |
---|
653 | & (/ undef, -0.3, -1.3, -2.0, -1.7, -1.0, -2.0, & !! conductivity through cavitation. @tex $(MPa)$ @endtex |
---|
654 | -1.0, -2.0, undef, undef, undef, undef /) |
---|
655 | |
---|
656 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: c_cavitation_mtc = & !! Shape parameter for loss of conductance Machado & Tyree, 1994 |
---|
657 | & (/ undef, 5., 3., 3., 3., 3., 3., & !! (unitless) |
---|
658 | 3., 3., undef, undef, undef, undef /) |
---|
659 | |
---|
660 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: phi_soil_tune_mtc = & !! Additive tuning parameter to account for soil-root interactions |
---|
661 | & (/ undef, 0., 0., 0., 0., 0., 0., & !! @tex $(MPa)$ @endtex |
---|
662 | 0., 0., 0., 0., 0., 0. /) |
---|
663 | |
---|
664 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_happy_mtc = & !! Lai threshold below which carbohydrate |
---|
665 | & (/ undef, 1., 1., 1., 1., 1., 1., & !! reserve may be used in functional allocation. |
---|
666 | 1., 1., 1., 1., 1., 1. /) !! Also used in phenology to see if mixed classes |
---|
667 | !! should die. These seem completely arbitrary. |
---|
668 | !! @tex $(m^2.m^{-2})$ @endtex |
---|
669 | |
---|
670 | ! ------------------------------------------------------------------------------------------------------- |
---|
671 | ! tzjh parameter for the new hydraulic architecture -- all set up for PFT2 now |
---|
672 | ! ------------------------------------------------------------------------------------------------------- |
---|
673 | |
---|
674 | ! Stomatal conductance parameters |
---|
675 | |
---|
676 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gpsi_mtc = & !! ! gs vs psi_leaf curve parameter |
---|
677 | & (/ undef, -2.0, -2.0, -2.0, -2.0, -2.0, -2.0, & !! |
---|
678 | & -2.0, -2.0, -2.0, -2.0, -2.0, -2.0 /) |
---|
679 | |
---|
680 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gpsi_50_mtc = & !! ! psi_leaf at 50% stomatal closure, -MPa |
---|
681 | & (/ undef, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, & !! |
---|
682 | & 1.5, 1.5, 1.5, 1.5, 1.5, 1.5 /) |
---|
683 | |
---|
684 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gmax_mtc = & !! maximum stomatal conductance |
---|
685 | & (/ undef, 500., 500., 500., 500., 500., 500., & !! @tex $mmol m^{-2}s^{-1}$ @endtex |
---|
686 | & 500., 500., 500., 500., 500., 500. /) |
---|
687 | |
---|
688 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gmin_mtc = & !! minimum (cuticular) conductance |
---|
689 | & (/ undef, 10., 10., 10., 10., 10., 10., & !! @tex $mmol m^{-2}s^{-1}$ @endtex |
---|
690 | & 10., 10., 10., 10., 10., 10. /) |
---|
691 | |
---|
692 | ! Hydraulic conductivity parameters |
---|
693 | |
---|
694 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kmax_leaf_mtc = & !! maximum hydraulic conductivity of leaf |
---|
695 | & (/ undef, 20., 20., 20., 20., 20., 20., & !! @tex $mmol m^{-2}s^{-1} MPa^{-1}$ @endtex |
---|
696 | & 10., 10., 10., 10., 10., 10. /) |
---|
697 | |
---|
698 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kmax_stem_mtc = & !! maximum hydraulic conductivity of stem |
---|
699 | & (/ undef, 10., 10., 10., 10., 10., 10., & !! @tex $mmol m^{-2}s^{-1} MPa^{-1}$ @endtex |
---|
700 | & 10., 10., 10., 10., 10., 10. /) |
---|
701 | |
---|
702 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kmax_root_mtc = & !! maximum hydraulic conductivity of root |
---|
703 | & (/ undef, 10., 10., 10., 10., 10., 10., & !! @tex $mmol m^{-2}s^{-1} MPa^{-1}$ @endtex |
---|
704 | & 10., 10., 10., 10., 10., 10. /) |
---|
705 | |
---|
706 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a_leaf_mtc = & !! kleaf vs. psi_leaf curve parameter |
---|
707 | & (/ undef, -1.2, -1.2, -1.2, -1.2, -1.2, -1.2, & !! |
---|
708 | & -1.2, -1.2, -1.2, -1.2, -1.2, -1.2 /) |
---|
709 | |
---|
710 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a_stem_mtc = & !! kstem vs. psi_stem curve parameter |
---|
711 | & (/ undef, -1.2, -1.2, -1.2, -1.2, -1.2, -1.2, & !! |
---|
712 | & -1.2, -1.2, -1.2, -1.2, -1.2, -1.2 /) |
---|
713 | |
---|
714 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a_root_mtc = & !! kroot vs. psi_root curve parameter |
---|
715 | & (/ undef, -1.2, -1.2, -1.2, -1.2, -1.2, -1.2, & !! |
---|
716 | & -1.2, -1.2, -1.2, -1.2, -1.2, -1.2 /) |
---|
717 | |
---|
718 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: P50_leaf_mtc = & !! psi_leaf at 50% loss of leaf hydraulic conductivity, MPa |
---|
719 | & (/ undef, 2.0, 2.0, 2.0, 2.0, 2.0, 2.0, & !! |
---|
720 | & 2.0, 2.0, 2.0, 2.0, 2.0, 2.0 /) |
---|
721 | |
---|
722 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: P50_stem_mtc = & !! psi_stem at 50% loss of leaf hydraulic conductivity, MPa |
---|
723 | & (/ undef, 2.5, 2.5, 2.5, 2.5, 2.5, 2.5, & !! |
---|
724 | & 2.5, 2.5, 2.5, 2.5, 2.5, 2.5 /) |
---|
725 | |
---|
726 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: P50_root_mtc = & !! psi_root at 50% loss of leaf hydraulic conductivity, MPa |
---|
727 | & (/ undef, 2.0, 2.0, 2.0, 2.0, 2.0, 2.0, & !! |
---|
728 | & 2.0, 2.0, 2.0, 2.0, 2.0, 2.0 /) |
---|
729 | |
---|
730 | ! Water storage parameters |
---|
731 | |
---|
732 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wood_density_mtc = & !! g of stem dry mass per m3 of stem volume Averaged across all Neotropical species |
---|
733 | & (/ undef, 645000.0, 645000.0, 645000.0, 645000.0, 645000.0, 645000.0, & !! from Chave et al. 2006 Ecological Applications |
---|
734 | & 645000.0, 645000.0, 645000.0, 645000.0, 645000.0, 645000.0 /) !! in the code pipe_density, not the same values |
---|
735 | !! (create a new variable for now to don't change the allocation) |
---|
736 | |
---|
737 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: w_density_stem_mtc = & !! mmol H2O per m3 of stem volume values averaged from a Bornean tropical forest, |
---|
738 | & (/ undef, 25000000.0, 25000000.0, 25000000.0, 25000000.0, 25000000.0, 25000000.0, & !! from Suzuki et al. 1999 Ecological Research |
---|
739 | & 25000000.0, 25000000.0, 25000000.0, 25000000.0, 25000000.0, 25000000.0 /) !! |
---|
740 | |
---|
741 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: root_shoot_ratio_mtc = & !! ratio of root mass to shoot mass, g g-1 values are averaged for wet and |
---|
742 | & (/ undef, 0.25, 0.25 , 0.25 , 0.25 , 0.25 , 0.25 , & !! dry tropical forests from Mokany et al. 2005 Global Change Biology |
---|
743 | & 0.25 , 0.25 , 0.25 , 0.25, 0.25, 0.25 /) |
---|
744 | |
---|
745 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rwc_root_mtc = & !! mmol H2O per g of dry root mass |
---|
746 | & (/ undef, 35.0, 35.0 , 35.0, 35.0, 35.0, 35.0, & !! dry tropical forests from Mokany et al. 2005 Global Change Biology |
---|
747 | & 35.0 , 35.0, 35.0, 35.0, 35.0, 35.0 /) |
---|
748 | |
---|
749 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: root_density_mtc = & !! wood density of the roots, g dry mass cm-3 volume |
---|
750 | & (/ undef, 0.502, 0.502 , 0.502, 0.502, 0.502, 0.502, & !! |
---|
751 | & 0.502 , 0.502, 0.502, 0.502, 0.502, 0.502 /) |
---|
752 | |
---|
753 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LDMC_mtc = & !! leaf dry matter content (g dry mass g-1 fresh mass), currently the global mean in the TRY |
---|
754 | & (/ undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, & !! database but should be replaced with the mean across tropical species (Kattge et al. 2011 Global Change Biology) |
---|
755 | & 0.2, 0.2, 0.2, 0.2, 0.2, 0.2 /) |
---|
756 | |
---|
757 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: sla_hydro_mtc = & !! sla (m2 kg-1), currenly the global mean in the TRY |
---|
758 | & (/ undef, 16.6, 16.6, 16.6, 16.6, 16.6, 16.6, & !! database but should be replaced with the mean across tropical species (Kattge et |
---|
759 | & 16.6, 16.6, 16.6, 16.6, 16.6, 16.6 /) !! al. 2011 Global Change Biology) idem, sla dalready in the code, to change ? |
---|
760 | |
---|
761 | ! Capacitance parameters |
---|
762 | |
---|
763 | ! REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cxyl_mtc = & !! stem capacitance, kg m^-3 MPa-1 |
---|
764 | ! & (/ undef, 0, 0, 0, 0, 0, 0, & !! |
---|
765 | ! & 0, 0, 0, 0, 0, 0 /) !! |
---|
766 | |
---|
767 | ! REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cr_mtc = & !! root capacitance, kg m^-3 MPa-1 |
---|
768 | ! & (/ undef, 0, 0, 0, 0, 0, 0, & !! |
---|
769 | ! & 0, 0, 0, 0, 0, 0 /) !! |
---|
770 | |
---|
771 | ! REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cl_mtc = & !! leaf capacitance, mmol m^2 MPa-1 |
---|
772 | ! & (/ undef, 0, 0, 0, 0, 0, 0, & !! |
---|
773 | ! & 0, 0, 0, 0, 0, 0 /) !! |
---|
774 | |
---|
775 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cxyl_mtc = & !! stem capacitance, kg m^-3 MPa-1 |
---|
776 | & (/ undef, 124.0, 124.0, 124.0, 124.0, 124.0, 124.0, & !! |
---|
777 | & 124.0, 124.0, 124.0, 124.0, 124.0, 124.0 /) !! |
---|
778 | |
---|
779 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cr_mtc = & !! root capacitance, kg m^-3 MPa-1 |
---|
780 | & (/ undef, 150.0, 150.0, 150.0, 150.0, 150.0, 150.0, & !! |
---|
781 | & 150.0, 150.0, 150.0, 150.0, 150.0, 150.0 /) !! |
---|
782 | |
---|
783 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cl_mtc = & !! leaf capacitance, mmol m^2 MPa-1 |
---|
784 | & (/ undef, 750.0, 670.0, 670.0, 670.0, 670.0, 670.0, & !! |
---|
785 | & 670.0, 670.0, 670.0, 670.0, 670.0, 670.0 /) !! |
---|
786 | ! |
---|
787 | ! MORTALITY (stomate) |
---|
788 | ! |
---|
789 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: death_distribution_factor_mtc = & !! The scale factor between the smallest and largest |
---|
790 | (/ undef, 100., 100., 100., 100., 100., 100., & !! circ class for tree mortality in stomate_mark_kill. |
---|
791 | 100., 100., undef, undef, undef, undef /) !! (unitless) |
---|
792 | |
---|
793 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: npp_reset_value_mtc = & !! The value of the NPP that the long-term value is |
---|
794 | (/ undef, undef, undef, undef, undef, undef, undef, & !! reset to after a PFT dies in stomate_kill. This |
---|
795 | undef, undef, 500., 500., 500., 500. /) !! only seems to be used for non-trees. |
---|
796 | !! @tex $(gC m^{-2})$ @endtex |
---|
797 | |
---|
798 | |
---|
799 | ! |
---|
800 | ! FIRE (stomate) |
---|
801 | ! |
---|
802 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: flam_mtc = & !! flamability: critical fraction of water |
---|
803 | & (/ undef, 0.15, 0.25, 0.25, 0.25, 0.25, 0.25, & !! holding capacity (0-1, unitless) |
---|
804 | & 0.25, 0.25, 0.25, 0.25, 0.35, 0.35 /) |
---|
805 | |
---|
806 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: resist_mtc = & !! fire resistance (0-1, unitless) |
---|
807 | & (/ undef, 0.95, 0.90, 0.12, 0.50, 0.12, 0.12, & |
---|
808 | & 0.12, 0.12, 0.0, 0.0, 0.0, 0.0 /) |
---|
809 | |
---|
810 | |
---|
811 | ! |
---|
812 | ! FLUX - LUC |
---|
813 | ! |
---|
814 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_s_mtc = & !! Coeff of biomass export for the year |
---|
815 | & (/ undef, 0.897, 0.897, 0.597, 0.597, 0.597, 0.597, & !! (0-1, unitless) |
---|
816 | & 0.597, 0.597, 0.597, 0.597, 0.597, 0.597 /) |
---|
817 | |
---|
818 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_m_mtc = & !! Coeff of biomass export for the decade |
---|
819 | & (/ undef, 0.103, 0.103, 0.299, 0.299, 0.299, 0.299, & !! (0-1, unitless) |
---|
820 | & 0.299, 0.299, 0.299, 0.403, 0.299, 0.403 /) |
---|
821 | |
---|
822 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_l_mtc = & !! Coeff of biomass export for the century |
---|
823 | & (/ undef, 0.0, 0.0, 0.104, 0.104, 0.104, 0.104, & !! (0-1, unitless) |
---|
824 | & 0.104, 0.104, 0.104, 0.0, 0.104, 0.0 /) |
---|
825 | |
---|
826 | |
---|
827 | ! |
---|
828 | ! PHENOLOGY |
---|
829 | ! |
---|
830 | !- |
---|
831 | ! 1. Stomate |
---|
832 | !- |
---|
833 | REAL(r_std), PARAMETER, DIMENSION (nvmc) :: lai_max_mtc = & !! maximum LAI, PFT-specific |
---|
834 | & (/ undef, 7.0, 7.0, 5.0, 5.0, 5.0, 4.5, & !! @tex $(m^2.m^{-2})$ @endtex |
---|
835 | & 4.5, 3.0, 2.5, 2.5, 5.0, 5.0 /) |
---|
836 | |
---|
837 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pheno_type_mtc = & !! type of phenology (0-4, unitless) |
---|
838 | & (/ 0, 1, 3, 1, 1, 2, 1, & !! 0=bare ground 1=evergreen, 2=summergreen, |
---|
839 | & 2, 2, 4, 4, 2, 3 /) !! 3=raingreen, 4=perennial |
---|
840 | !- |
---|
841 | ! 2. Leaf Onset |
---|
842 | !- |
---|
843 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_c_mtc = & !! critical gdd, tabulated (C), |
---|
844 | & (/ undef, undef, undef, undef, undef, undef, undef, & !! constant c of aT^2+bT+c |
---|
845 | & undef, undef, 320.0, 400.0, 450.0, 550.0 /) |
---|
846 | |
---|
847 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_b_mtc = & !! critical gdd, tabulated (C), |
---|
848 | & (/ undef, undef, undef, undef, undef, undef, undef, & !! constant b of aT^2+bT+c |
---|
849 | & undef, undef, 6.25, 0.0, 6.25, 0.0 /) |
---|
850 | |
---|
851 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_a_mtc = & !! critical gdd, tabulated (C), |
---|
852 | & (/ undef, undef, undef, undef, undef, undef, undef, & !! constant a of aT^2+bT+c |
---|
853 | & undef, undef, 0.03125, 0.0, 0.0315, 0.0 /) |
---|
854 | |
---|
855 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ngd_crit_mtc = & !! critical cumulated ngd, tabulated. |
---|
856 | & (/ undef, undef, undef, undef, undef, undef, undef, & !! Threshold -5 degrees (C) |
---|
857 | & undef, 17.0, undef, undef, undef, undef /) |
---|
858 | |
---|
859 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: opti_kpheno_crit_mtc = & !! multiplicative factor to use optimized |
---|
860 | & (/ undef, 1., 1., 1., 1., 1.13, 1., & !! gdd_crit (N. MacBean) |
---|
861 | & 0.87, 1.08, 0.81, 1., 1., 1. /) |
---|
862 | |
---|
863 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ncdgdd_temp_mtc = & !! critical temperature for the ncd vs. gdd |
---|
864 | & (/ undef, undef, undef, undef, undef, 5.0, undef, & !! function in phenology (C) |
---|
865 | & 0.0, 0.0, undef, undef, undef, undef /) |
---|
866 | |
---|
867 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_frac_mtc = & !! critical humidity (relative to min/max) |
---|
868 | & (/ undef, undef, 0.5, undef, undef, undef, undef, & !! for phenology (unitless) |
---|
869 | & undef, undef, 0.5, 0.5, 0.5, 0.5 /) |
---|
870 | |
---|
871 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_min_time_mtc = & !! minimum time elapsed since |
---|
872 | & (/ undef, undef, 50.0, undef, undef, undef, undef, & !! moisture minimum (days) |
---|
873 | & undef, undef, 58.71, 35.0, 75.0, 75.0 /) |
---|
874 | |
---|
875 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_sap_mtc = & !! Sapwood longivety (days) |
---|
876 | & (/ undef, 730., 730., 730., 730., 730., 730., & |
---|
877 | & 730., 730., undef, undef, undef, undef /) |
---|
878 | |
---|
879 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_fruit_mtc = & !! fruit longivety (days) |
---|
880 | & (/ undef, 90., 90., 90., 90., 90., 90., & |
---|
881 | & 90., 90., undef, undef, undef, undef /) |
---|
882 | |
---|
883 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_root_mtc = & !! roots longevity (days) |
---|
884 | & (/ undef, 365., 365., 365., 365., 365., 365., & |
---|
885 | & 365., 365., 365., 365., 365., 365. /)/7 |
---|
886 | |
---|
887 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_leaf_mtc = & !! leaf longevity (days) |
---|
888 | & (/ undef, 730., 180., 910., 730., 160.62, 910., & |
---|
889 | & 240., 89.57, 89.57, 120., 90., 90. /) |
---|
890 | |
---|
891 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ecureuil_mtc = & !! fraction of primary leaf and root allocation |
---|
892 | & (/ undef, 0.0, 1.0, 0.0, 0.0, 1.0, 0.0, & !! put into reserve (0-1, unitless) |
---|
893 | & 1.0, 1.0, 1.0, 1.0, 1.0, 1.0 /) |
---|
894 | |
---|
895 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_min_mtc = & !! NEW - allocation above/below = f(age) |
---|
896 | & (/ undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, & !! - 30/01/04 NV/JO/PF |
---|
897 | & 0.2, 0.2, undef, undef, undef, undef /) |
---|
898 | |
---|
899 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_max_mtc = & !! NEW - allocation above/below = f(age) |
---|
900 | & (/ undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, & !! - 30/01/04 NV/JO/PF |
---|
901 | & 0.8, 0.8, undef, undef, undef, undef /) |
---|
902 | |
---|
903 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: demi_alloc_mtc = & !! NEW - allocation above/below = f(age) |
---|
904 | & (/ undef, 5.0, 5.0, 5.0, 5.0, 5.0, 5.0, & !! - 30/01/04 NV/JO/PF |
---|
905 | & 5.0, 5.0, undef, undef, undef, undef /) |
---|
906 | |
---|
907 | !- |
---|
908 | ! 3. Senescence |
---|
909 | !- |
---|
910 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaffall_mtc = & !! length of death of leaves, tabulated (days) |
---|
911 | & (/ undef, undef, 10.0, undef, undef, 29.48, undef, & |
---|
912 | & 4.71, 9.41, 10.0, 10.0, 10.0, 10.0 /) |
---|
913 | |
---|
914 | CHARACTER(LEN=6), PARAMETER, DIMENSION(nvmc) :: senescence_type_mtc = & !! type of senescence, tabulated (unitless) |
---|
915 | & (/ 'none ', 'none ', 'dry ', 'none ', 'none ', & |
---|
916 | & 'cold ', 'none ', 'cold ', 'cold ', 'mixed ', & |
---|
917 | & 'mixed ', 'crop ', 'crop ' /) |
---|
918 | |
---|
919 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_hum_mtc = & !! critical relative moisture availability |
---|
920 | & (/ undef, undef, 0.3, undef, undef, undef, undef, & !! for senescence (0-1, unitless) |
---|
921 | & undef, undef, 0.2, 0.2, 0.3, 0.2 /) |
---|
922 | |
---|
923 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nosenescence_hum_mtc = & !! relative moisture availability above which |
---|
924 | & (/ undef, undef, 0.8, undef, undef, undef, undef, & !! there is no humidity-related senescence |
---|
925 | & undef, undef, 0.63, 0.3, 0.3, 0.3 /) !! (0-1, unitless) |
---|
926 | |
---|
927 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_turnover_time_mtc = & !! maximum turnover time for grasses (days) |
---|
928 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
929 | & undef, undef, 80.0, 80.0, 80.0, 80.0 /) |
---|
930 | |
---|
931 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_turnover_time_mtc = & !! minimum turnover time for grasses (days) |
---|
932 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
933 | & undef, undef, 10.0, 10.0, 10.0, 10.0 /) |
---|
934 | |
---|
935 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_leaf_age_for_senescence_mtc = & !! minimum leaf age to allow |
---|
936 | & (/ undef, undef, 90.0, undef, undef, 90.0, undef, & !! senescence g (days) |
---|
937 | & 60.0, 60.0, 30.0, 30.0, 30.0, 30.0 /) |
---|
938 | |
---|
939 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_c_mtc = & !! critical temperature for senescence (C) |
---|
940 | & (/ undef, undef, undef, undef, undef, 16.57, undef, & !! constant c of aT^2+bT+c, tabulated |
---|
941 | & 14.61, 12.0, 9.38, 5.0, 13.0, 10.0 /) !! (unitless) |
---|
942 | |
---|
943 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_b_mtc = & !! critical temperature for senescence (C), |
---|
944 | & (/ undef, undef, undef, undef, undef, 0.0, undef, & !! constant b of aT^2+bT+c, tabulated |
---|
945 | & 0.0, 0.0, 0.1, 0.0, 0.0, 0.0 /) !! (unitless) |
---|
946 | |
---|
947 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_a_mtc = & !! critical temperature for senescence (C), |
---|
948 | & (/ undef, undef, undef, undef, undef, 0.0, undef, & !! constant a of aT^2+bT+c, tabulated |
---|
949 | & 0.0, 0.0, 0.00375, 0.0, 0.0, 0.0 /) !! (unitless) |
---|
950 | |
---|
951 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gdd_senescence_mtc = & !! minimum gdd to allow senescence of crops (days) |
---|
952 | & (/ undef, undef, undef, undef, undef, undef, undef, & |
---|
953 | & undef, undef, undef, undef, 1500., 1500. /) |
---|
954 | |
---|
955 | |
---|
956 | ! |
---|
957 | ! DGVM |
---|
958 | ! |
---|
959 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: residence_time_mtc = & !! residence time of trees (years). NOTE: the meaning of |
---|
960 | & (/ undef, 30.0, 30.0, 40.0, 40.0, 40.0, 80.0, & !! ::residence_time is very different between the DOFOCO |
---|
961 | & 80.0, 80.0, 0.0, 0.0, 0.0, 0.0 /) !! branch and the trunk. In the trunk biomass has no age |
---|
962 | !! thus the residence time accounts for all forest dynamics |
---|
963 | !! including self-thinning, pests, diseases and wind fall. |
---|
964 | !! In the DOFOCO branch biomass has an age and |
---|
965 | !! self-thinning is explicitly accounted for. Hence, the |
---|
966 | !! residence time should be much higher as it only accounts |
---|
967 | !! for mortality due to pest, diseases and windfall. Even the |
---|
968 | !! latter is not exact because as long as those disturbances |
---|
969 | !! are small scale they are probably accounted for in the ! added by yitong yao 07 Jan 2020 08:43 !! parametrization of self-thinning. |
---|
970 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: plc_kill_frac_mtc = & |
---|
971 | & (/ undef, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, & |
---|
972 | & 0.01, 0.01, 0.0, 0.0, 0.0, 0.0 /) |
---|
973 | ! added by yitong yao 07 Jan 2020 08:44 above line |
---|
974 | |
---|
975 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mor_kill_frac_mtc = & |
---|
976 | & (/ undef, 0.001, 0.01, 0.01, 0.01, 0.01, 0.01, & |
---|
977 | & 0.01, 0.01, 0.0, 0.0, 0.0, 0.0 /) |
---|
978 | |
---|
979 | |
---|
980 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_crit_mtc = & |
---|
981 | & (/ undef, 0.0, 0.0, -30.0, -14.0, -30.0, -45.0, & !! critical tmin, tabulated (C) |
---|
982 | & -45.0, undef, undef, undef, undef, undef /) |
---|
983 | |
---|
984 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tcm_crit_mtc = & |
---|
985 | & (/ undef, undef, undef, 5.0, 15.5, 15.5, -8.0, & !! critical tcm, tabulated (C) |
---|
986 | & -8.0, -8.0, undef, undef, undef, undef /) |
---|
987 | |
---|
988 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mortality_min_mtc = & !! Asymptotic mortality if plant growth exceeds long term |
---|
989 | & (/ undef, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, & !! NPP (thus a strongly growing PFT) |
---|
990 | & 0.01, 0.01, 0.01, 0.01, 0.01, 0.01 /) !! @tex $(year^{-1})$ @endtex |
---|
991 | |
---|
992 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mortality_max_mtc = & !! Maximum mortality if plants hardly grows thus |
---|
993 | & (/ undef, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, & !! NPP << NPPlongterm @tex $(year^{-1})$ @endtex |
---|
994 | & 0.1, 0.1, 0.1, 0.1, 0.1, 0.1 /) |
---|
995 | |
---|
996 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ref_mortality_mtc = & !! Reference mortality rate used to calculate mortality |
---|
997 | & (/ undef, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035, & !! as a function of the plant vigor |
---|
998 | & 0.035, 0.035, 0.035, 0.035, 0.035, 0.035 /) !! @tex $(year^{-1})$ @endtex |
---|
999 | |
---|
1000 | |
---|
1001 | |
---|
1002 | ! |
---|
1003 | ! Biogenic Volatile Organic Compounds |
---|
1004 | ! |
---|
1005 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_isoprene_mtc = & !! Isoprene emission factor |
---|
1006 | & (/ 0., 24., 24., 8., 16., 45., 8., & !! |
---|
1007 | & 8., 8., 16., 24., 5., 5. /) |
---|
1008 | |
---|
1009 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_monoterpene_mtc = & !! Monoterpene emission factor |
---|
1010 | & (/ 0., 0.8, 0.8, 2.4, 1.2, 0.8, 2.4, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1011 | & 2.4, 2.4, 0.8, 1.2, 0.2, 0.2 /) |
---|
1012 | |
---|
1013 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_ORVOC_mtc = & !! ORVOC emissions factor |
---|
1014 | & (/ 0., 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1015 | & 1.5, 1.5, 1.5, 1.5, 1.5, 1.5 /) |
---|
1016 | |
---|
1017 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_OVOC_mtc = & !! OVOC emissions factor |
---|
1018 | & (/ 0., 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1019 | & 1.5, 1.5, 1.5, 1.5, 1.5, 1.5 /) |
---|
1020 | |
---|
1021 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_MBO_mtc = & !! MBO emissions factor |
---|
1022 | & (/ 0., 0., 0., 20.0, 0., 0., 0., & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1023 | & 0., 0., 0., 0., 0., 0. /) |
---|
1024 | |
---|
1025 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_methanol_mtc = & !! Methanol emissions factor |
---|
1026 | & (/ 0., 0.6, 0.6, 1.8, 0.9, 0.6, 1.8, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1027 | & 1.8, 1.8, 0.6, 0.9, 2., 2. /) |
---|
1028 | |
---|
1029 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetone_mtc = & !! Acetone emissions factor |
---|
1030 | & (/ 0., 0.29, 0.29, 0.87, 0.43, 0.29, 0.87, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1031 | & 0.87, 0.87, 0.29, 0.43, 0.07, 0.07 /) |
---|
1032 | |
---|
1033 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetal_mtc = & !! Acetaldehyde emissions factor |
---|
1034 | & (/ 0., 0.1, 0.1, 0.3, 0.15, 0.1, 0.3, 0.3, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1035 | & 0.3, 0.1, 0.15, 0.025, 0.025 /) |
---|
1036 | |
---|
1037 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formal_mtc = & !! Formaldehyde emissions factor |
---|
1038 | & (/ 0., 0.07, 0.07, 0.2, 0.1, 0.07, 0.2, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1039 | & 0.2, 0.2, 0.07, 0.1, 0.017, 0.017 /) |
---|
1040 | |
---|
1041 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetic_mtc = & !! Acetic Acid emissions factor |
---|
1042 | & (/ 0., 0.002, 0.002, 0.006, 0.003, 0.002, 0.006, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1043 | & 0.006, 0.006, 0.002, 0.003, 0.0005, 0.0005 /) |
---|
1044 | |
---|
1045 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formic_mtc = & !! Formic Acid emissions factor |
---|
1046 | & (/ 0., 0.01, 0.01, 0.03, 0.015, 0.01, 0.03, & !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
1047 | & 0.03, 0.03, 0.01, 0.015, 0.0025, 0.0025 /) |
---|
1048 | |
---|
1049 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_wet_mtc = & !! NOx emissions factor soil emissions and exponential |
---|
1050 | & (/ 0., 2.6, 0.06, 0.03, 0.03, 0.03, 0.03, & !! dependancy factor for wet soils |
---|
1051 | & 0.03, 0.03, 0.36, 0.36, 0.36, 0.36 /) !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex |
---|
1052 | |
---|
1053 | REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_dry_mtc = & !! NOx emissions factor soil emissions and exponential |
---|
1054 | & (/ 0., 8.60, 0.40, 0.22, 0.22, 0.22, 0.22, & !! dependancy factor for dry soils |
---|
1055 | & 0.22, 0.22, 2.65, 2.65, 2.65, 2.65 /) !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex |
---|
1056 | |
---|
1057 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Larch_mtc = & !! Larcher 1991 SAI/LAI ratio (unitless) |
---|
1058 | & (/ 0., 0.015, 0.015, 0.003, 0.005, 0.005, 0.003, & |
---|
1059 | & 0.005, 0.003, 0.005, 0.005, 0.008, 0.008 /) |
---|
1060 | |
---|
1061 | ! |
---|
1062 | ! Forest Management |
---|
1063 | ! |
---|
1064 | |
---|
1065 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fm_allo_a_mtc = & |
---|
1066 | !!$ & (/ undef, 19.42, 19.42, 9.3, 19.42, 19.42, 9.3, & |
---|
1067 | !!$ & 19.42, 9.3, undef, undef, undef, undef /) |
---|
1068 | !!$ |
---|
1069 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fm_allo_c_mtc = & |
---|
1070 | !!$ & (/ undef, 0.11, 0.11, 0.35, 0.11, 0.11, 0.35, & |
---|
1071 | !!$ & 0.11, 0.35, undef, undef, undef, undef /) |
---|
1072 | !!$ |
---|
1073 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fm_allo_d_mtc = & |
---|
1074 | !!$ & (/ undef, 0.13, 0.13, 0.3, 0.13, 0.13, 0.3, & |
---|
1075 | !!$ & 0.13, 0.3, undef, undef, undef, undef /) |
---|
1076 | !!$ |
---|
1077 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fm_allo_p_mtc = & |
---|
1078 | !!$ & (/ undef, 0.75, 0.75, 0.69, 0.75, 0.75, 0.69, & |
---|
1079 | !!$ & 0.75, 0.69, undef, undef, undef, undef /) |
---|
1080 | !!$ |
---|
1081 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fm_allo_q_mtc = & |
---|
1082 | !!$ & (/ undef, -0.12, -0.12, -0.32, -0.12, -0.12, -0.32, & |
---|
1083 | !!$ & -0.12, -0.32, undef, undef, undef, undef /) |
---|
1084 | !!$ |
---|
1085 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: allo_crown_a0_mtc = & |
---|
1086 | !!$ & (/ undef, -0.7602, -0.7602, -1.019, -0.7602, -0.7602, -1.019, & |
---|
1087 | !!$ & -0.7602, -1.019, undef, undef, undef, undef /) |
---|
1088 | !!$ |
---|
1089 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: allo_crown_a1_mtc = & |
---|
1090 | !!$ & (/ undef, 0.6672, 0.6672, 0.887, 0.6672, 0.6672, 0.887, & |
---|
1091 | !!$ & 0.6672, 0.887, undef, undef, undef, undef /) |
---|
1092 | !!$ |
---|
1093 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: allo_crown_a2_mtc = & |
---|
1094 | !!$ & (/ undef, 0.12646, 0.12646, 0.188, 0.12646, 0.12646, 0.188, & |
---|
1095 | !!$ & 0.12646, 0.188, undef, undef, undef, undef /) |
---|
1096 | !!$ |
---|
1097 | !!$ LOGICAL, PARAMETER, DIMENSION(nvmc) :: plantation_mtc = & |
---|
1098 | !!$ & (/ .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., & |
---|
1099 | !!$ & .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /) |
---|
1100 | !!$ |
---|
1101 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: decl_factor_mtc = & |
---|
1102 | !!$ & (/ 0.0, 0.0005, 0.0005, 0.0007, 0.0005, 0.0005, 0.0009, & |
---|
1103 | !!$ & 0.00075, 0.0005, 1.0, 1.0, 1.0, 1.0 /) |
---|
1104 | !!$ |
---|
1105 | !!$ REAL(r_std), PARAMETER, DIMENSION(nvmc) :: opt_factor_mtc = & |
---|
1106 | !!$ & (/ 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, & |
---|
1107 | !!$ & 1.0, 1.0, 1.0, 1.0, 1.0, 1.0 /) |
---|
1108 | |
---|
1109 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: h_first_mtc = & !! Height at which thinning will start (m) |
---|
1110 | & (/ 0.0, 10.0, 10.0, 10.0, 10.0, 10.0, 10.0, & |
---|
1111 | & 10.0, 10.0, 0.0, 0.0, 0.0, 0.0 /) |
---|
1112 | |
---|
1113 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: dens_target_mtc = & !! Minimal density. Below this density the forest |
---|
1114 | & (/ 0.0, 100.0, 100.0, 200.0, 100.0, 100.0, 200.0, & !! will be clearcut (trees.ha-1) |
---|
1115 | & 100.0, 200.0, 0.0, 0.0, 0.0, 0.0 /) |
---|
1116 | |
---|
1117 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: thinstrat_mtc = & !! Thinning strategy. The FM code distinguished |
---|
1118 | & (/ 0.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, & !! thinning from above (<0) or from below (>0). |
---|
1119 | & 1.0, 1.0, 0.0, 0.0, 0.0, 0.0 /) |
---|
1120 | |
---|
1121 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: taumin_mtc = & !! Minimum probability that a tree get thinned (unitless) |
---|
1122 | & (/ 0.0, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, & |
---|
1123 | & 0.01, 0.01, 0.0, 0.0, 0.0, 0.0 /) |
---|
1124 | |
---|
1125 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: taumax_mtc = & !! Maximum probability that a tree get thinned (unitless) |
---|
1126 | & (/ 0.0, 0.05, 0.05, 0.05, 0.05, 0.05, 0.05, & |
---|
1127 | & 0.05, 0.05, 0.0, 0.0, 0.0, 0.0 /) |
---|
1128 | |
---|
1129 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_rdi_upper_mtc = & !! Coefficient of the yield-table derived thinning relationship |
---|
1130 | &(/ undef, 3000., 3000., 592., 862., 504., 1287., & !! D=alpha*N^beta estimated from JRC yield table database |
---|
1131 | & 984., 589., undef, undef, undef, undef/) |
---|
1132 | |
---|
1133 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: beta_rdi_upper_mtc = & !! Coefficient of the yield-table derived thinning relationship |
---|
1134 | &(/ undef, -0.57, -0.57, -0.46, -0.51, -0.44, -0.59, & !! D=alpha*N^beta estimated from JRC yield table database |
---|
1135 | & -0.57, -0.48, undef, undef, undef, undef/) |
---|
1136 | |
---|
1137 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_rdi_lower_mtc = & !! Coefficient of the yield-table derived thinning relationship |
---|
1138 | &(/ undef, 2999., 2999., 433., 445., 369., 1022., & !! D=alpha*N^beta estimated from JRC yield table database |
---|
1139 | & 828., 385., undef, undef, undef, undef/) |
---|
1140 | |
---|
1141 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: beta_rdi_lower_mtc = & !! Coefficient of the yield-table derived thinning relationship |
---|
1142 | &(/ undef, -0.57, -0.57, -0.46, -0.51, -0.44, -0.59, & !! D=alpha*N^beta estimated from JRC yield table database |
---|
1143 | & -0.57, -0.48, undef, undef, undef, undef/) |
---|
1144 | |
---|
1145 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: largest_tree_dia_mtc = & !! Maximal tree diameter (m). If this diameter is exceeded a |
---|
1146 | & (/ 0.0, .45, .45, .45, .45, .45, .45, & !! a clearcut will happen. |
---|
1147 | & .45, .45, 0.0, 0.0, 0.0, 0.0 /) |
---|
1148 | |
---|
1149 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: branch_ratio_mtc = & !! Ratio of branches to total woody biomass (unitless) |
---|
1150 | & (/ 0.0, 0.38, 0.38, 0.25, 0.38, 0.38, 0.25, & |
---|
1151 | & 0.38, 0.25, 0.0, 0.0, 0.0, 0.0 /) |
---|
1152 | |
---|
1153 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: branch_harvest_mtc = & !! Ratio of branches harvested in FM2 management. |
---|
1154 | & (/ 0.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, & |
---|
1155 | & 1.0, 1.0, 0.0, 0.0, 0.0, 0.0 /) |
---|
1156 | |
---|
1157 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: m_dv_mtc = & !! Parameter in the Deleuze & Dhote allocation |
---|
1158 | & (/ undef, 1.05, 1.05, 1.05, 1.05, 1.05, 1.05, & !! rule that relaxes the cut-off imposed by |
---|
1159 | & 1.05, 1.05, 0., 0., 0., 0. /) !! ::sigma. Owing to m_relax trees still grow |
---|
1160 | !! a little when their ::circ is below ::sigma |
---|
1161 | |
---|
1162 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coppice_diameter_mtc = & !! The trunk diameter above which one coppices |
---|
1163 | & (/ undef, 0.20, 0.20, 0.20, 0.20, 0.20, 0.20, & !! trees. (m) |
---|
1164 | & 0.20, 0.20, 0., 0., 0., 0. /) |
---|
1165 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: shoots_per_stool_mtc = & !! The number of shoots which regrow on a stool after |
---|
1166 | (/ 9999, 6, 6, 6, 6, 6, 6, & !! coppicing. |
---|
1167 | 6, 6, 9999, 9999, 9999, 9999 /) |
---|
1168 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: src_rot_length_mtc = & !! The number of years between SRC cuttings. |
---|
1169 | (/ 9999, 3, 3, 3, 3, 3, 3, & !! (-) |
---|
1170 | 3, 3, 9999, 9999, 9999, 9999 /) |
---|
1171 | INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: src_nrots_mtc = & !! The number of SRC rotations before the whole stand |
---|
1172 | (/ 9999, 10, 10, 10, 10, 10, 10, & !! is harvested (-) |
---|
1173 | 10, 10, 9999, 9999, 9999, 9999 /) |
---|
1174 | |
---|
1175 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_a_mtc = & !! intercept of the intra-tree competition within a stand |
---|
1176 | & (/ undef, 0.23, 0.23, 0.23, 0.23, 0.23, 0.23, & !! based on the competion rule of Deleuze and Dhote 2004 |
---|
1177 | & 0.23, 0.23, undef, undef, undef, undef /) !! Used when n_circ > 6 |
---|
1178 | |
---|
1179 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_b_mtc = & !! slope of the intra-tree competition within a stand |
---|
1180 | & (/ undef, 0.58, 0.58, 0.58, 0.58, 0.58, 0.58, & !! based on the competion rule of Deleuze and Dhote 2004 |
---|
1181 | & 0.58, 0.58, undef, undef, undef, undef /) !! Used when n_circ > 6 |
---|
1182 | |
---|
1183 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_p_all_mtc = & !! Percentile of the circumferences that receives photosynthates |
---|
1184 | & (/ undef, 0.50, 0.50, 0.99, 0.99, 0.99, 0.99, & !! based on the competion rule of Deleuze and Dhote 2004 |
---|
1185 | & 0.99, 0.99, undef, undef, undef, undef /) !! Used when n_circ > 6 for FM1, FM2 and FM4 |
---|
1186 | |
---|
1187 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_p_coppice_mtc = & !! Percentile of the circumferences that receives photosynthates |
---|
1188 | & (/ undef, 0.50, 0.50, 0.50, 0.50, 0.50, 0.50, & !! based on the competion rule of Deleuze and Dhote 2004 |
---|
1189 | & 0.50, 0.50, undef, undef, undef, undef /) !! Used when n_circ > 6 for FM3 |
---|
1190 | |
---|
1191 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recruitment_light_threshold_mtc = & !! Light threshold (0 - 1) under which no recruitment is possible |
---|
1192 | &(/ undef, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, undef, undef, undef, undef/) |
---|
1193 | |
---|
1194 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: dia_recr_mtc = & !! Diameter (m) of the recruited stems |
---|
1195 | &(/ undef, 0.001, 0.001, 0.001, 0.001, 0.001, 0.001, 0.001, 0.001, undef, undef, undef, undef/) |
---|
1196 | |
---|
1197 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hei_recr_mtc = & !! Height (m) of the recruited stems (derived from allometric equation |
---|
1198 | &(/ undef, 0.9, 0.9, 0.9, 0.9, 0.9, 0.9, 0.9, 0.9, undef, undef, undef, undef/) !! for Nouragues, French Guiana). |
---|
1199 | |
---|
1200 | |
---|
1201 | ! |
---|
1202 | ! CROP MAANAGEMENT |
---|
1203 | ! |
---|
1204 | REAL(r_std), PARAMETER, DIMENSION(nvmc) :: harvest_ratio_mtc = & !! Share of biomass that is removed from the site during harvest |
---|
1205 | & (/ undef, undef, undef, undef, undef, undef, undef, & !! A high value indicates a high harvest efficiency and thus a |
---|
1206 | & undef, undef, undef, undef, 0.5, 0.5 /) !! input of residuals. (unitless, 0-1). |
---|
1207 | |
---|
1208 | |
---|
1209 | END MODULE constantes_mtc |
---|