source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parameters/pft_parameters_var.f90 @ 7852

Last change on this file since 7852 was 7555, checked in by sebastiaan.luyssaert, 2 years ago

Contributes to ticket #837. Simplified forest management for young stands a bit

  • Property svn:keywords set to Date Revision
File size: 86.8 KB
Line 
1! =================================================================================================================================
2! MODULE       : pft_parameters_var
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.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
27MODULE 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(:) :: is_temperate               !! Is PFT temperate ? (true/false)
77!$OMP THREADPRIVATE(is_temperate)
78   
79  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_boreal                  !! Is PFT boreal ? (true/false)
80!$OMP THREADPRIVATE(is_boreal)
81
82  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: natural                    !! natural? (true/false)
83!$OMP THREADPRIVATE(natural)
84
85  CHARACTER(len=5), ALLOCATABLE, SAVE, DIMENSION(:) :: type_of_lai       !! Type of behaviour of the LAI evolution algorithm
86                                                                         !! for each vegetation type.
87                                                                         !! Value of type_of_lai, one for each vegetation type :
88                                                                         !! mean or interp
89!$OMP THREADPRIVATE(type_of_lai)
90
91  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: veget_ori_fixed_test_1 !! Value for veget_ori for tests in 0-dim simulations
92                                                                         !! (0-1, unitless)
93!$OMP THREADPRIVATE(veget_ori_fixed_test_1)
94
95  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimax                !! laimax for maximum lai see also type of lai
96                                                                         !! interpolation
97                                                                         !! @tex $(m^2.m^{-2})$ @endtex
98!$OMP THREADPRIVATE(llaimax)
99
100  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimin                !! laimin for minimum lai see also type of lai
101                                                                         !! interpolation
102                                                                         !! @tex $(m^2.m^{-2})$ @endtex
103!$OMP THREADPRIVATE(llaimin)
104
105  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_presc           !! prescribed height of vegetation.(m)
106                                                                         !! Value for height_presc : one for each vegetation type
107!$OMP THREADPRIVATE(height_presc)
108
109  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: z0_over_height        !! Factor to calculate roughness height from
110                                                                        !! vegetation height (unitless)   
111!$OMP THREADPRIVATE(z0_over_height)
112
113  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ratio_z0m_z0h         !! Ratio between z0m and z0h
114!$OMP THREADPRIVATE(ratio_z0m_z0h)
115
116  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) ::  rveg_pft              !! Potentiometer to set vegetation resistance (unitless)
117                                                                         !! Nathalie on March 28th, 2006 - from Fred Hourdin,
118!$OMP THREADPRIVATE(rveg_pft)
119
120  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sla                    !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
121!$OMP THREADPRIVATE(sla)
122
123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: slainit                !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
124!$OMP THREADPRIVATE(slainit)
125
126  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: availability_fact      !! calculate dynamic mortality in lpj_gap
127!$OMP THREADPRIVATE(availability_fact)
128
129  !
130  ! EVAPOTRANSPIRATION (sechiba)
131  !
132  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const          !! Structural resistance.
133                                                                         !! Value for rstruct_const : one for each vegetation type
134                                                                         !! @tex $(s.m^{-1})$ @endtex
135!$OMP THREADPRIVATE(rstruct_const)
136
137  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero                  !! A vegetation dependent constant used in the calculation
138                                                                         !! of the surface resistance.
139                                                                         !! Value for kzero one for each vegetation type
140                                                                         !! @tex $(kg.m^2.s^{-1})$ @endtex
141!$OMP THREADPRIVATE(kzero)
142
143  !
144  ! WATER (sechiba)
145  !
146  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wmax_veg               !! Volumetric available soil water capacity in each PFT
147                                                                         !! @tex $(kg.m^{-3} of soil)$ @endtex
148!$OMP THREADPRIVATE(wmax_veg)
149
150  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: humcste                !! Root profile description for the different vegetation types.
151                                                                         !! These are the factor in the exponential which gets
152                                                                         !! the root density as a function of depth
153                                                                         !! @tex $(m^{-1})$ @endtex
154!$OMP THREADPRIVATE(humcste)
155 
156  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_root_depth         !! Maximum rooting depth for the PFT irrespective of other
157                                                                         !! constraints from the active layer thickness @tex $(m)$ @endtex
158!$OMP THREADPRIVATE(max_root_depth)
159
160  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft     !! Percent by PFT of precip that is not intercepted by the canopy
161!$OMP THREADPRIVATE(throughfall_by_pft)
162
163  !
164  ! ALBEDO (sechiba)
165  !
166  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_vis         !! Minimum snow albedo value for each vegetation type
167                                                                         !! after aging (dirty old snow), visible albedo (unitless)
168                                                                         !! Source : Values are from the Thesis of S. Chalita (1992)
169!$OMP THREADPRIVATE(snowa_aged_vis)
170
171  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_nir         !! Minimum snow albedo value for each vegetation type
172                                                                         !! after aging (dirty old snow), near infrared albedo (unitless)
173                                                                         !! Source : Values are from the Thesis of S. Chalita (1992)
174!$OMP THREADPRIVATE(snowa_aged_nir)
175
176  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_vis          !! Decay rate of snow albedo value for each vegetation type
177                                                                         !! as it will be used in condveg_snow, visible albedo (unitless)
178                                                                         !! Source : Values are from the Thesis of S. Chalita (1992)
179!$OMP THREADPRIVATE(snowa_dec_vis)
180
181  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_nir          !! Decay rate of snow albedo value for each vegetation type
182                                                                         !! as it will be used in condveg_snow, near infrared albedo (unitless)
183                                                                         !! Source : Values are from the Thesis of S. Chalita (1992)
184!$OMP THREADPRIVATE(snowa_dec_nir)
185
186  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis           !! leaf albedo of vegetation type, visible albedo (unitless)
187!$OMP THREADPRIVATE(alb_leaf_vis)
188
189  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir           !! leaf albedo of vegetation type, near infrared albedo (unitless)
190!$OMP THREADPRIVATE(alb_leaf_nir)
191
192   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: leaf_ssa            !! leaf single scattering albedo of all
193!$OMP THREADPRIVATE(leaf_ssa)
194  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: leaf_psd             !! leaf prefered scattering direction of all
195                                                                         !! vegetation types and spectra (unitless)
196!$OMP THREADPRIVATE(leaf_psd)
197
198  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: bgd_reflectance      !! background reflectance of all vegetation types and spectra (unitless)
199!$OMP THREADPRIVATE(bgd_reflectance)
200
201
202
203  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_to_shoot_clumping !! The clumping factor for leaves to shoots in the
204                                                                         !! effective LAI calculation...notice this should be
205                                                                         !! equal to unity for grasslands/croplands
206!$OMP THREADPRIVATE(leaf_to_shoot_clumping)
207
208
209! NOTE: this next variable originally was a plant-to-stand clumping factor to be used
210! in describing how grasses and crops clump together at the plant level (but not trees,
211! as their plant-to-stand clumping is calculated directly) to calculate abledo. However, we
212! get the effective spectral parameters for the albedo calculation from inverting satelite data,
213! which includes all clumping.  Therefore we do not wish to account for this effect twice.
214! What will be incorrect about our grassland and crop albedo is the lack of management options
215! for these PFTs in ORCHIDEE, which will lead to LAI values which are wrong.  Thus we
216! will include an LAI correction factor in the calculation of the effective LAI which
217! allows us to compensate for this via tuning.
218  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_correction_factor  !! see note above
219!$OMP THREADPRIVATE(lai_correction_factor)
220
221  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_level_sep          !! This is used in determining the levels
222                                                                         !! for photosynthesis.  This is the thinnest
223                                                                         !! that the levels are allowed to be, in
224                                                                         !! vertical thickness.
225                                                                         !! @tex $(m)$ @endtex
226!$OMP THREADPRIVATE(min_level_sep)
227
228  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_top                !!Diffuco.f90 calculates the stomatal conductance of the
229                                                                         !! top layer of the canopy. Because the top layer can contain
230                                                                         !! different amounts of LAI depending on the crown diameter
231                                                                         !! we had to define top layer in terms of the LAI it contains.
232                                                                         !! stomatal conductance in the top layer contributes to the
233                                                                         !! transpiration (m2 m-2). Arbitrary values.
234!$OMP THREADPRIVATE(lai_top)
235
236  !
237  ! SOIL - VEGETATION
238  !
239  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg      !! Table which contains the correlation between the soil
240                                                                        !! types and vegetation type. Two modes exist :
241                                                                        !! 1) pref_soil_veg = 0 then we have an equidistribution
242                                                                        !!    of vegetation on soil types
243                                                                        !! 2) Else for each pft the prefered soil type is given :
244                                                                        !!    1=sand, 2=loan, 3=clay
245                                                                        !! This variable is initialized in slowproc.(1-3, unitless)
246!$OMP THREADPRIVATE(pref_soil_veg)
247
248  !
249  ! PHOTOSYNTHESIS
250  !
251  !-
252  ! 1. CO2
253  !-
254  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4             !! flag for C4 vegetation types (true/false)
255!$OMP THREADPRIVATE(is_c4)
256
257  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix     !! values used for vcmax when STOMATE is not activated
258                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
259!$OMP THREADPRIVATE(vcmax_fix)
260
261  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation (unitless)
262!$OMP THREADPRIVATE(downregulation_co2_coeff)
263
264  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC         !! Energy of activation for KmC (J mol-1)
265!$OMP THREADPRIVATE(E_KmC)                                                               
266  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO         !! Energy of activation for KmO (J mol-1)
267!$OMP THREADPRIVATE(E_KmO)         
268  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Sco         !! Energy of activation for Sco (J mol-1)
269!$OMP THREADPRIVATE(E_Sco)
270  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star  !! Energy of activation for gamma_star (J mol-1)
271!$OMP THREADPRIVATE(E_gamma_star)   
272  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax       !! Energy of activation for Vcmax (J mol-1)
273!$OMP THREADPRIVATE(E_Vcmax)                                                             
274  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax        !! Energy of activation for Jmax (J mol-1)
275!$OMP THREADPRIVATE(E_Jmax)
276  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)
277!$OMP THREADPRIVATE(aSV)   
278  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)
279!$OMP THREADPRIVATE(bSV)
280  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min   !! minimum photosynthesis temperature (deg C)
281!$OMP THREADPRIVATE(tphoto_min)
282  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max   !! maximum photosynthesis temperature (deg C)
283!$OMP THREADPRIVATE(tphoto_max)
284  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)
285!$OMP THREADPRIVATE(aSJ)   
286  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)
287!$OMP THREADPRIVATE(bSJ)   
288  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax       !! Energy of deactivation for Vcmax (J mol-1)
289!$OMP THREADPRIVATE(D_Vcmax)                     
290  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax        !! Energy of deactivation for Jmax (J mol-1)
291!$OMP THREADPRIVATE(D_Jmax)                           
292
293  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gm          !! Energy of activation for gm (J mol-1)
294!$OMP THREADPRIVATE(E_gm)                                       
295  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S_gm          !! Entropy term for gm (J K-1 mol-1)
296!$OMP THREADPRIVATE(S_gm)                                       
297  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_gm          !! Energy of deactivation for gm (J mol-1)
298!$OMP THREADPRIVATE(D_gm)                                       
299         
300  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd          !! Energy of activation for Rd (J mol-1)
301!$OMP THREADPRIVATE(E_Rd)                                     
302  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25       !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
303                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
304!$OMP THREADPRIVATE(Vcmax25)
305  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)
306!$OMP THREADPRIVATE(arJV)
307  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)
308!$OMP THREADPRIVATE(brJV)
309  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25         !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
310!$OMP THREADPRIVATE(KmC25)                                     
311  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25         !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
312!$OMP THREADPRIVATE(KmO25)     
313  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Sco25         !! Relative CO2 /O2 specificity factor for Rubisco at 25°C (bar bar-1)
314!$OMP THREADPRIVATE(Sco25)           
315  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25  !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
316!$OMP THREADPRIVATE(gamma_star25)   
317  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gm25          !! Mesophyll diffusion conductance at 25°C (mol mâ2 sâ1 barâ1)
318!$OMP THREADPRIVATE(gm25)   
319  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a1            !! Empirical factor involved in the calculation of fvpd (-)
320!$OMP THREADPRIVATE(a1)                                       
321  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b1            !! Empirical factor involved in the calculation of fvpd (-)
322!$OMP THREADPRIVATE(b1)                                       
323  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: g0            !! Residual stomatal conductance when irradiance approaches zero (mol m−2 s−1 bar−1)
324!$OMP THREADPRIVATE(g0)                                       
325  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_protons     !! Number of protons required to produce one ATP (mol mol-1)
326!$OMP THREADPRIVATE(h_protons)                                 
327  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpsir         !! Fraction of PSII e− transport rate partitioned to the C4 cycle (-)
328!$OMP THREADPRIVATE(fpsir)                                         
329  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
330!$OMP THREADPRIVATE(fQ)                                       
331  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpseudo       !! Fraction of electrons at PSI that follow  pseudocyclic transport (-) - Values for C3 platns are not used
332!$OMP THREADPRIVATE(fpseudo)                                   
333  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kp            !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
334!$OMP THREADPRIVATE(kp)                                       
335  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha         !! Fraction of PSII activity in the bundle sheath (-)
336!$OMP THREADPRIVATE(alpha)                                     
337  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gbs           !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
338!$OMP THREADPRIVATE(gbs)                                       
339  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: theta         !! Convexity factor for response of J to irradiance (-)
340!$OMP THREADPRIVATE(theta)                                     
341  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_LL      !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
342!$OMP THREADPRIVATE(alpha_LL)
343  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_vcmax  !! Stress on vcmax
344!$OMP THREADPRIVATE(stress_vcmax)
345  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gs     !! Stress on vcmax
346!$OMP THREADPRIVATE(stress_gs)
347  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gm     !! Stress on vcmax
348!$OMP THREADPRIVATE(stress_gm)
349
350  !-
351  ! 2. Stomate
352  !-
353  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff     !! extinction coefficient of the Monsi&Saeki relationship (1953)
354                                                                !! (unitless)
355!$OMP THREADPRIVATE(ext_coeff)
356  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff_vegetfrac     !! extinction coefficient used for the calculation of the
357                                                                !! bare soil fraction (unitless)
358!$OMP THREADPRIVATE(ext_coeff_vegetfrac)
359
360  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff_N   !! extinction coefficient of the leaf N content profile within the canopy
361                                                                !! ((m2[ground]) (m-2[leaf]))
362                                                                !! based on Dewar et al. (2012, value of 0.18), on Carswell et al. (2000, value of 0.11 used in OCN)
363!$OMP THREADPRIVATE(ext_coeff_N)
364  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nue_opt       !! Nitrogen use efficiency of Vcmax
365                                                                !! ((mumol[CO2] s-1) (gN[leaf])-1)
366                                                                !! based on the work of Kattge et al. (2009, GCB)
367!$OMP THREADPRIVATE(nue_opt)
368  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: vmax_uptake !! Vmax of nitrogen uptake by plants
369                                                                !! for Ammonium (ind.1) and Nitrate (ind.2)
370                                                                !! (in umol (g DryWeight_root)-1 h-1)
371                                                                !! from  Kronzucker et al. (1995, 1996)
372!$OMP THREADPRIVATE(vmax_uptake)
373
374
375  !
376  ! RESPIRATION (stomate)
377  !
378  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp  !! fraction of GPP which is lost as growth respiration
379
380!$OMP THREADPRIVATE(frac_growthresp)
381
382  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_maint_init    !! maintenance respiration coefficient at 10 deg C,
383                                                                      !! @tex $(gC.gN^{-1}.day^{-1})$ @endtex
384!$OMP THREADPRIVATE(coeff_maint_init)
385
386  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tref_maint_resp     !! maintenance respiration Temperature coefficient,
387                                                                      !! @tex $(degC)$ @endtex
388!$OMP THREADPRIVATE(tref_maint_resp)
389
390  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_maint_resp     !! maintenance respiration Temperature coefficient,
391                                                                      !! @tex $(degC)$ @endtex
392!$OMP THREADPRIVATE(tmin_maint_resp)
393
394  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: e0_maint_resp       !! maintenance respiration Temperature coefficient,
395                                                                      !! @tex $(unitless)$ @endtex
396!$OMP THREADPRIVATE(e0_maint_resp)
397
398 
399  !
400  ! ALLOCATION
401  !
402  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tref_labile         !! Growth from labile pool - temperature at which all labile C will be allocated to growth
403                                                                      !! @tex $(degC)$ @endtex
404!$OMP THREADPRIVATE(tref_labile)
405
406  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_labile         !! Growth from labile pool  - temperature above which labile will be allocated to growth
407                                                                      !! @tex $(degC)$ @endtex
408!$OMP THREADPRIVATE(tmin_labile)
409
410  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: e0_labile           !! Growth temperature coefficient - tuned see stomate_growth_fun_all.f90
411                                                                      !! @tex $(unitless)$ @endtex
412!$OMP THREADPRIVATE(e0_labile)
413
414  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: always_labile       !! share of the labile pool that will remain in the labile pool (unitless)
415 
416!$OMP THREADPRIVATE(always_labile)
417
418  !
419  ! FIRE (stomate)
420  !
421  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
422                                                                    !! capacity (0-1, unitless)
423!$OMP THREADPRIVATE(flam)
424
425  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
426!$OMP THREADPRIVATE(resist)
427
428
429  !
430  ! FLUX - LUC (Land Use Change)
431  !
432  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1   !! Coeff of biomass export for the year (unitless)
433!$OMP THREADPRIVATE(coeff_lcchange_1)
434
435  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10  !! Coeff of biomass export for the decade (unitless)
436!$OMP THREADPRIVATE(coeff_lcchange_10)
437
438  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless)
439!$OMP THREADPRIVATE(coeff_lcchange_100)
440 
441  !
442  ! FLUX - LUC (Land Use Change)
443  !
444  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_s   !! Coeff of biomass export for the year (unitless)
445!$OMP THREADPRIVATE(coeff_lcchange_s)
446
447  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_m  !! Coeff of biomass export for the decade (unitless)
448!$OMP THREADPRIVATE(coeff_lcchange_m)
449
450  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_l  !! Coeff of biomass export for the century (unitless)
451!$OMP THREADPRIVATE(coeff_lcchange_l)
452 
453  !
454  ! PHENOLOGY
455  !
456  !-
457  ! 1. Stomate
458  !-
459  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy  !! threshold of LAI below which plant uses carbohydrate reserves
460!$OMP THREADPRIVATE(lai_max_to_happy)
461
462  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
463!$OMP THREADPRIVATE(lai_max)
464
465  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
466                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
467                                                                    !! 3=raingreen,  4=perennial
468                                                                    !! For the moment, the bare ground phenotype is not managed,
469                                                                    !! so it is considered as "evergreen"
470!$OMP THREADPRIVATE(pheno_type)
471
472  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: force_pheno       !! Number of days after the mean
473                                                                    !! doy at which budbreak occurs
474                                                                    !! at which phenology will be forced
475!$OMP THREADPRIVATE(force_pheno)
476  !-
477  ! 2. Leaf Onset
478  !-
479  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
480!$OMP THREADPRIVATE(pheno_gdd_crit)
481
482  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
483                                                                     !! constant c of aT^2+bT+c (unitless)
484!$OMP THREADPRIVATE(pheno_gdd_crit_c)
485
486  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
487                                                                     !! constant b of aT^2+bT+c (unitless)
488!$OMP THREADPRIVATE(pheno_gdd_crit_b)
489
490  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
491                                                                     !! constant a of aT^2+bT+c (unitless)
492!$OMP THREADPRIVATE(pheno_gdd_crit_a)
493
494  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C)
495!$OMP THREADPRIVATE(pheno_moigdd_t_crit)
496
497  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
498!$OMP THREADPRIVATE(ngd_crit)
499
500  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
501                                                                     !! in phenology (C)
502!$OMP THREADPRIVATE(ncdgdd_temp)
503
504  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
505                                                                     !! (0-1, unitless)
506!$OMP THREADPRIVATE(hum_frac)
507
508  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
509!$OMP THREADPRIVATE(hum_min_time)
510
511  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: longevity_sap      !! sapwood -> heartwood conversion time (days)
512!$OMP THREADPRIVATE(longevity_sap)
513
514  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: longevity_leaf     !! leaf turnover (1/years)
515!$OMP THREADPRIVATE(longevity_leaf)
516
517  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_age_crit_tref !! Reference temperature of the PFT (degrees Celsius)
518                                                                     !! Used to calculate the leaf_age_crit as a function of longevity
519!$OMP THREADPRIVATE(leaf_age_crit_tref)
520
521  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_age_crit_coeff1 !! Coeff1 (unitless) to link leaf_age_crit to leaf_age_crit_tref
522!$OMP THREADPRIVATE(leaf_age_crit_coeff1)
523
524  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_age_crit_coeff2 !! Coeff2 (unitless) to link leaf_age_crit to leaf_age_crit_tref
525!$OMP THREADPRIVATE(leaf_age_crit_coeff2)
526
527  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_age_crit_coeff3 !! Coeff3 (unitless) to link leaf_age_crit to leaf_age_crit_tref
528!$OMP THREADPRIVATE(leaf_age_crit_coeff3)
529
530  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: longevity_fruit    !! fruit lifetime (days)
531!$OMP THREADPRIVATE(longevity_fruit)
532
533  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: longevity_root     !! root turnover (1/days)
534!$OMP THREADPRIVATE(longevity_root)
535
536  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
537                                                                     !! into reserve (0-1, unitless)
538!$OMP THREADPRIVATE(ecureuil)
539
540  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
541!$OMP THREADPRIVATE(alloc_min)
542
543  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
544!$OMP THREADPRIVATE(alloc_max)
545
546  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
547!$OMP THREADPRIVATE(demi_alloc)
548
549  !-
550  ! 3. Senescence
551  !-
552  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
553!$OMP THREADPRIVATE(leaffall)
554
555  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: presenescence_ratio   !! The ratio of maintenance respiration to
556                                                                        !! gpp beyond which presenescence stage of
557                                                                        !! plant phenology is declared to begin (0-1, unitless).
558!$OMP THREADPRIVATE(presenescence_ratio)
559
560  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
561                                                                        !! List of avaible types of senescence :
562                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
563!$OMP THREADPRIVATE(senescence_type)
564
565  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
566                                                                        !! (0-1, unitless)
567!$OMP THREADPRIVATE(senescence_hum)
568
569  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
570                                                                        !! no humidity-related senescence (0-1, unitless)
571!$OMP THREADPRIVATE(nosenescence_hum)
572
573  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
574!$OMP THREADPRIVATE(max_turnover_time)
575
576  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
577!$OMP THREADPRIVATE(min_turnover_time)
578
579  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: recycle_leaf          !! Fraction of N leaf that is recycled when leaves are senescent
580!$OMP THREADPRIVATE(recycle_leaf)
581
582  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: recycle_root          !! Fraction of N root that is recycled when leaves are senescent
583!$OMP THREADPRIVATE(recycle_root)
584
585  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
586!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
587
588  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
589                                                                        !! used in the code
590!$OMP THREADPRIVATE(senescence_temp)
591
592  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
593                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
594!$OMP THREADPRIVATE(senescence_temp_c)
595
596  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
597                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
598!$OMP THREADPRIVATE(senescence_temp_b)
599
600  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
601                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
602!$OMP THREADPRIVATE(senescence_temp_a)
603
604  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
605!$OMP THREADPRIVATE(gdd_senescence)
606
607  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: always_init               !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
608!$OMP THREADPRIVATE(always_init)
609
610  !-
611  ! 4. N cycle
612  !-
613  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_min           !! minimum CN ratio of leaves (gC/gN)
614!$OMP THREADPRIVATE(cn_leaf_min)
615
616  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_max           !! maximum CN ratio of leaves (gC/gN)
617!$OMP THREADPRIVATE(cn_leaf_max)
618
619  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_soil_n_bnf        !! Value of total N (NH4+NO3)
620                                                                        !! above which we stop adding N via BNF
621                                                                        !! (gN/m**2)
622!$OMP THREADPRIVATE(max_soil_n_bnf)
623
624  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: manure_pftweight      ! Weight of the distribution of manure over the PFT surface
625!$OMP THREADPRIVATE(manure_pftweight)
626
627  !
628  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: harvest_ratio  !! Share of biomass that is removed from the site during harvest
629                                                                    !! A high value indicates a high harvest efficiency and thus a
630                                                                    !! input of residuals. (unitless, 0-1).
631
632!$OMP THREADPRIVATE(harvest_ratio)
633
634  !
635  ! STOMATE - Age classes
636  !
637
638  INTEGER(i_std), SAVE                            :: nvmap          !! The number of PFTs we have if we ignore age classes.
639                                                                    !! @tex $-$ @endtex
640!$OMP THREADPRIVATE(nvmap)
641  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: agec_group     !! The age class group that this PFT belongs to.
642                                                                    !! If you're not using age classes, this will just be
643                                                                    !! set to the number of the PFT and should be ignored
644                                                                    !! in the code.
645                                                                    !! @tex $-$ @endtex
646!$OMP THREADPRIVATE(agec_group)
647! I do not like the location of these next two variables.  They are computed
648! after agec_group is read in.  Ideally, they would be passed around
649! as arguments or in a structure, since they are not really
650! parameters read in from the input file.
651  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: start_index    !! Gives the index that this real PFT starts
652                                                                    !! on, ignoring age classes
653                                                                    !! @tex $-$ @endtex
654!$OMP THREADPRIVATE(start_index)
655  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nagec_pft      !! The number of age classes for each PFT.
656                                                                    !! Only 1 or nagec are supported right now.
657                                                                    !! @tex $-$ @endtex
658!$OMP THREADPRIVATE(nagec_pft)
659
660  !
661  ! DGVM
662  !
663
664  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time        !! residence time of trees (y)
665!$OMP THREADPRIVATE(residence_time)
666
667  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit             !! critical tmin, tabulated (C)
668!$OMP THREADPRIVATE(tmin_crit)
669
670  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit              !! critical tcm, tabulated (C)
671!$OMP THREADPRIVATE(tcm_crit)
672
673  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: mortality_min     !! Asymptotic mortality if plant growth exceeds long term
674                                                                    !! NPP @tex $(year^{-1})$ @endtex
675!$OMP THREADPRIVATE(mortality_min)
676
677  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: mortality_max     !! Maximum mortality if plants hardly grows
678                                                                    !! @tex $(year^{-1})$ @endtex
679!$OMP THREADPRIVATE(mortality_max)
680
681  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: ref_mortality     !! Reference mortality rate used to calculate mortality
682                                                                    !! as a function of the plant vigor @tex $(year^{-1})$ @endtex
683!$OMP THREADPRIVATE(ref_mortality)
684
685  !
686  ! Biogenic Volatile Organic Compounds
687  !
688
689  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
690                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
691!$OMP THREADPRIVATE(em_factor_isoprene)
692
693  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
694                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
695!$OMP THREADPRIVATE(em_factor_monoterpene)
696
697  REAL(r_std), SAVE :: LDF_mono                                            !! monoterpenes fraction dependancy to light
698!$OMP THREADPRIVATE(LDF_mono)
699  REAL(r_std), SAVE :: LDF_sesq                                            !! sesquiterpenes fraction dependancy to light
700!$OMP THREADPRIVATE(LDF_sesq)
701  REAL(r_std), SAVE :: LDF_meth                                            !! methanol fraction dependancy to light
702!$OMP THREADPRIVATE(LDF_meth)
703  REAL(r_std), SAVE :: LDF_acet                                            !! acetone fraction dependancy to light
704!$OMP THREADPRIVATE(LDF_acet)
705  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene        !! Alfa pinene emission factor
706                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
707!$OMP THREADPRIVATE(em_factor_apinene)
708
709  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene        !! Beta pinene emission factor
710                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
711!$OMP THREADPRIVATE(em_factor_bpinene)
712
713  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene       !! Limonene emission factor
714                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
715!$OMP THREADPRIVATE(em_factor_limonene)
716
717  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene        !! Myrcene emission factor
718                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
719!$OMP THREADPRIVATE(em_factor_myrcene)
720
721  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene       !! Sabinene emission factor
722                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
723!$OMP THREADPRIVATE(em_factor_sabinene)
724
725  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene       !! Camphene emission factor
726                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
727!$OMP THREADPRIVATE(em_factor_camphene)
728
729  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene        !! 3-carene emission factor
730                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
731!$OMP THREADPRIVATE(em_factor_3carene)
732
733  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene      !! T-beta-ocimene emission factor
734                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
735!$OMP THREADPRIVATE(em_factor_tbocimene)
736
737  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot     !! Other monoterpenes emission factor
738                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
739!$OMP THREADPRIVATE(em_factor_othermonot)
740
741  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp     !! Sesquiterpene emission factor
742                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
743!$OMP THREADPRIVATE(em_factor_sesquiterp)
744
745  REAL(r_std), SAVE :: beta_mono                                           !! Monoterpenes temperature dependency coefficient
746!$OMP THREADPRIVATE(beta_mono)
747  REAL(r_std), SAVE :: beta_sesq                                           !! Sesquiterpenes temperature dependency coefficient
748!$OMP THREADPRIVATE(beta_sesq)
749  REAL(r_std), SAVE :: beta_meth                                           !! Methanol temperature dependency coefficient
750!$OMP THREADPRIVATE(beta_meth)
751  REAL(r_std), SAVE :: beta_acet                                           !! Acetone temperature dependency coefficient
752!$OMP THREADPRIVATE(beta_acet)
753  REAL(r_std), SAVE :: beta_oxyVOC                                         !! Other oxygenated BVOC temperature dependency coefficient
754!$OMP THREADPRIVATE(beta_oxyVOC)
755
756  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
757                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
758!$OMP THREADPRIVATE(em_factor_ORVOC)
759
760  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
761                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
762!$OMP THREADPRIVATE(em_factor_OVOC)
763
764  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
765                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
766!$OMP THREADPRIVATE(em_factor_MBO)
767
768  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
769                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
770!$OMP THREADPRIVATE(em_factor_methanol)
771
772  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
773                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
774!$OMP THREADPRIVATE(em_factor_acetone)
775
776  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
777                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
778!$OMP THREADPRIVATE(em_factor_acetal)
779
780  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
781                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
782!$OMP THREADPRIVATE(em_factor_formal)
783
784  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
785                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
786!$OMP THREADPRIVATE(em_factor_acetic)
787
788  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
789                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
790!$OMP THREADPRIVATE(em_factor_formic)
791
792  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
793                                                                           !! exponential dependancy factor for wet soils
794                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
795!$OMP THREADPRIVATE(em_factor_no_wet)
796
797  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
798                                                                           !! exponential dependancy factor for dry soils
799                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
800!$OMP THREADPRIVATE(em_factor_no_dry)
801
802  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
803!$OMP THREADPRIVATE(Larch)
804
805  !
806  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
807  !
808
809  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
810                                                                !! @tex $(m^2.m^{-2})$ @endtex
811!$OMP THREADPRIVATE(lai_initmin)
812
813  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl   !! sapling biomass @tex $(gC.ind^{-1})$ @endtex
814!$OMP THREADPRIVATE(bm_sapl)
815
816  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
817!$OMP THREADPRIVATE(migrate)
818
819  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
820                                                                !! increases (m)
821!$OMP THREADPRIVATE(maxdia)
822
823  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
824!$OMP THREADPRIVATE(cn_sapl)
825
826  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_max       !! Maximum leaf-to-sapwood area ratio (unitless)
827!$OMP THREADPRIVATE(k_latosa_max)
828
829  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_min       !! Minimum leaf-to-sapwood area ratio (unitless)
830!$OMP THREADPRIVATE(k_latosa_min)
831
832 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: LC                 !! Lignin/C ratio of the different biomass pools and PFTs (unitless)
833                                                                      !! based on CN from White et al. (2000)
834!$OMP THREADPRIVATE(LC)
835
836 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_leaf              !! Lignin/C ratio of leaf pool (unitless)
837                                                                      !! based on CN from White et al. (2000)
838!$OMP THREADPRIVATE(LC_leaf)
839
840 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_sapabove          !! Lignin/C ratio of sapabove pool (unitless)
841                                                                      !! based on CN from White et al. (2000)
842!$OMP THREADPRIVATE(LC_sapabove)
843
844 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_sapbelow          !! Lignin/C ratio of sapbelow pool (unitless)
845                                                                      !! based on CN from White et al. (2000)
846!$OMP THREADPRIVATE(LC_sapbelow)
847
848 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_heartabove        !! Lignin/C ratio of heartabove pool (unitless)
849                                                                      !! based on CN from White et al. (2000)
850!$OMP THREADPRIVATE(LC_heartabove)
851
852 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_heartbelow        !! Lignin/C ratio of heartbelow pool (unitless)
853                                                                      !! based on CN from White et al. (2000)
854!$OMP THREADPRIVATE(LC_heartbelow)
855
856 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_fruit             !! Lignin/C ratio of fruit pool (unitless)
857                                                                      !! based on CN from White et al. (2000)
858!$OMP THREADPRIVATE(LC_fruit)
859
860 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_root              !! Lignin/C ratio of root pool (unitless)
861                                                                      !! based on CN from White et al. (2000)
862!$OMP THREADPRIVATE(LC_root)
863
864 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_carbres           !! Lignin/C ratio of carbres pool (unitless)
865                                                                      !! based on CN from White et al. (2000)
866!$OMP THREADPRIVATE(LC_carbres)
867
868 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_labile            !! Lignin/C ratio of labile pool (unitless)
869                                                                      !! based on CN from White et al. (2000)
870!$OMP THREADPRIVATE(LC_labile)
871
872 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: decomp_factor        !! Multpliactive factor modifying
873                                                                      !! the standard decomposition factor for each SOM pool
874!$OMP THREADPRIVATE(decomp_factor)
875
876   !
877  ! STAND STRUCTURE (stomate)
878  !
879  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_density        !! Wood density in @tex $(gC.m^{-3})$ @endtex
880!$OMP THREADPRIVATE(pipe_density)
881
882  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune2          !! height=pipe_tune2 * diameter**pipe_tune3
883!$OMP THREADPRIVATE(pipe_tune2)     
884 
885  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune3          !! height=pipe_tune2 * diameter**pipe_tune3
886!$OMP THREADPRIVATE(pipe_tune3)     
887 
888  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune4          !! ???needed for stem diameter
889!$OMP THREADPRIVATE(pipe_tune4)     
890 
891  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_k1             !! ???
892!$OMP THREADPRIVATE(pipe_k1)       
893 
894  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tree_ff             !! Volume reduction factor from cylinder to real tree shape (inc.branches)
895!$OMP THREADPRIVATE(tree_ff)
896
897  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: crown_to_height    !! Ratio between tree height and the vertical crown diameter. If this value is changed check beforehand that the crown diameter will never exceed the tree height.
898!$OMP THREADPRIVATE(crown_to_height)
899
900  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: crown_vertohor_dia !!Ratio between the vertical and horizontal crown diameter height, so indirectly the horizonatl crown diameter also depends on crown diameter
901!$OMP THREADPRIVATE(crown_vertohor_dia)
902
903  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: mass_ratio_heart_sap!! mass ratio (heartwood+sapwood)/heartwood
904!$OMP THREADPRIVATE(mass_ratio_heart_sap)
905
906  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: canopy_cover        !! Canopy cover - current values are guesses for testing
907                                                                      !! could tune this variable to match MODIS albedo
908!$OMP THREADPRIVATE(canopy_cover)
909   
910  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nmaxplants           !! Intial number of seedlings per hectare. Used
911                                                                      !! in prescribe to initialize the model and after
912                                                                      !! every clearcut
913!$OMP THREADPRIVATE(nmaxplants)
914
915  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: p_use_reserve       
916!$OMP THREADPRIVATE(p_use_reserve)
917
918 
919  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_init         !! The height when a new grassland or cropland is established 
920                                                                      !! @tex $(m)$ @endtex
921!$OMP THREADPRIVATE(height_init)
922
923  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: dia_init_max        !! Min diameter use to initilize stand in prescribe
924!$OMP THREADPRIVATE(dia_init_max)
925
926  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: dia_init_min        !! Max diameter use to initilize stand in prescribe
927!$OMP THREADPRIVATE(dia_init_min)
928
929  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_root              !! Fine root specific conductivity
930                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
931!$OMP THREADPRIVATE(k_root)
932 
933  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_belowground       !! Belowground (root + soil) specific conductivity
934                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
935!$OMP THREADPRIVATE(k_belowground)
936
937  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_sap               !! Sapwood specific conductivity
938                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
939!$OMP THREADPRIVATE(k_sap)
940
941  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_leaf              !! Leaf conductivity @tex $(m s^{-1} MPa^{-1})$ @endtex
942!$OMP THREADPRIVATE(k_leaf)
943
944  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: psi_leaf            !! Minimal leaf water potential @tex $(m s^{-1} MPa^{-1})$ @endtex
945!$OMP THREADPRIVATE(psi_leaf)
946
947  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: psi_50              !! Sapwood leaf water potential that causes 50% loss of xylem
948                                                                      !! conductivity through cavitation @tex $(m s^{-1} MPa^{-1})$ @endtex
949!$OMP THREADPRIVATE(psi_50)
950   
951  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: c_cavitation        !!Shape parameter for loss of conductance Machado & Tyree, 1994 (unitless)         
952!$OMP THREADPRIVATE(c_cavitation)
953     
954 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: srl                  !! Specific root length  @tex $(m g^{-1})$ @endtex       
955!$OMP THREADPRIVATE(srl)
956 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: r_froot              !! Radius of fine roots  @tex $(m)$ @endtex       
957!$OMP THREADPRIVATE(r_froot)
958 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: psi_root             !! Minimum root water potential  @tex $(MPa)$ @endtex       
959!$OMP THREADPRIVATE(psi_root)
960
961 
962  ! RECRUITMENT (stomate)
963 
964  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: recruitment_pft                 !! Do recruitment? (true/false) 
965!$OMP THREADPRIVATE(recruitment_pft)   
966
967  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: beetle_pft                 !!Do beetle? (true/false) 
968!$OMP THREADPRIVATE(beetle_pft)
969
970  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: recruitment_height          !! Height of recruits 
971!$OMP THREADPRIVATE(recruitment_height) 
972
973  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: recruitment_alpha           !! Alpha parameter for recruitment model 
974!$OMP THREADPRIVATE(recruitment_alpha) 
975
976  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: recruitment_beta            !! Beta parameter for recruitment model 
977!$OMP THREADPRIVATE(recruitment_beta)
978
979  !
980  ! PRESCRIBE (stomate)
981  !
982  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tune_reserves_in_sapling  !! A factor to scale the reserve pool of newly
983                                                                            !!planted saplings.  This is required by some deciduous
984                                                                            !! trees in order to survive the first year until budburst,
985                                                                            !!but it has no physical basis.
986                                                                            !!(unitless)
987   
988!$OMP THREADPRIVATE(tune_reserves_in_sapling)
989
990!
991  ! MORTALITY (stomate)
992  !
993  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) &
994                          :: death_distribution_factor              !! The scale factor between the smallest and largest
995                                                                    !! circ class for tree mortality in lpj_kill.
996                                                                    !! (unitless)
997!$OMP THREADPRIVATE(death_distribution_factor)
998  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) &
999                          :: npp_reset_value                        !! The value of the NPP that the long-term value is
1000                                                                    !! reset to after a PFT dies in stomate_kill.  This
1001                                                                    !! only seems to be used for non-trees.
1002                                                                    !! @tex $(gC m^{-2})$ @endtex
1003!$OMP THREADPRIVATE(npp_reset_value)
1004
1005REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: ndying_year       !! Reference number of year in which the forest will disappear after reaching the the stem density threshold. 
1006!$OMP THREADPRIVATE(ndying_year)
1007
1008  ! BEETLE (stomate_pest)
1009  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: age_susceptibility_a  !! a parameter for the relationship between stand age and beetle susceptibility
1010  !$OMP THREADPRIVATE(age_susceptibility_a)
1011  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: age_susceptibility_b  !! b parameter for the relationship between stand age and beetle susceptibility
1012  !$OMP THREADPRIVATE(age_susceptibility_b)
1013  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: age_susceptibility_c  !! c parameter for the relationship between stand age and beetle susceptibility
1014  !$OMP THREADPRIVATE(age_susceptibility_c)
1015  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: remaining_beetles  !! fraction of the beetle population which remaing on the stand after beettle departure
1016  !$OMP THREADPRIVATE(remaining_beetles)
1017  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pressure_feedback  !! parameter wich increase/reduce the importance of the previous infestation in the calculation of the BPI (beetle pressure index)
1018  !$OMP THREADPRIVATE(pressure_feedback)
1019  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rdi_susceptibility_a  !! a parameter for the relationship between stand rdi and beetle susceptibility
1020  !$OMP THREADPRIVATE(rdi_susceptibility_a)
1021  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rdi_target_suscept  !!
1022  !$OMP THREADPRIVATE(rdi_target_suscept)
1023  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rdi_susceptibility_b  !! b parameter for the relationship between stand rdi and beetle susceptibility
1024  !$OMP THREADPRIVATE(rdi_susceptibility_b)
1025  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: share_susceptibility_a  !! a parameter for the relationship between stand share and beetle susceptibility
1026  !$OMP THREADPRIVATE(share_susceptibility_a)
1027  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: share_susceptibility_b  !! b parameter for the relationship between stand share and beetle susceptibility
1028  !$OMP THREADPRIVATE(share_susceptibility_b)
1029  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: drought_susceptibility_a  !! a parameter for the relationship between drought and beetle susceptibility
1030  !$OMP THREADPRIVATE(drought_susceptibility_a)
1031  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: drought_susceptibility_b  !! b parameter for the relationship between drought and beetle susceptibility
1032  !$OMP THREADPRIVATE(drought_susceptibility_b)
1033  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: windthrow_susceptibility_tune  !! parameter for the relationship between windthrow and beetle susceptibility
1034  !$OMP THREADPRIVATE(windthrow_susceptibility_tune)
1035  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beetle_generation_a  !! a parameter for the calculation of the number of beetle generation per year
1036  !$OMP THREADPRIVATE(beetle_generation_a)
1037  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beetle_generation_b  !! b parameter for the calculation of the number of beetle generation per year
1038  !$OMP THREADPRIVATE(beetle_generation_b)
1039  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beetle_generation_c  !! c parameter for the calculation of the number of beetle generation per year
1040  !$OMP THREADPRIVATE(beetle_generation_c)
1041  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_temp_beetle  !! temperature threshold below which Teff is not calculated (*C)
1042  !$OMP THREADPRIVATE(min_temp_beetle)
1043  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_temp_beetle  !! temperature threshold above which Teff is not calculated (*C)
1044  !$OMP THREADPRIVATE(max_temp_beetle)
1045  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: opt_temp_beetle  !! optimal temperature to breed bark beetle (*C)
1046  !$OMP THREADPRIVATE(opt_temp_beetle)
1047
1048  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: eff_temp_beetle_a  !! a parameter for the calculation of the effective temperature used in beetle phenology
1049  !$OMP THREADPRIVATE(eff_temp_beetle_a)
1050  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: eff_temp_beetle_b  !! b parameter for the calculation of the effective temperature used in beetle phenology
1051  !$OMP THREADPRIVATE(eff_temp_beetle_b)
1052  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: eff_temp_beetle_c  !! c parameter for the calculation of the effective temperature used in beetle phenology
1053  !$OMP THREADPRIVATE(eff_temp_beetle_c)
1054  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: eff_temp_beetle_d  !! d parameter for the calculation of the effective temperature used in beetle phenology
1055  !$OMP THREADPRIVATE(eff_temp_beetle_d)
1056  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: diapause_thres_daylength  !! daylength in hour above which bark beetle start diapause
1057  !$OMP THREADPRIVATE(diapause_thres_daylength)
1058 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wght_sirdi_a ! a parameter of the weight of rdi susceptibility in the calculation of landscape susceptibility
1059 !$OMP THREADPRIVATE(wght_sirdi_a)
1060 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wght_sirdi_b ! b parameter of the weight of rdi susceptibility in the calculation of landscape susceptibility
1061 !$OMP THREADPRIVATE(wght_sirdi_b)
1062 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wght_sid ! the weight of long term drought susceptibility in the calculation of landscape susceptibility
1063 !$OMP THREADPRIVATE(wght_sid)
1064 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wght_sis ! the weight of share susceptibility in the calculation of landscape susceptibility
1065 !$OMP THREADPRIVATE(wght_sis)
1066
1067  !
1068  ! WINDFALL (stomate_windthrow)
1069  !
1070  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_c_leaf                         !! Modulus of Rupture (unitless)
1071!$OMP THREADPRIVATE(streamlining_c_leaf)
1072  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_c_leafless                     !! Modulus of Rupture (unitless)
1073!$OMP THREADPRIVATE(streamlining_c_leafless)
1074  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_n_leaf                         !! Modulus of Rupture (unitless)
1075!$OMP THREADPRIVATE(streamlining_n_leaf)
1076  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_n_leafless                     !! Modulus of Rupture (unitless)
1077!$OMP THREADPRIVATE(streamlining_n_leafless)
1078  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: modulus_rupture                             !! Modulus of Rupture (Pa)
1079!$OMP THREADPRIVATE(modulus_rupture)
1080  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: f_knot                                      !! Modulus of Rupture (unitless)
1081!$OMP THREADPRIVATE(f_knot)
1082  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_shallow           !! Modulus of Rupture (Nm.kg-1)
1083!$OMP THREADPRIVATE(overturning_free_draining_shallow)
1084  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_shallow_leafless  !! Modulus of Rupture (Nm.kg-1)
1085!$OMP THREADPRIVATE(overturning_free_draining_shallow_leafless)
1086  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_deep              !! Modulus of Rupture (Nm.kg-1)
1087!$OMP THREADPRIVATE(overturning_free_draining_deep)
1088  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_deep_leafless     !! Modulus of Rupture (Nm.kg-1)
1089!$OMP THREADPRIVATE(overturning_free_draining_deep_leafless)
1090  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_average           !! Modulus of Rupture (Nm.kg-1)
1091!$OMP THREADPRIVATE(overturning_free_draining_average)
1092  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_average_leafless  !! Modulus of Rupture (Nm.kg-1)
1093!$OMP THREADPRIVATE(overturning_free_draining_average_leafless)
1094  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_shallow                  !! Modulus of Rupture (Nm.kg-1)
1095!$OMP THREADPRIVATE(overturning_gleyed_shallow)
1096  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_shallow_leafless         !! Modulus of Rupture (Nm.kg-1)
1097!$OMP THREADPRIVATE(overturning_gleyed_shallow_leafless)
1098  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_deep                     !! Modulus of Rupture (Nm.kg-1)
1099!$OMP THREADPRIVATE(overturning_gleyed_deep)
1100  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_deep_leafless            !! Modulus of Rupture (Nm.kg-1)
1101!$OMP THREADPRIVATE(overturning_gleyed_deep_leafless)
1102  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_average                  !! Modulus of Rupture (Nm.kg-1)
1103!$OMP THREADPRIVATE(overturning_gleyed_average)
1104  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_average_leafless         !! Modulus of Rupture (Nm.kg-1)
1105!$OMP THREADPRIVATE(overturning_gleyed_average_leafless)
1106  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_shallow                   !! Modulus of Rupture (Nm.kg-1)
1107!$OMP THREADPRIVATE(overturning_peaty_shallow)
1108  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_shallow_leafless          !! Modulus of Rupture (Nm.kg-1)
1109!$OMP THREADPRIVATE(overturning_peaty_shallow_leafless)
1110  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_deep                      !! Modulus of Rupture (Nm.kg-1)
1111!$OMP THREADPRIVATE(overturning_peaty_deep)
1112  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_deep_leafless             !! Modulus of Rupture (Nm.kg-1)
1113!$OMP THREADPRIVATE(overturning_peaty_deep_leafless)
1114  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_average                   !! Modulus of Rupture (Nm.kg-1)
1115!$OMP THREADPRIVATE(overturning_peaty_average)
1116  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_average_leafless          !! Modulus of Rupture (Nm.kg-1)
1117!$OMP THREADPRIVATE(overturning_peaty_average_leafless)
1118  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_shallow                    !! Modulus of Rupture (Nm.kg-1)
1119!$OMP THREADPRIVATE(overturning_peat_shallow)
1120  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_shallow_leafless           !! Modulus of Rupture (Nm.kg-1)
1121!$OMP THREADPRIVATE(overturning_peat_shallow_leafless)
1122  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_deep                       !! Modulus of Rupture (Nm.kg-1)
1123!$OMP THREADPRIVATE(overturning_peat_deep)
1124  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_deep_leafless              !! Modulus of Rupture (Nm.kg-1)
1125!$OMP THREADPRIVATE(overturning_peat_deep_leafless)
1126  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_average                    !! Modulus of Rupture (Nm.kg-1)
1127!$OMP THREADPRIVATE(overturning_peat_average)
1128  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_average_leafless           !! Modulus of Rupture (Nm.kg-1)
1129!$OMP THREADPRIVATE(overturning_peat_average_leafless)
1130
1131  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_damage_further                          !! Maximum damage rate for inner area (unitless) 
1132!$OMP THREADPRIVATE(max_damage_further)
1133  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_damage_closer                           !! Maximum damage rate for forest edge (unitless)
1134!$OMP THREADPRIVATE(max_damage_closer)
1135  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sfactor_further                             !! Scaling coefficient s for inner forest (unitless)
1136!$OMP THREADPRIVATE(sfactor_further)
1137  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sfactor_closer                              !! Scaling coefficient s for forest edge (unitless)
1138!$OMP THREADPRIVATE(sfactor_closer)
1139
1140  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: green_density                               !! (kg/m^3)
1141!$OMP THREADPRIVATE(green_density)
1142
1143 
1144
1145  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_to_height       !! Covert lai into vegetation height for grasses and crops
1146!$OMP THREADPRIVATE(lai_to_height)   
1147
1148  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_a      !! intercept of the intra-tree competition within a stand
1149                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1150                                                                    !! Used when n_circ > 6
1151!$OMP THREADPRIVATE(deleuze_a)
1152
1153  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_b      !! slope of the intra-tree competition within a stand
1154                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1155                                                                    !! Used when n_circ > 6
1156!$OMP THREADPRIVATE(deleuze_b)
1157
1158  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_p_all  !! Percentile of the circumferences that receives photosynthates
1159                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1160                                                                    !! Used when n_circ > 6 for FM1, FM2 and FM4
1161!$OMP THREADPRIVATE(deleuze_p_all)
1162
1163  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_p_coppice  !! Percentile of the circumferences that receives photosynthates
1164                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1165                                                                    !! Used when n_circ > 6 for FM3
1166!$OMP THREADPRIVATE(deleuze_p_coppice)
1167
1168  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_power_a!! Divisor of the power for the slope of intra-tree competition within a stand
1169                                                                    !! based on the competition rule of Deleuze and Dhote 2004
1170!$OMP THREADPRIVATE(deleuze_power_a)
1171
1172
1173  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: m_dv                !! Parameter in the Deleuze & Dhote allocation rule that
1174                                                                      !! relaxes the cut-off imposed by ::sigma. Owing to m_relax
1175                                                                      !! trees still grow a little when their ::circ is below
1176                                                                      !! ::sigma
1177!$OMP THREADPRIVATE(m_dv)
1178
1179  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_self_thinning !! Coefficient of the self-thinning relationship D=alpha*N^beta
1180                                                                    !! estimated from German, French, Spanish and Swedish
1181                                                                    !! forest inventories
1182!$OMP THREADPRIVATE(alpha_self_thinning)
1183 
1184  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beta_self_thinning!! Exponent of the self-thinning relationship D=alpha*N^beta
1185                                                                    !! estimated from German, French, Spanish and swedish
1186                                                                    !! forest inventories
1187!$OMP THREADPRIVATE(beta_self_thinning)
1188
1189  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: thinstrat         !! The thinning strategy used for forest management.
1190                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
1191                                                                    !! @tex $(unitless)$ @endtex
1192!$OMP THREADPRIVATE(thinstrat)
1193  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: taumin            !! Minimum tree death probability. stomate_forest.f90
1194                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
1195                                                                    !! @tex $(unitless)$ @endtex
1196!$OMP THREADPRIVATE(taumin)
1197  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: taumax            !! Maximum tree death probability. stomate_forest.f90
1198                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
1199                                                                    !! @tex $(unitless)$ @endtex
1200!$OMP THREADPRIVATE(taumax)
1201  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a_rdi_upper_unman !! Coefficient of self-thinning relationship justified by
1202                                                                    !! the rdi observed in Luyssaert et al 2011
1203!$OMP THREADPRIVATE(a_rdi_upper_unman)
1204  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b_rdi_upper_unman !! Coefficient of self-thinning relationship justified by
1205                                                                    !! the rdi observed in Luyssaert et al 2011
1206!$OMP THREADPRIVATE(b_rdi_upper_unman)
1207  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: c_rdi_upper_unman !! Upper boundary for upper rdi for unmanaged fores
1208!$OMP THREADPRIVATE(c_rdi_upper_unman)
1209  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: d_rdi_upper_unman !! Lower boundary for upper rdi for unmanaged forests
1210!$OMP THREADPRIVATE(d_rdi_upper_unman)
1211  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a_rdi_lower_unman !! Coefficient of self-thinning relationship justified by
1212                                                                    !! the rdi observed in Luyssaert et al 2011
1213!$OMP THREADPRIVATE(a_rdi_lower_unman)
1214  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b_rdi_lower_unman !! Coefficient of self-thinning relationship justified by
1215                                                                    !! the rdi observed in Luyssaert et al 2011
1216!$OMP THREADPRIVATE(b_rdi_lower_unman)
1217  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: c_rdi_lower_unman !! Upper boundary for lower rdi for unmanaged forests
1218!$OMP THREADPRIVATE(c_rdi_lower_unman)
1219  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: d_rdi_lower_unman !! Lower boundary for lower rdi for unmanaged forests
1220!$OMP THREADPRIVATE(d_rdi_lower_unman)
1221  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a_rdi_upper_man   !! Coefficient of the yield-table derived thinning relationship
1222                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1223!$OMP THREADPRIVATE(a_rdi_upper_man)
1224  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b_rdi_upper_man   !! Coefficient of the yield-table derived thinning relationship
1225                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1226!$OMP THREADPRIVATE(b_rdi_upper_man)
1227  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: c_rdi_upper_man   !! Upper boundary for upper rdi for managed fores
1228!$OMP THREADPRIVATE(c_rdi_upper_man)
1229  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: d_rdi_upper_man   !! Lower boundary for upper rdi for managed forests
1230!$OMP THREADPRIVATE(d_rdi_upper_man)
1231  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a_rdi_lower_man   !! Coefficient of the yield-table derived thinning relationship
1232                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1233!$OMP THREADPRIVATE(a_rdi_lower_man)
1234  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b_rdi_lower_man   !! Coefficient of the yield-table derived thinning relationship
1235                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1236!$OMP THREADPRIVATE(b_rdi_lower_man)
1237  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: c_rdi_lower_man   !! Upper boundary for lower rdi for managed forests
1238!$OMP THREADPRIVATE(c_rdi_lower_man)
1239  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: d_rdi_lower_man   !! Lower boundary for lower rdi for managed forests
1240!$OMP THREADPRIVATE(d_rdi_lower_man)
1241  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: dens_target       !! The minimum density of trees in a stand before
1242                                                                    !! they all die off and we replant.  This is to prevent
1243                                                                    !! the stand from becoming just one large tree.
1244                                                                    !! @tex $(trees ha{-1})$ @endtex
1245!$OMP THREADPRIVATE(dens_target)
1246   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: largest_tree_dia !! The diameter at which we decide to clearcut
1247                                                                    !! a stand because our equipment cannot handle
1248                                                                    !! trees larger than this.
1249                                                                    !! @tex $(cm)$ @endtex
1250!$OMP THREADPRIVATE(largest_tree_dia)
1251
1252   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fuelwood_diameter !! Diameter below which the wood harvest is used as fuelwood (m)
1253                                                                    !! Affects the way the wood is used in the dim_product_use
1254                                                                    !! subroutine         
1255!$OMP THREADPRIVATE(fuelwood_diameter)
1256
1257  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coppice_kill_be_wood !! Diameter below which the wood harvest is used as fuelwood (m)
1258!$OMP THREADPRIVATE(coppice_kill_be_wood)
1259                                 
1260  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: branch_ratio      !! branches/total aboveground biomass ratio
1261                                                                    !! (cf carbofor for CITEPA inventory, these
1262                                                                    !! Guerric, Lim 2004, Peischl 2007,
1263                                                                    !! Schulp 2008: 15-30% slash after harvest,
1264                                                                    !! Zaehle 2007: 30% slash after harvest)
1265!$OMP THREADPRIVATE(branch_ratio)
1266  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: branch_harvest    !! The fraction of branches which are harvested
1267                                                                    !! during thinning and clearcut operations on
1268                                                                    !! forests.  1.0 means all branches are taken offsite,
1269                                                                    !! 0.0 means all branches are left onsite and go
1270                                                                    !! into the litter pool.  This number is not
1271                                                                    !! based on any data.
1272!$OMP THREADPRIVATE(branch_harvest)                   
1273
1274  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: coppice_diameter !! The trunk diameter at which a coppice will be cut.
1275                                                                    !! @tex $(m)$ @endtex
1276!$OMP THREADPRIVATE(coppice_diameter) 
1277  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: shoots_per_stool !! The number of shoots that regrow per stool after
1278                                                                    !! the first coppice cut
1279                                                                    !! @tex $-$ @endtex
1280!$OMP THREADPRIVATE(shoots_per_stool)
1281  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: src_rot_length !! The number of years between cuttings for short
1282                                                                    !! rotation coppices.
1283                                                                    !! @tex $-$ @endtex
1284!$OMP THREADPRIVATE(src_rot_length)
1285  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: src_nrots      !! The number of rotations for short rotations coppices
1286                                                                    !! before the roots are killed and replanted.
1287                                                                    !! @tex $-$ @endtex
1288!$OMP THREADPRIVATE(src_nrots)
1289
1290  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fruit_alloc         !! Fraction of biomass allocated to fruit production (0-1)
1291
1292!$OMP THREADPRIVATE(fruit_alloc)
1293
1294 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: labile_reserve       !! The size of the labile pool as a fraction of the
1295                                                                      !! weekly gpp (-). For example, 3 indicates that the
1296                                                                      !! is 3 times the weekly gpp.
1297!$OMP THREADPRIVATE(labile_reserve)
1298
1299 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: deciduous_reserve    !! Fraction of sapwood mass stored in the reserve pool of deciduous
1300                                                                      !! trees during the growing season (unitless, 0-1)
1301
1302!$OMP THREADPRIVATE(deciduous_reserve)
1303
1304 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: evergreen_reserve    !! Fraction of sapwood mass stored in the reserve pool of evergreen
1305                                                                      !! trees (unitless, 0-1)
1306
1307!$OMP THREADPRIVATE(evergreen_reserve)
1308
1309 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescense_reserve   !! Fraction of sapwood mass stored in the reserve pool of deciduous
1310                                                                      !! trees during senescense(unitless, 0-1)
1311
1312!$OMP THREADPRIVATE(senescense_reserve)
1313
1314 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: root_reserve         !! Fraction of sapwood mass stored in the reserve pool of deciduous
1315                                                                      !! trees during the growing season (unitless, 0-1)
1316!$OMP THREADPRIVATE(root_reserve)
1317
1318  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_wood            !! CN ratio of wood for allocation, relative to leaf CN according
1319                                                                      !! to Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
1320!$OMP THREADPRIVATE(fcn_wood)
1321
1322  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_root            !! CN of roots for allocation, relative to leaf CN according
1323                                                                      !! to Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
1324!$OMP THREADPRIVATE(fcn_root)
1325
1326  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_init        !! CN of foliage for allocation, according to Sitch et al 2003
1327                                                                      !! (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
1328!$OMP THREADPRIVATE(cn_leaf_init)
1329
1330  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient 
1331                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
1332!$OMP THREADPRIVATE(maint_resp_slope)
1333                         
1334  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
1335                                                                      !! constant c of aT^2+bT+c , tabulated
1336!$OMP THREADPRIVATE(maint_resp_slope_c)
1337 
1338  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K), 
1339                                                                      !! constant b of aT^2+bT+c , tabulated
1340!$OMP THREADPRIVATE(maint_resp_slope_b)
1341                 
1342  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K), 
1343                                                                      !! constant a of aT^2+bT+c , tabulated
1344!$OMP THREADPRIVATE(maint_resp_slope_a)
1345
1346END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.