1 | ! ================================================================================================================================= |
---|
2 | ! MODULE : pft_parameters_var |
---|
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 variables in function of plant funtional type (pft). |
---|
10 | !! |
---|
11 | !!\n DESCRIPTION: This module contains the declarations for the externalized variables in function of the |
---|
12 | !! plant foncional type(pft). \n |
---|
13 | !! The module is already USE in module pft_parameters. Therefor no need to USE it seperatly except |
---|
14 | !! if the subroutines in module pft_parameters are not needed.\n |
---|
15 | !! |
---|
16 | !! RECENT CHANGE(S): None |
---|
17 | !! |
---|
18 | !! REFERENCE(S) : None |
---|
19 | !! |
---|
20 | !! SVN : |
---|
21 | !! $HeadURL: $ |
---|
22 | !! $Date$ |
---|
23 | !! $Revision$ |
---|
24 | !! \n |
---|
25 | !_ ================================================================================================================================ |
---|
26 | |
---|
27 | MODULE pft_parameters_var |
---|
28 | |
---|
29 | USE defprec |
---|
30 | |
---|
31 | IMPLICIT NONE |
---|
32 | |
---|
33 | |
---|
34 | ! |
---|
35 | ! PFT GLOBAL |
---|
36 | ! |
---|
37 | INTEGER(i_std), SAVE :: nvm = 13 !! Number of vegetation types (2-N, unitless) |
---|
38 | !$OMP THREADPRIVATE(nvm) |
---|
39 | |
---|
40 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pft_to_mtc !! Table of conversion : we associate one pft to one metaclass |
---|
41 | !! (1-13, unitless) |
---|
42 | !$OMP THREADPRIVATE(pft_to_mtc) |
---|
43 | |
---|
44 | CHARACTER(LEN=34), ALLOCATABLE, SAVE, DIMENSION(:) :: PFT_name !! Description of the PFT (unitless) |
---|
45 | !$OMP THREADPRIVATE(PFT_name) |
---|
46 | |
---|
47 | LOGICAL, SAVE :: l_first_pft_parameters = .TRUE. !! To keep first call trace of the module (true/false) |
---|
48 | !$OMP THREADPRIVATE(l_first_pft_parameters) |
---|
49 | |
---|
50 | ! |
---|
51 | ! VEGETATION STRUCTURE |
---|
52 | ! |
---|
53 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_tab !! leaf type (1-4, unitless) |
---|
54 | !! 1=broad leaved tree, 2=needle leaved tree, |
---|
55 | !! 3=grass 4=bare ground |
---|
56 | !$OMP THREADPRIVATE(leaf_tab) |
---|
57 | |
---|
58 | CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_model !! which phenology model is used? (tabulated) (unitless) |
---|
59 | !$OMP THREADPRIVATE(pheno_model) |
---|
60 | |
---|
61 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tree !! Is the vegetation type a tree ? (true/false) |
---|
62 | !$OMP THREADPRIVATE(is_tree) |
---|
63 | |
---|
64 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_deciduous !! Is PFT deciduous ? (true/false) |
---|
65 | !$OMP THREADPRIVATE(is_deciduous) |
---|
66 | |
---|
67 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_evergreen !! Is PFT evegreen ? (true/false) |
---|
68 | !$OMP THREADPRIVATE(is_evergreen) |
---|
69 | |
---|
70 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_needleleaf !! Is PFT needleleaf ? (true/false) |
---|
71 | !$OMP THREADPRIVATE(is_needleleaf) |
---|
72 | |
---|
73 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tropical !! Is PFT tropical ? (true/false) |
---|
74 | !$OMP THREADPRIVATE(is_tropical) |
---|
75 | |
---|
76 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: natural !! natural? (true/false) |
---|
77 | !$OMP THREADPRIVATE(natural) |
---|
78 | |
---|
79 | CHARACTER(len=5), ALLOCATABLE, SAVE, DIMENSION(:) :: type_of_lai !! Type of behaviour of the LAI evolution algorithm |
---|
80 | !! for each vegetation type. |
---|
81 | !! Value of type_of_lai, one for each vegetation type : |
---|
82 | !! mean or interp |
---|
83 | !$OMP THREADPRIVATE(type_of_lai) |
---|
84 | |
---|
85 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: veget_ori_fixed_test_1 !! Value for veget_ori for tests in 0-dim simulations |
---|
86 | !! (0-1, unitless) |
---|
87 | !$OMP THREADPRIVATE(veget_ori_fixed_test_1) |
---|
88 | |
---|
89 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimax !! laimax for maximum lai see also type of lai |
---|
90 | !! interpolation |
---|
91 | !! @tex $(m^2.m^{-2})$ @endtex |
---|
92 | !$OMP THREADPRIVATE(llaimax) |
---|
93 | |
---|
94 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimin !! laimin for minimum lai see also type of lai |
---|
95 | !! interpolation |
---|
96 | !! @tex $(m^2.m^{-2})$ @endtex |
---|
97 | !$OMP THREADPRIVATE(llaimin) |
---|
98 | |
---|
99 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_presc !! prescribed height of vegetation.(m) |
---|
100 | !! Value for height_presc : one for each vegetation type |
---|
101 | !$OMP THREADPRIVATE(height_presc) |
---|
102 | |
---|
103 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: z0_over_height !! Factor to calculate roughness height from |
---|
104 | !! vegetation height (unitless) |
---|
105 | !$OMP THREADPRIVATE(z0_over_height) |
---|
106 | |
---|
107 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ratio_z0m_z0h !! Ratio between z0m and z0h |
---|
108 | !$OMP THREADPRIVATE(ratio_z0m_z0h) |
---|
109 | |
---|
110 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rveg_pft !! Potentiometer to set vegetation resistance (unitless) |
---|
111 | !! Nathalie on March 28th, 2006 - from Fred Hourdin, |
---|
112 | !$OMP THREADPRIVATE(rveg_pft) |
---|
113 | |
---|
114 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sla !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex |
---|
115 | !$OMP THREADPRIVATE(sla) |
---|
116 | |
---|
117 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: availability_fact !! calculate dynamic mortality in lpj_gap |
---|
118 | !$OMP THREADPRIVATE(availability_fact) |
---|
119 | |
---|
120 | ! |
---|
121 | ! EVAPOTRANSPIRATION (sechiba) |
---|
122 | ! |
---|
123 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const !! Structural resistance. |
---|
124 | !! Value for rstruct_const : one for each vegetation type |
---|
125 | !! @tex $(s.m^{-1})$ @endtex |
---|
126 | !$OMP THREADPRIVATE(rstruct_const) |
---|
127 | |
---|
128 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero !! A vegetation dependent constant used in the calculation |
---|
129 | !! of the surface resistance. |
---|
130 | !! Value for kzero one for each vegetation type |
---|
131 | !! @tex $(kg.m^2.s^{-1})$ @endtex |
---|
132 | !$OMP THREADPRIVATE(kzero) |
---|
133 | |
---|
134 | ! |
---|
135 | ! WATER (sechiba) |
---|
136 | ! |
---|
137 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wmax_veg !! Volumetric available soil water capacity in each PFT |
---|
138 | !! @tex $(kg.m^{-3} of soil)$ @endtex |
---|
139 | !$OMP THREADPRIVATE(wmax_veg) |
---|
140 | |
---|
141 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: humcste !! Root profile description for the different vegetation types. |
---|
142 | !! These are the factor in the exponential which gets |
---|
143 | !! the root density as a function of depth |
---|
144 | !! @tex $(m^{-1})$ @endtex |
---|
145 | !$OMP THREADPRIVATE(humcste) |
---|
146 | |
---|
147 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft !! Fraction of rain intercepted by the canopy (0-100, unitless) |
---|
148 | !$OMP THREADPRIVATE(throughfall_by_pft) |
---|
149 | |
---|
150 | ! |
---|
151 | ! ALBEDO (sechiba) |
---|
152 | ! |
---|
153 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_vis !! Minimum snow albedo value for each vegetation type |
---|
154 | !! after aging (dirty old snow), visible albedo (unitless) |
---|
155 | !! Source : Values are from the Thesis of S. Chalita (1992) |
---|
156 | !$OMP THREADPRIVATE(snowa_aged_vis) |
---|
157 | |
---|
158 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_nir !! Minimum snow albedo value for each vegetation type |
---|
159 | !! after aging (dirty old snow), near infrared albedo (unitless) |
---|
160 | !! Source : Values are from the Thesis of S. Chalita (1992) |
---|
161 | !$OMP THREADPRIVATE(snowa_aged_nir) |
---|
162 | |
---|
163 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_vis !! Decay rate of snow albedo value for each vegetation type |
---|
164 | !! as it will be used in condveg_snow, visible albedo (unitless) |
---|
165 | !! Source : Values are from the Thesis of S. Chalita (1992) |
---|
166 | !$OMP THREADPRIVATE(snowa_dec_vis) |
---|
167 | |
---|
168 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_nir !! Decay rate of snow albedo value for each vegetation type |
---|
169 | !! as it will be used in condveg_snow, near infrared albedo (unitless) |
---|
170 | !! Source : Values are from the Thesis of S. Chalita (1992) |
---|
171 | !$OMP THREADPRIVATE(snowa_dec_nir) |
---|
172 | |
---|
173 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis !! leaf albedo of vegetation type, visible albedo (unitless) |
---|
174 | !$OMP THREADPRIVATE(alb_leaf_vis) |
---|
175 | |
---|
176 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir !! leaf albedo of vegetation type, near infrared albedo (unitless) |
---|
177 | !$OMP THREADPRIVATE(alb_leaf_nir) |
---|
178 | |
---|
179 | ! |
---|
180 | ! SOIL - VEGETATION |
---|
181 | ! |
---|
182 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg !! Table which contains the correlation between the soil |
---|
183 | !! types and vegetation type. Two modes exist : |
---|
184 | !! 1) pref_soil_veg = 0 then we have an equidistribution |
---|
185 | !! of vegetation on soil types |
---|
186 | !! 2) Else for each pft the prefered soil type is given : |
---|
187 | !! 1=sand, 2=loan, 3=clay |
---|
188 | !! This variable is initialized in slowproc.(1-3, unitless) |
---|
189 | !$OMP THREADPRIVATE(pref_soil_veg) |
---|
190 | |
---|
191 | ! |
---|
192 | ! PHOTOSYNTHESIS |
---|
193 | ! |
---|
194 | !- |
---|
195 | ! 1. CO2 |
---|
196 | !- |
---|
197 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4 !! flag for C4 vegetation types (true/false) |
---|
198 | !$OMP THREADPRIVATE(is_c4) |
---|
199 | |
---|
200 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix !! values used for vcmax when STOMATE is not activated |
---|
201 | !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex |
---|
202 | !$OMP THREADPRIVATE(vcmax_fix) |
---|
203 | |
---|
204 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation (unitless) |
---|
205 | !$OMP THREADPRIVATE(downregulation_co2_coeff) |
---|
206 | |
---|
207 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC !! Energy of activation for KmC (J mol-1) |
---|
208 | !$OMP THREADPRIVATE(E_KmC) |
---|
209 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO !! Energy of activation for KmO (J mol-1) |
---|
210 | !$OMP THREADPRIVATE(E_KmO) |
---|
211 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Sco !! Energy of activation for Sco (J mol-1) |
---|
212 | !$OMP THREADPRIVATE(E_Sco) |
---|
213 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star !! Energy of activation for gamma_star (J mol-1) |
---|
214 | !$OMP THREADPRIVATE(E_gamma_star) |
---|
215 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax !! Energy of activation for Vcmax (J mol-1) |
---|
216 | !$OMP THREADPRIVATE(E_Vcmax) |
---|
217 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax !! Energy of activation for Jmax (J mol-1) |
---|
218 | !$OMP THREADPRIVATE(E_Jmax) |
---|
219 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: aSV !! a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1) |
---|
220 | !$OMP THREADPRIVATE(aSV) |
---|
221 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: bSV !! b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1 °C-1) |
---|
222 | !$OMP THREADPRIVATE(bSV) |
---|
223 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min !! minimum photosynthesis temperature (deg C) |
---|
224 | !$OMP THREADPRIVATE(tphoto_min) |
---|
225 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max !! maximum photosynthesis temperature (deg C) |
---|
226 | !$OMP THREADPRIVATE(tphoto_max) |
---|
227 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: aSJ !! a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1) |
---|
228 | !$OMP THREADPRIVATE(aSJ) |
---|
229 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: bSJ !! b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1 °C-1) |
---|
230 | !$OMP THREADPRIVATE(bSJ) |
---|
231 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax !! Energy of deactivation for Vcmax (J mol-1) |
---|
232 | !$OMP THREADPRIVATE(D_Vcmax) |
---|
233 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax !! Energy of deactivation for Jmax (J mol-1) |
---|
234 | !$OMP THREADPRIVATE(D_Jmax) |
---|
235 | |
---|
236 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gm !! Energy of activation for gm (J mol-1) |
---|
237 | !$OMP THREADPRIVATE(E_gm) |
---|
238 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S_gm !! Entropy term for gm (J K-1 mol-1) |
---|
239 | !$OMP THREADPRIVATE(S_gm) |
---|
240 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_gm !! Energy of deactivation for gm (J mol-1) |
---|
241 | !$OMP THREADPRIVATE(D_gm) |
---|
242 | |
---|
243 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd !! Energy of activation for Rd (J mol-1) |
---|
244 | !$OMP THREADPRIVATE(E_Rd) |
---|
245 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25 !! Maximum rate of Rubisco activity-limited carboxylation at 25°C |
---|
246 | !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex |
---|
247 | !$OMP THREADPRIVATE(Vcmax25) |
---|
248 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: arJV !! a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio (mu mol e- (mu mol CO2)-1) |
---|
249 | !$OMP THREADPRIVATE(arJV) |
---|
250 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: brJV !! b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio (mu mol e- (mu mol CO2)-1) |
---|
251 | !$OMP THREADPRIVATE(brJV) |
---|
252 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25 !! MichaelisâMenten constant of Rubisco for CO2 at 25°C (ubar) |
---|
253 | !$OMP THREADPRIVATE(KmC25) |
---|
254 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25 !! MichaelisâMenten constant of Rubisco for O2 at 25°C (ubar) |
---|
255 | !$OMP THREADPRIVATE(KmO25) |
---|
256 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Sco25 !! Relative CO2 /O2 specificity factor for Rubisco at 25ðC (bar bar-1) |
---|
257 | !$OMP THREADPRIVATE(Sco25) |
---|
258 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25 !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar) |
---|
259 | !$OMP THREADPRIVATE(gamma_star25) |
---|
260 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gm25 !! Mesophyll diffusion conductance at 25°C (mol mâ2 sâ1 barâ1) |
---|
261 | !$OMP THREADPRIVATE(gm25) |
---|
262 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a1 !! Empirical factor involved in the calculation of fvpd (-) |
---|
263 | !$OMP THREADPRIVATE(a1) |
---|
264 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b1 !! Empirical factor involved in the calculation of fvpd (-) |
---|
265 | !$OMP THREADPRIVATE(b1) |
---|
266 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: g0 !! Residual stomatal conductance when irradiance approaches zero (mol mâ2 sâ1 barâ1) |
---|
267 | !$OMP THREADPRIVATE(g0) |
---|
268 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_protons !! Number of protons required to produce one ATP (mol mol-1) |
---|
269 | !$OMP THREADPRIVATE(h_protons) |
---|
270 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpsir !! Fraction of PSII eâ transport rate partitioned to the C4 cycle (-) |
---|
271 | !$OMP THREADPRIVATE(fpsir) |
---|
272 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fQ !! Fraction of electrons at reduced plastoquinone that follow the Q-cycle (-) - Values for C3 platns are not used |
---|
273 | !$OMP THREADPRIVATE(fQ) |
---|
274 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpseudo !! Fraction of electrons at PSI that follow pseudocyclic transport (-) - Values for C3 platns are not used |
---|
275 | !$OMP THREADPRIVATE(fpseudo) |
---|
276 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kp !! Initial carboxylation efficiency of the PEP carboxylase (mol mâ2 sâ1 barâ1) |
---|
277 | !$OMP THREADPRIVATE(kp) |
---|
278 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha !! Fraction of PSII activity in the bundle sheath (-) |
---|
279 | !$OMP THREADPRIVATE(alpha) |
---|
280 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gbs !! Bundle-sheath conductance (mol mâ2 sâ1 barâ1) |
---|
281 | !$OMP THREADPRIVATE(gbs) |
---|
282 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: theta !! Convexity factor for response of J to irradiance (-) |
---|
283 | !$OMP THREADPRIVATE(theta) |
---|
284 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_LL !! Conversion efficiency of absorbed light into J at strictly limiting light (mol eâ (mol photon)â1) |
---|
285 | !$OMP THREADPRIVATE(alpha_LL) |
---|
286 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_vcmax !! Stress on vcmax |
---|
287 | !$OMP THREADPRIVATE(stress_vcmax) |
---|
288 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gs !! Stress on vcmax |
---|
289 | !$OMP THREADPRIVATE(stress_gs) |
---|
290 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gm !! Stress on vcmax |
---|
291 | !$OMP THREADPRIVATE(stress_gm) |
---|
292 | |
---|
293 | !- |
---|
294 | ! 2. Stomate |
---|
295 | !- |
---|
296 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff !! extinction coefficient of the Monsi&Saeki relationship (1953) |
---|
297 | !! (unitless) |
---|
298 | !$OMP THREADPRIVATE(ext_coeff) |
---|
299 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff_vegetfrac !! extinction coefficient used for the calculation of the |
---|
300 | !! bare soil fraction (unitless) |
---|
301 | !$OMP THREADPRIVATE(ext_coeff_vegetfrac) |
---|
302 | |
---|
303 | |
---|
304 | ! |
---|
305 | ! ALLOCATION (stomate) |
---|
306 | ! |
---|
307 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: R0 !! Default root allocation (0-1, unitless) |
---|
308 | !$OMP THREADPRIVATE(R0) |
---|
309 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0 !! Default sapwood allocation (0-1, unitless) |
---|
310 | !$OMP THREADPRIVATE(S0) |
---|
311 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0 !! Default leaf allocation (0-1, unitless) |
---|
312 | !$OMP THREADPRIVATE(L0) |
---|
313 | |
---|
314 | |
---|
315 | ! |
---|
316 | ! RESPIRATION (stomate) |
---|
317 | ! |
---|
318 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp !! fraction of GPP which is lost as growth respiration |
---|
319 | |
---|
320 | !$OMP THREADPRIVATE(frac_growthresp) |
---|
321 | |
---|
322 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope !! slope of maintenance respiration coefficient |
---|
323 | !! (1/K, 1/K^2, 1/K^3), used in the code |
---|
324 | !$OMP THREADPRIVATE(maint_resp_slope) |
---|
325 | |
---|
326 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c !! slope of maintenance respiration coefficient (1/K), |
---|
327 | !! constant c of aT^2+bT+c , tabulated |
---|
328 | !$OMP THREADPRIVATE(maint_resp_slope_c) |
---|
329 | |
---|
330 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b !! slope of maintenance respiration coefficient (1/K), |
---|
331 | !! constant b of aT^2+bT+c , tabulated |
---|
332 | !$OMP THREADPRIVATE(maint_resp_slope_b) |
---|
333 | |
---|
334 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a !! slope of maintenance respiration coefficient (1/K), |
---|
335 | !! constant a of aT^2+bT+c , tabulated |
---|
336 | !$OMP THREADPRIVATE(maint_resp_slope_a) |
---|
337 | |
---|
338 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: coeff_maint_zero !! maintenance respiration coefficient at 0 deg C, |
---|
339 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
340 | !$OMP THREADPRIVATE(coeff_maint_zero) |
---|
341 | |
---|
342 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_leaf !! maintenance respiration coefficient at 0 deg C, |
---|
343 | !! for leaves, tabulated |
---|
344 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
345 | !$OMP THREADPRIVATE(cm_zero_leaf) |
---|
346 | |
---|
347 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapabove !! maintenance respiration coefficient at 0 deg C, |
---|
348 | !! for sapwood above, tabulated |
---|
349 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
350 | !$OMP THREADPRIVATE(cm_zero_sapabove) |
---|
351 | |
---|
352 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapbelow !! maintenance respiration coefficient at 0 deg C, |
---|
353 | !! for sapwood below, tabulated |
---|
354 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
355 | !$OMP THREADPRIVATE(cm_zero_sapbelow) |
---|
356 | |
---|
357 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartabove !! maintenance respiration coefficient at 0 deg C |
---|
358 | !! for heartwood above, tabulated |
---|
359 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
360 | !$OMP THREADPRIVATE(cm_zero_heartabove) |
---|
361 | |
---|
362 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartbelow !! maintenance respiration coefficient at 0 deg C, |
---|
363 | !! for heartwood below, tabulated |
---|
364 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
365 | !$OMP THREADPRIVATE(cm_zero_heartbelow) |
---|
366 | |
---|
367 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_root !! maintenance respiration coefficient at 0 deg C, |
---|
368 | !! for roots, tabulated |
---|
369 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
370 | !$OMP THREADPRIVATE(cm_zero_root) |
---|
371 | |
---|
372 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_fruit !! maintenance respiration coefficient at 0 deg C, |
---|
373 | !! for fruits, tabulated |
---|
374 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
375 | !$OMP THREADPRIVATE(cm_zero_fruit) |
---|
376 | |
---|
377 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_carbres !! maintenance respiration coefficient at 0 deg C, |
---|
378 | !! for carbohydrate reserve, tabulated |
---|
379 | !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex |
---|
380 | !$OMP THREADPRIVATE(cm_zero_carbres) |
---|
381 | |
---|
382 | |
---|
383 | ! |
---|
384 | ! FIRE (stomate) |
---|
385 | ! |
---|
386 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam !! flamability : critical fraction of water holding |
---|
387 | !! capacity (0-1, unitless) |
---|
388 | !$OMP THREADPRIVATE(flam) |
---|
389 | |
---|
390 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist !! fire resistance (0-1, unitless) |
---|
391 | !$OMP THREADPRIVATE(resist) |
---|
392 | |
---|
393 | |
---|
394 | ! |
---|
395 | ! FLUX - LUC (Land Use Change) |
---|
396 | ! |
---|
397 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1 !! Coeff of biomass export for the year (unitless) |
---|
398 | !$OMP THREADPRIVATE(coeff_lcchange_1) |
---|
399 | |
---|
400 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10 !! Coeff of biomass export for the decade (unitless) |
---|
401 | !$OMP THREADPRIVATE(coeff_lcchange_10) |
---|
402 | |
---|
403 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless) |
---|
404 | !$OMP THREADPRIVATE(coeff_lcchange_100) |
---|
405 | |
---|
406 | |
---|
407 | ! |
---|
408 | ! PHENOLOGY |
---|
409 | ! |
---|
410 | !- |
---|
411 | ! 1. Stomate |
---|
412 | !- |
---|
413 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy !! threshold of LAI below which plant uses carbohydrate reserves |
---|
414 | !$OMP THREADPRIVATE(lai_max_to_happy) |
---|
415 | |
---|
416 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex |
---|
417 | !$OMP THREADPRIVATE(lai_max) |
---|
418 | |
---|
419 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type !! type of phenology (0-4, unitless) |
---|
420 | !! 0=bare ground 1=evergreen, 2=summergreen, |
---|
421 | !! 3=raingreen, 4=perennial |
---|
422 | !! For the moment, the bare ground phenotype is not managed, |
---|
423 | !! so it is considered as "evergreen" |
---|
424 | !$OMP THREADPRIVATE(pheno_type) |
---|
425 | |
---|
426 | !- |
---|
427 | ! 2. Leaf Onset |
---|
428 | !- |
---|
429 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit !! critical gdd,tabulated (C), used in the code |
---|
430 | !$OMP THREADPRIVATE(pheno_gdd_crit) |
---|
431 | |
---|
432 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c !! critical gdd,tabulated (C), |
---|
433 | !! constant c of aT^2+bT+c (unitless) |
---|
434 | !$OMP THREADPRIVATE(pheno_gdd_crit_c) |
---|
435 | |
---|
436 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b !! critical gdd,tabulated (C), |
---|
437 | !! constant b of aT^2+bT+c (unitless) |
---|
438 | !$OMP THREADPRIVATE(pheno_gdd_crit_b) |
---|
439 | |
---|
440 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a !! critical gdd,tabulated (C), |
---|
441 | !! constant a of aT^2+bT+c (unitless) |
---|
442 | !$OMP THREADPRIVATE(pheno_gdd_crit_a) |
---|
443 | |
---|
444 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C) |
---|
445 | !$OMP THREADPRIVATE(pheno_moigdd_t_crit) |
---|
446 | |
---|
447 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit !! critical ngd,tabulated. Threshold -5 degrees (days) |
---|
448 | !$OMP THREADPRIVATE(ngd_crit) |
---|
449 | |
---|
450 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp !! critical temperature for the ncd vs. gdd function |
---|
451 | !! in phenology (C) |
---|
452 | !$OMP THREADPRIVATE(ncdgdd_temp) |
---|
453 | |
---|
454 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac !! critical humidity (relative to min/max) for phenology |
---|
455 | !! (0-1, unitless) |
---|
456 | !$OMP THREADPRIVATE(hum_frac) |
---|
457 | |
---|
458 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time !! minimum time elapsed since moisture minimum (days) |
---|
459 | !$OMP THREADPRIVATE(hum_min_time) |
---|
460 | |
---|
461 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap !! sapwood -> heartwood conversion time (days) |
---|
462 | !$OMP THREADPRIVATE(tau_sap) |
---|
463 | |
---|
464 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit !! fruit lifetime (days) |
---|
465 | !$OMP THREADPRIVATE(tau_fruit) |
---|
466 | |
---|
467 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit !! time to attain the initial foliage using the carbohydrate reserve |
---|
468 | !$OMP THREADPRIVATE(tau_leafinit) |
---|
469 | |
---|
470 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil !! fraction of primary leaf and root allocation put |
---|
471 | !! into reserve (0-1, unitless) |
---|
472 | !$OMP THREADPRIVATE(ecureuil) |
---|
473 | |
---|
474 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
475 | !$OMP THREADPRIVATE(alloc_min) |
---|
476 | |
---|
477 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
478 | !$OMP THREADPRIVATE(alloc_max) |
---|
479 | |
---|
480 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
481 | !$OMP THREADPRIVATE(demi_alloc) |
---|
482 | |
---|
483 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaflife_tab !! leaf longevity, tabulated (??units??) |
---|
484 | !$OMP THREADPRIVATE(leaflife_tab) |
---|
485 | |
---|
486 | !- |
---|
487 | ! 3. Senescence |
---|
488 | !- |
---|
489 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall !! length of death of leaves,tabulated (days) |
---|
490 | !$OMP THREADPRIVATE(leaffall) |
---|
491 | |
---|
492 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leafagecrit !! critical leaf age,tabulated (days) |
---|
493 | !$OMP THREADPRIVATE(leafagecrit) |
---|
494 | |
---|
495 | CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type !! type of senescence,tabulated (unitless) |
---|
496 | !! List of avaible types of senescence : |
---|
497 | !! 'cold ', 'dry ', 'mixed ', 'none ' |
---|
498 | !$OMP THREADPRIVATE(senescence_type) |
---|
499 | |
---|
500 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum !! critical relative moisture availability for senescence |
---|
501 | !! (0-1, unitless) |
---|
502 | !$OMP THREADPRIVATE(senescence_hum) |
---|
503 | |
---|
504 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum !! relative moisture availability above which there is |
---|
505 | !! no humidity-related senescence (0-1, unitless) |
---|
506 | !$OMP THREADPRIVATE(nosenescence_hum) |
---|
507 | |
---|
508 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time !! maximum turnover time for grasses (days) |
---|
509 | !$OMP THREADPRIVATE(max_turnover_time) |
---|
510 | |
---|
511 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time !! minimum turnover time for grasses (days) |
---|
512 | !$OMP THREADPRIVATE(min_turnover_time) |
---|
513 | |
---|
514 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence !! minimum leaf age to allow senescence g (days) |
---|
515 | !$OMP THREADPRIVATE(min_leaf_age_for_senescence) |
---|
516 | |
---|
517 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp !! critical temperature for senescence (C), |
---|
518 | !! used in the code |
---|
519 | !$OMP THREADPRIVATE(senescence_temp) |
---|
520 | |
---|
521 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c !! critical temperature for senescence (C), |
---|
522 | !! constant c of aT^2+bT+c , tabulated (unitless) |
---|
523 | !$OMP THREADPRIVATE(senescence_temp_c) |
---|
524 | |
---|
525 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b !! critical temperature for senescence (C), |
---|
526 | !! constant b of aT^2+bT+c , tabulated (unitless) |
---|
527 | !$OMP THREADPRIVATE(senescence_temp_b) |
---|
528 | |
---|
529 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a !! critical temperature for senescence (C), |
---|
530 | !! constant a of aT^2+bT+c , tabulated (unitless) |
---|
531 | !$OMP THREADPRIVATE(senescence_temp_a) |
---|
532 | |
---|
533 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence !! minimum gdd to allow senescence of crops (days) |
---|
534 | !$OMP THREADPRIVATE(gdd_senescence) |
---|
535 | |
---|
536 | ! |
---|
537 | ! DGVM |
---|
538 | ! |
---|
539 | |
---|
540 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time !! residence time of trees (y) |
---|
541 | !$OMP THREADPRIVATE(residence_time) |
---|
542 | |
---|
543 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit !! critical tmin, tabulated (C) |
---|
544 | !$OMP THREADPRIVATE(tmin_crit) |
---|
545 | |
---|
546 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit !! critical tcm, tabulated (C) |
---|
547 | !$OMP THREADPRIVATE(tcm_crit) |
---|
548 | |
---|
549 | ! |
---|
550 | ! Biogenic Volatile Organic Compounds |
---|
551 | ! |
---|
552 | |
---|
553 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene !! Isoprene emission factor |
---|
554 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
555 | !$OMP THREADPRIVATE(em_factor_isoprene) |
---|
556 | |
---|
557 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene !! Monoterpene emission factor |
---|
558 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
559 | !$OMP THREADPRIVATE(em_factor_monoterpene) |
---|
560 | |
---|
561 | REAL(r_std), SAVE :: LDF_mono !! monoterpenes fraction dependancy to light |
---|
562 | !$OMP THREADPRIVATE(LDF_mono) |
---|
563 | REAL(r_std), SAVE :: LDF_sesq !! sesquiterpenes fraction dependancy to light |
---|
564 | !$OMP THREADPRIVATE(LDF_sesq) |
---|
565 | REAL(r_std), SAVE :: LDF_meth !! methanol fraction dependancy to light |
---|
566 | !$OMP THREADPRIVATE(LDF_meth) |
---|
567 | REAL(r_std), SAVE :: LDF_acet !! acetone fraction dependancy to light |
---|
568 | !$OMP THREADPRIVATE(LDF_acet) |
---|
569 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene !! Alfa pinene emission factor |
---|
570 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
571 | !$OMP THREADPRIVATE(em_factor_apinene) |
---|
572 | |
---|
573 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene !! Beta pinene emission factor |
---|
574 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
575 | !$OMP THREADPRIVATE(em_factor_bpinene) |
---|
576 | |
---|
577 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene !! Limonene emission factor |
---|
578 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
579 | !$OMP THREADPRIVATE(em_factor_limonene) |
---|
580 | |
---|
581 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene !! Myrcene emission factor |
---|
582 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
583 | !$OMP THREADPRIVATE(em_factor_myrcene) |
---|
584 | |
---|
585 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene !! Sabinene emission factor |
---|
586 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
587 | !$OMP THREADPRIVATE(em_factor_sabinene) |
---|
588 | |
---|
589 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene !! Camphene emission factor |
---|
590 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
591 | !$OMP THREADPRIVATE(em_factor_camphene) |
---|
592 | |
---|
593 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene !! 3-carene emission factor |
---|
594 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
595 | !$OMP THREADPRIVATE(em_factor_3carene) |
---|
596 | |
---|
597 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene !! T-beta-ocimene emission factor |
---|
598 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
599 | !$OMP THREADPRIVATE(em_factor_tbocimene) |
---|
600 | |
---|
601 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot !! Other monoterpenes emission factor |
---|
602 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
603 | !$OMP THREADPRIVATE(em_factor_othermonot) |
---|
604 | |
---|
605 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp !! Sesquiterpene emission factor |
---|
606 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
607 | !$OMP THREADPRIVATE(em_factor_sesquiterp) |
---|
608 | |
---|
609 | REAL(r_std), SAVE :: beta_mono !! Monoterpenes temperature dependency coefficient |
---|
610 | !$OMP THREADPRIVATE(beta_mono) |
---|
611 | REAL(r_std), SAVE :: beta_sesq !! Sesquiterpenes temperature dependency coefficient |
---|
612 | !$OMP THREADPRIVATE(beta_sesq) |
---|
613 | REAL(r_std), SAVE :: beta_meth !! Methanol temperature dependency coefficient |
---|
614 | !$OMP THREADPRIVATE(beta_meth) |
---|
615 | REAL(r_std), SAVE :: beta_acet !! Acetone temperature dependency coefficient |
---|
616 | !$OMP THREADPRIVATE(beta_acet) |
---|
617 | REAL(r_std), SAVE :: beta_oxyVOC !! Other oxygenated BVOC temperature dependency coefficient |
---|
618 | !$OMP THREADPRIVATE(beta_oxyVOC) |
---|
619 | |
---|
620 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC !! ORVOC emissions factor |
---|
621 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
622 | !$OMP THREADPRIVATE(em_factor_ORVOC) |
---|
623 | |
---|
624 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC !! OVOC emissions factor |
---|
625 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
626 | !$OMP THREADPRIVATE(em_factor_OVOC) |
---|
627 | |
---|
628 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO !! MBO emissions factor |
---|
629 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
630 | !$OMP THREADPRIVATE(em_factor_MBO) |
---|
631 | |
---|
632 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol !! Methanol emissions factor |
---|
633 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
634 | !$OMP THREADPRIVATE(em_factor_methanol) |
---|
635 | |
---|
636 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone !! Acetone emissions factor |
---|
637 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
638 | !$OMP THREADPRIVATE(em_factor_acetone) |
---|
639 | |
---|
640 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal !! Acetaldehyde emissions factor |
---|
641 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
642 | !$OMP THREADPRIVATE(em_factor_acetal) |
---|
643 | |
---|
644 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal !! Formaldehyde emissions factor |
---|
645 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
646 | !$OMP THREADPRIVATE(em_factor_formal) |
---|
647 | |
---|
648 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic !! Acetic Acid emissions factor |
---|
649 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
650 | !$OMP THREADPRIVATE(em_factor_acetic) |
---|
651 | |
---|
652 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic !! Formic Acid emissions factor |
---|
653 | !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex |
---|
654 | !$OMP THREADPRIVATE(em_factor_formic) |
---|
655 | |
---|
656 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet !! NOx emissions factor soil emissions and |
---|
657 | !! exponential dependancy factor for wet soils |
---|
658 | !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex |
---|
659 | !$OMP THREADPRIVATE(em_factor_no_wet) |
---|
660 | |
---|
661 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry !! NOx emissions factor soil emissions and |
---|
662 | !! exponential dependancy factor for dry soils |
---|
663 | !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex |
---|
664 | !$OMP THREADPRIVATE(em_factor_no_dry) |
---|
665 | |
---|
666 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch !! Larcher 1991 SAI/LAI ratio (unitless) |
---|
667 | !$OMP THREADPRIVATE(Larch) |
---|
668 | |
---|
669 | ! |
---|
670 | ! INTERNAL PARAMETERS USED IN STOMATE_DATA |
---|
671 | ! |
---|
672 | |
---|
673 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin !! Initial lai for trees/grass |
---|
674 | !! @tex $(m^2.m^{-2})$ @endtex |
---|
675 | !$OMP THREADPRIVATE(lai_initmin) |
---|
676 | |
---|
677 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl !! sapling biomass @tex $(gC.ind^{-1})$ @endtex |
---|
678 | !$OMP THREADPRIVATE(bm_sapl) |
---|
679 | |
---|
680 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate !! migration speed @tex $(m.year^{-1})$ @endtex |
---|
681 | !$OMP THREADPRIVATE(migrate) |
---|
682 | |
---|
683 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia !! maximum stem diameter from which on crown area no longer |
---|
684 | !! increases (m) |
---|
685 | !$OMP THREADPRIVATE(maxdia) |
---|
686 | |
---|
687 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl !! crown of tree when sapling @tex $(m^2$)$ @endtex |
---|
688 | !$OMP THREADPRIVATE(cn_sapl) |
---|
689 | |
---|
690 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst !! time constant for leaf age discretisation (days) |
---|
691 | !$OMP THREADPRIVATE(leaf_timecst) |
---|
692 | |
---|
693 | |
---|
694 | END MODULE pft_parameters_var |
---|