source: branches/publications/ORCHIDEE_CAN_r3069/src_parameters/pft_parameters_var.f90 @ 5241

Last change on this file since 5241 was 2945, checked in by sebastiaan.luyssaert, 9 years ago

DEV: tested 1 year global. This code contains the latest version for anthropogenic tree species channges, several bug fixes to forest management as well as the code for the fully integrated multi-layer energy budget. This implies that the multi-layer energy budget makes use Pinty's albedo scheme, the rognostic canopy structure as well as a vertical profile for stomatal conductance. This is an intermediate version because species change code is not complete as some management changes have not been implemented yet. Further the multi-layer albedo code needs more work in terms of calculating average fluxes at the pixel rather than the PFT level

  • Property svn:keywords set to Date Revision
File size: 70.4 KB
Line 
1! =================================================================================================================================
2! MODULE       : pft_parameters_var
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module contains the variables in function of plant funtional type (pft).
10!!
11!!\n DESCRIPTION: This module contains the declarations for the externalized variables in function of the
12!!                plant foncional type(pft). \n
13!!                The module is already USE in module pft_parameters. Therefor no need to USE it seperatly except
14!!                if the subroutines in module pft_parameters are not needed.\n
15!!
16!! RECENT CHANGE(S): None
17!!
18!! REFERENCE(S) : None
19!!
20!! SVN          :
21!! $HeadURL: $
22!! $Date$
23!! $Revision$
24!! \n
25!_ ================================================================================================================================
26
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  LOGICAL, SAVE   :: ok_throughfall_by_pft = .FALSE.             !! Flag to use the parameter PERCENT_THROUGHFALL_PFT (true/false)
50!$OMP THREADPRIVATE(ok_throughfall_by_pft)
51
52
53  !
54  ! VEGETATION STRUCTURE
55  !
56  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_tab       !! leaf type (1-4, unitless)
57                                                                    !! 1=broad leaved tree, 2=needle leaved tree,
58                                                                    !! 3=grass 4=bare ground
59!$OMP THREADPRIVATE(leaf_tab)
60
61  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_model  !! which phenology model is used? (tabulated) (unitless)
62!$OMP THREADPRIVATE(pheno_model)
63
64  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tree               !! Is the vegetation type a tree ? (true/false)
65!$OMP THREADPRIVATE(is_tree)
66
67  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_deciduous          !! Is PFT deciduous ? (true/false)
68!$OMP THREADPRIVATE(is_deciduous)
69
70   LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tropical          !! Is PFT tropical ? (true/false)
71!$OMP THREADPRIVATE(is_tropical)
72
73  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_temperate          !! Is PFT temperate ? (true/false)
74!$OMP THREADPRIVATE(is_temperate)
75
76  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_boreal             !! Is PFT boreal ? (true/false)
77!$OMP THREADPRIVATE(is_boreal)
78
79  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_evergreen          !! Is PFT evegreen ? (true/false)
80!$OMP THREADPRIVATE(is_evergreen)
81
82  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_needleleaf         !! Is PFT needleleaf ? (true/false)
83!$OMP THREADPRIVATE(is_needleleaf)
84
85  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: natural               !! natural? (true/false)
86!$OMP THREADPRIVATE(natural)
87
88  CHARACTER(len=5), ALLOCATABLE, SAVE, DIMENSION(:) :: type_of_lai  !! Type of behaviour of the LAI evolution algorithm
89                                                                    !! for each vegetation type.
90                                                                    !! Value of type_of_lai, one for each vegetation type :
91                                                                    !! mean or interp
92!$OMP THREADPRIVATE(type_of_lai)
93
94  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: veget_ori_fixed_test_1 !! Value for veget_ori for tests in 0-dim simulations
95                                                                         !! (0-1, unitless)
96!$OMP THREADPRIVATE(veget_ori_fixed_test_1)
97
98  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimax                !! laimax for maximum lai see also type of lai
99                                                                         !! interpolation
100                                                                         !! @tex $(m^2.m^{-2})$ @endtex
101!$OMP THREADPRIVATE(llaimax)
102
103  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimin                !! laimin for minimum lai see also type of lai
104                                                                         !! interpolation
105                                                                         !! @tex $(m^2.m^{-2})$ @endtex
106!$OMP THREADPRIVATE(llaimin)
107
108  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_presc           !! prescribed height of vegetation.(m) Only used without stomate
109                                                                         !! Value for height_presc : one for each vegetation type
110!$OMP THREADPRIVATE(height_presc)
111
112  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) ::  rveg_pft              !! Potentiometer to set vegetation resistance (unitless)
113                                                                         !! Nathalie on March 28th, 2006 - from Fred Hourdin,
114!$OMP THREADPRIVATE(rveg_pft)
115
116  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sla                    !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
117!$OMP THREADPRIVATE(sla)
118
119  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_happy              !! Lai threshold below which carbohydrate
120                                                                         !! reserve may be used in functional allocation.
121                                                                         !! Also used in phenology to see if mixed classes
122                                                                         !! should die.  These seem completely arbitrary.
123                                                                         !! @tex $(m^2.m^{-2})$ @endtex
124!$OMP THREADPRIVATE(lai_happy)
125
126  !
127  ! EVAPOTRANSPIRATION (sechiba)
128  !
129  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const          !! Structural resistance.
130                                                                         !! Value for rstruct_const : one for each vegetation type
131                                                                         !! @tex $(s.m^{-1})$ @endtex
132!$OMP THREADPRIVATE(rstruct_const)
133
134  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero                  !! A vegetation dependent constant used in the calculation
135                                                                         !! of the surface resistance.
136                                                                         !! Value for kzero one for each vegetation type
137                                                                         !! @tex $(kg.m^2.s^{-1})$ @endtex
138!$OMP THREADPRIVATE(kzero)
139
140  !
141  ! WATER (sechiba)
142  !
143  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wmax_veg  !! Volumetric available soil water capacity in each PFT
144                                                            !! @tex $(kg.m^{-3} of soil)$ @endtex
145!$OMP THREADPRIVATE(wmax_veg)
146
147  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: humcste   !! Root profile description for the different vegetation types.
148                                                            !! These are the factor in the exponential which gets
149                                                            !! the root density as a function of depth
150                                                            !! @tex $(m^{-1})$ @endtex
151!$OMP THREADPRIVATE(humcste)
152
153  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft !! Fraction of rain intercepted by the canopy (0-100, unitless)
154!$OMP THREADPRIVATE(throughfall_by_pft)
155
156  !
157  ! ALBEDO (sechiba)
158  !
159  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged    !! Minimum snow albedo value for each vegetation type
160                                                                !! after aging (dirty old snow) (unitless)
161                                                                !! Source : Values are from the Thesis of S. Chalita (1992)
162!$OMP THREADPRIVATE(snowa_aged)
163
164  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec     !! Decay rate of snow albedo value for each vegetation type
165                                                                !! as it will be used in condveg_snow (unitless)
166                                                                !! Source : Values are from the Thesis of S. Chalita (1992)
167!$OMP THREADPRIVATE(snowa_dec)
168
169  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis  !! leaf albedo of vegetation type, visible albedo (unitless)
170!$OMP THREADPRIVATE(alb_leaf_vis)
171
172  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir  !! leaf albedo of vegetation type, near infrared albedo (unitless)
173!$OMP THREADPRIVATE(alb_leaf_nir)
174
175  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: leaf_ssa       !! leaf single scattering albedo of all
176!$OMP THREADPRIVATE(leaf_ssa)
177
178  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: leaf_psd       !! leaf prefered scattering direction of all
179                                                                       !! vegetation types and spectra (unitless)
180!$OMP THREADPRIVATE(leaf_psd)
181
182  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: bgd_reflectance  !! background reflectance of all vegetation types and spectra (unitless)
183!$OMP THREADPRIVATE(bgd_reflectance)
184
185  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_to_shoot_clumping       !! The clumping factor for leaves to shoots in the
186                                                                               !! effective LAI calculation...notice this should be
187                                                                               !! equal to unity for grasslands/croplands
188!$OMP THREADPRIVATE(leaf_to_shoot_clumping)
189
190
191!---add by YC ---a constant for tunning the LAI, which coupled with the atmosphere for the transpiaration 
192  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tune_coupled                 !! The coupled factor of LAI for the transpiration                                                                   
193!$OMP THREADPRIVATE(tune_coupled)
194
195
196
197
198! NOTE: this next variable originally was a plant-to-stand clumping factor to be used
199! in describing how grasses and crops clump together at the plant level (but not trees,
200! as their plant-to-stand clumping is calculated directly) to calculate abledo. However, we
201! get the effective spectral parameters for the albedo calculation from inverting satelite data,
202! which includes all clumping.  Therefore we do not wish to account for this effect twice.
203! What will be incorrect about our grassland and crop albedo is the lack of management options
204! for these PFTs in ORCHIDEE, which will lead to LAI values which are wrong.  Thus we
205! will include an LAI correction factor in the calculation of the effective LAI which
206! allows us to compensate for this via tuning.
207  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_correction_factor  !! see note above
208!$OMP THREADPRIVATE(lai_correction_factor)
209
210  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_level_sep          !! This is used in determining the levels
211                                                                         !! for photosynthesis.  This is the thinnest
212                                                                         !! that the levels are allowed to be, in
213                                                                         !! vertical thickness.
214                                                                         !! @tex $(m)$ @endtex
215!$OMP THREADPRIVATE(min_level_sep)
216
217  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_top                !! Diffuco.f90 calculates the stomatal conductance of the
218                                                                         !! top layer of the canopy. Because the top layer can contain
219                                                                         !! different amounts of LAI depending on the crown diameter
220                                                                         !! we had to define top layer in terms of the LAI it contains.
221                                                                         !! stomatal conductance in the top layer contributes to the
222                                                                         !! transpiration (m2 m-2). Arbitrary values.
223!$OMP THREADPRIVATE(lai_top)
224
225
226
227  !
228  ! SOIL - VEGETATION
229  !
230  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg      !! Table which contains the correlation between the soil
231                                                                        !! types and vegetation type. Two modes exist :
232                                                                        !! 1) pref_soil_veg = 0 then we have an equidistribution
233                                                                        !!    of vegetation on soil types
234                                                                        !! 2) Else for each pft the prefered soil type is given :
235                                                                        !!    1=sand, 2=loan, 3=clay
236                                                                        !! This variable is initialized in slowproc.(1-3, unitless)
237!$OMP THREADPRIVATE(pref_soil_veg)
238
239  !
240  ! PHOTOSYNTHESIS
241  !
242  !-
243  ! 1. CO2
244  !-
245  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4             !! flag for C4 vegetation types (true/false)
246!$OMP THREADPRIVATE(is_c4)
247
248  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix     !! values used for vcmax when STOMATE is not activated
249                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
250!$OMP THREADPRIVATE(vcmax_fix)
251
252  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vjmax_fix     !! values used for vjmax when STOMATE is not activated
253                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
254!$OMP THREADPRIVATE(vjmax_fix)
255
256  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: co2_tmin_fix  !! values used for photosynthesis tmin when STOMATE
257                                                                !! is not activated (C)
258!$OMP THREADPRIVATE(co2_tmin_fix)
259
260  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: co2_topt_fix  !! values used for photosynthesis topt when STOMATE
261                                                                !! is not activated (C)
262!$OMP THREADPRIVATE(co2_topt_fix)
263
264  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: co2_tmax_fix  !! values used for photosynthesis tmax when STOMATE
265                                                                !! is not activated (C)
266!$OMP THREADPRIVATE(co2_tmax_fix)
267
268  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation (unitless)
269!$OMP THREADPRIVATE(downregulation_co2_coeff)
270
271
272  !-
273  ! 2. Stomate
274  !-
275  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff     !! extinction coefficient of the Monsi&Saeki relationship (1953)
276                                                                !! (unitless)
277!$OMP THREADPRIVATE(ext_coeff)
278 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC          !! Energy of activation for KmC (J mol-1)
279!$OMP THREADPRIVATE(E_KmC)                                                               
280  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO         !! Energy of activation for KmO (J mol-1)
281!$OMP THREADPRIVATE(E_KmO)         
282  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star  !! Energy of activation for gamma_star (J mol-1)
283!$OMP THREADPRIVATE(E_gamma_star)   
284  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax       !! Energy of activation for Vcmax (J mol-1)
285!$OMP THREADPRIVATE(E_Vcmax)                                                             
286  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax        !! Energy of activation for Jmax (J mol-1)
287!$OMP THREADPRIVATE(E_Jmax)
288  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)
289!$OMP THREADPRIVATE(aSV)   
290  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)
291!$OMP THREADPRIVATE(bSV)
292  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min   !! minimum photosynthesis temperature (deg C)
293!$OMP THREADPRIVATE(tphoto_min)
294  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max   !! maximum photosynthesis temperature (deg C)
295!$OMP THREADPRIVATE(tphoto_max)
296  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)
297!$OMP THREADPRIVATE(aSJ)   
298  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)
299!$OMP THREADPRIVATE(bSJ)   
300  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax       !! Energy of deactivation for Vcmax (J mol-1)
301!$OMP THREADPRIVATE(D_Vcmax)                     
302  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax        !! Energy of deactivation for Jmax (J mol-1)
303!$OMP THREADPRIVATE(D_Jmax)                                   
304  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd          !! Energy of activation for Rd (J mol-1)
305!$OMP THREADPRIVATE(E_Rd)                                     
306  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25       !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
307                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
308!$OMP THREADPRIVATE(Vcmax25)
309 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)
310!$OMP THREADPRIVATE(arJV)
311  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)
312!$OMP THREADPRIVATE(brJV)
313  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25         !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
314!$OMP THREADPRIVATE(KmC25)                                     
315  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25         !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
316!$OMP THREADPRIVATE(KmO25)               
317  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25  !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
318!$OMP THREADPRIVATE(gamma_star25)       
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                                                                                                                                                                             
344  !
345  ! ALLOCATION (stomate)
346  !
347  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: R0            !! Default root allocation (0-1, unitless)
348!$OMP THREADPRIVATE(R0)
349  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0            !! Default sapwood allocation (0-1, unitless)
350!$OMP THREADPRIVATE(S0)
351  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0            !! Default leaf allocation (0-1, unitless)
352!$OMP THREADPRIVATE(L0)
353
354
355  !
356  ! RESPIRATION (stomate)
357  !
358  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient
359                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
360!$OMP THREADPRIVATE(maint_resp_slope)
361
362  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
363                                                                      !! constant c of aT^2+bT+c , tabulated
364!$OMP THREADPRIVATE(maint_resp_slope_c)
365
366  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K),
367                                                                      !! constant b of aT^2+bT+c , tabulated
368!$OMP THREADPRIVATE(maint_resp_slope_b)
369
370  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K),
371                                                                      !! constant a of aT^2+bT+c , tabulated
372!$OMP THREADPRIVATE(maint_resp_slope_a)
373
374  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: coeff_maint_zero  !! maintenance respiration coefficient at 0 deg C,
375                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
376!$OMP THREADPRIVATE(coeff_maint_zero)
377
378  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_leaf        !! maintenance respiration coefficient at 0 deg C,
379                                                                      !! for leaves, tabulated
380                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
381!$OMP THREADPRIVATE(cm_zero_leaf)
382
383  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapabove    !! maintenance respiration coefficient at 0 deg C,
384                                                                      !! for sapwood above, tabulated
385                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
386!$OMP THREADPRIVATE(cm_zero_sapabove)
387
388  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapbelow    !! maintenance respiration coefficient at 0 deg C,
389                                                                      !! for sapwood below, tabulated
390                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
391!$OMP THREADPRIVATE(cm_zero_sapbelow)
392
393  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartabove  !! maintenance respiration coefficient at 0 deg C
394                                                                      !! for heartwood above, tabulated
395                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
396!$OMP THREADPRIVATE(cm_zero_heartabove)
397
398  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartbelow  !! maintenance respiration coefficient at 0 deg C,
399                                                                      !! for heartwood below, tabulated
400                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
401!$OMP THREADPRIVATE(cm_zero_heartbelow)
402
403  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_root        !! maintenance respiration coefficient at 0 deg C,
404                                                                      !! for roots, tabulated
405                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
406!$OMP THREADPRIVATE(cm_zero_root)
407
408  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_fruit       !! maintenance respiration coefficient  at 0 deg C,
409                                                                      !! for fruits, tabulated
410                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
411!$OMP THREADPRIVATE(cm_zero_fruit)
412
413  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_carbres     !! maintenance respiration coefficient at 0 deg C,
414                                                                      !! for carbohydrate reserve, tabulated
415                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
416!$OMP THREADPRIVATE(cm_zero_carbres)
417
418  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_labile      !! maintenance respiration coefficient at 0 deg C,
419                                                                      !! for the labile pool, tabulated
420                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
421!$OMP THREADPRIVATE(cm_zero_labile)
422
423  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_maint_init    !! initial value for maintenance respiration
424                                                                      !! coefficient at 0 deg C used in functional allocation
425                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
426!$OMP THREADPRIVATE(coeff_maint_init)
427
428  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp     !! Fraction of growth respiration expressed as
429                                                                      !! share of the total C that is to be allocated
430                                                                      !! (0-1).
431!$OMP THREADPRIVATE(frac_growthresp)
432
433 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: labile_reserve       !! The size of the labile pool as a fraction of the
434                                                                      !! weekly gpp (-). For example, 3 indicates that the
435                                                                      !! is 3 times the weekly gpp.
436!$OMP THREADPRIVATE(labile_reserve)
437
438 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: deciduous_reserve    !! Fraction of sapwood mass stored in the reserve pool of deciduous
439                                                                      !! trees during the growing season (unitless, 0-1)
440
441!$OMP THREADPRIVATE(deciduous_reserve)
442
443 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: evergreen_reserve    !! Fraction of sapwood mass stored in the reserve pool of evergreen
444                                                                      !! trees (unitless, 0-1)
445
446!$OMP THREADPRIVATE(evergreen_reserve)
447
448 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescense_reserve   !! Fraction of sapwood mass stored in the reserve pool of deciduous
449                                                                      !! trees during senescense(unitless, 0-1)
450
451!$OMP THREADPRIVATE(senescense_reserve)
452
453  !
454  ! STAND STRUCTURE (stomate)
455  !
456  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_density        !! Wood density in @tex $(gC.m^{-3})$ @endtex
457!$OMP THREADPRIVATE(pipe_density)
458
459  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune1          !! crown area = pipe_tune1*stem diameter**pipe_tune_exp_coeff
460!$OMP THREADPRIVATE(pipe_tune1)
461 
462  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune2          !! height=pipe_tune2 * diameter**pipe_tune3
463!$OMP THREADPRIVATE(pipe_tune2)
464
465  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tree_ff             !! Volume reduction factor from cylinder to real tree shape (inc.branches)
466!$OMP THREADPRIVATE(tree_ff)
467 
468  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune3          !! height=pipe_tune2 * diameter**pipe_tune3
469!$OMP THREADPRIVATE(pipe_tune3)     
470 
471  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune4          !! ???needed for stem diameter
472!$OMP THREADPRIVATE(pipe_tune4)     
473 
474  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_k1             !! ???
475!$OMP THREADPRIVATE(pipe_k1)       
476 
477  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune_exp_coeff !! crown area = pipe_tune1*stem diameter**pipe_tune_exp_coeff
478!$OMP THREADPRIVATE(pipe_tune_exp_coeff)     
479 
480  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: mass_ratio_heart_sap!! mass ratio (heartwood+sapwood)/heartwood
481!$OMP THREADPRIVATE(mass_ratio_heart_sap)
482
483  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_to_height       !! Covert lai into vegetation height for grasses and crops
484!$OMP THREADPRIVATE(lai_to_height)   
485
486  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: canopy_cover        !! Canopy cover - current values are guesses for testing
487                                                                      !! could tune this variable to match MODIS albedo
488!$OMP THREADPRIVATE(canopy_cover)
489 
490
491  !
492  ! GROWTH (resource limitation - stomate)
493 
494 
495  !
496  ! GROWTH (functional allocation - stomate)
497 
498  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_prescribed  !! CN of foliage for allocation, according to stich et al 2003
499!$OMP THREADPRIVATE(cn_leaf_prescribed)
500
501  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_wood            !! CN of wood for allocation, relative to leaf CN according
502                                                                      !! to stich et al 2003
503!$OMP THREADPRIVATE(fcn_wood)
504
505  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_root            !! CN of roots for allocation, relative to leaf CN according
506                                                                      !! to stich et al 2003
507!$OMP THREADPRIVATE(fcn_root)
508
509  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_max       !! Maximum leaf-to-sapwood area ratio (unitless)
510!$OMP THREADPRIVATE(k_latosa_max)
511
512  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_min       !! Minimum leaf-to-sapwood area ratio (unitless)
513!$OMP THREADPRIVATE(k_latosa_min)
514
515  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fruit_alloc         !! Fraction of biomass allocated to fruit production (0-1)
516
517!$OMP THREADPRIVATE(fruit_alloc)
518
519  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: m_dv                !! Parameter in the Deleuze & Dhote allocation rule that
520                                                                      !! relaxes the cut-off imposed by ::sigma. Owing to m_relax
521                                                                      !! trees still grow a little when their ::circ is below
522                                                                      !! ::sigma
523!$OMP THREADPRIVATE(m_dv)
524
525  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy    !! Multiplicative factor of lai_max that determines
526                                                                      !! the threshold value of LAI below which the carbohydrate
527                                                                      !! reserve is used.
528                                                       
529!$OMP THREADPRIVATE(lai_max_to_happy)
530
531  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_root              !! Fine root specific conductivity
532                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
533!$OMP THREADPRIVATE(k_root)
534 
535  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_sap               !! Sapwood specific conductivity
536                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
537!$OMP THREADPRIVATE(k_sap)
538
539  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_leaf              !! Leaf conductivity @tex $(m s^{-1} MPa^{-1})$ @endtex
540!$OMP THREADPRIVATE(k_leaf)
541
542  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phi_leaf            !! Minimal leaf water potential @tex $(m s^{-1} MPa^{-1})$ @endtex
543!$OMP THREADPRIVATE(phi_leaf)
544 
545  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phi_50              !! Sapwood leaf water potential that causes 50% loss of xylem
546                                                                      !! conductivity through cavitation @tex $(m s^{-1} MPa^{-1})$ @endtex
547!$OMP THREADPRIVATE(phi_50)
548
549  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: c_cavitation        !! Shape parameter for loss of conductance Machado & Tyree, 1994 (unitless)         
550!$OMP THREADPRIVATE(c_cavitation)
551
552  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phi_soil_tune       !! Additive tuning parameter to account for soil-root interaction
553                                                                      !! @tex $(MPa)$ @endtex       
554!$OMP THREADPRIVATE(phi_soil_tune)
555
556  !
557  ! PRESCRIBE (stomate)
558  !
559  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tune_reserves_in_sapling  !! A factor to scale the reserve pool of newly
560                                                                      !! planted saplings.  This is required by some deciduous
561                                                                      !! trees in order to survive the first year until budburst,
562                                                                      !! but it has no physical basis.
563                                                                      !! (unitless)
564
565!$OMP THREADPRIVATE(tune_reserves_in_sapling)
566
567  !
568  ! MORTALITY (stomate)
569  !
570  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) &
571                          :: death_distribution_factor              !! The scale factor between the smallest and largest
572                                                                    !! circ class for tree mortality in lpj_kill.
573                                                                    !! (unitless)
574!$OMP THREADPRIVATE(death_distribution_factor)
575  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) &
576                          :: npp_reset_value                        !! The value of the NPP that the long-term value is
577                                                                    !! reset to after a PFT dies in stomate_kill.  This
578                                                                    !! only seems to be used for non-trees.
579                                                                    !! @tex $(gC m^{-2})$ @endtex
580!$OMP THREADPRIVATE(npp_reset_value)
581
582  !
583  ! WINDFALL (stomate_windfall)
584  !
585  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_c_leaf                         !! Modulus of Rupture (Pa)
586!$OMP THREADPRIVATE(streamlining_c_leaf)
587  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_c_leafless                     !! Modulus of Rupture (Pa)
588!$OMP THREADPRIVATE(streamlining_c_leafless)
589  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_n_leaf                         !! Modulus of Rupture (Pa)
590!$OMP THREADPRIVATE(streamlining_n_leaf)
591  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_n_leafless                     !! Modulus of Rupture (Pa)
592!$OMP THREADPRIVATE(streamlining_n_leafless)
593  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_rb_leaf                        !! Modulus of Rupture (Pa)
594!$OMP THREADPRIVATE(streamlining_rb_leaf)
595  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: streamlining_rb_leafless                    !! Modulus of Rupture (Pa)
596!$OMP THREADPRIVATE(streamlining_rb_leafless)
597  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: canopy_density_leaf                         !! Modulus of Rupture (Pa)
598!$OMP THREADPRIVATE(canopy_density_leaf)
599  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: canopy_density_leafless                     !! Modulus of Rupture (Pa)
600!$OMP THREADPRIVATE(canopy_density_leafless)
601  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: intercept_breadth                           !! Modulus of Rupture (Pa)
602!$OMP THREADPRIVATE(intercept_breadth)
603  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: slope_breadth                               !! Modulus of Rupture (Pa)
604!$OMP THREADPRIVATE(slope_breadth)
605  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: intercept_depth                             !! Modulus of Rupture (Pa)
606!$OMP THREADPRIVATE(intercept_depth)
607  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: slope_depth                                 !! Modulus of Rupture (Pa)
608!$OMP THREADPRIVATE(slope_depth)
609  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: green_density                               !! Modulus of Rupture (Pa)
610!$OMP THREADPRIVATE(green_density)
611  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: modulus_rupture                             !! Modulus of Rupture (Pa)
612!$OMP THREADPRIVATE(modulus_rupture)
613  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: f_knot                                      !! Modulus of Rupture (Pa)
614!$OMP THREADPRIVATE(f_knot)
615  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_shallow           !! Modulus of Rupture (Pa)
616!$OMP THREADPRIVATE(overturning_free_draining_shallow)
617  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_shallow_leafless  !! Modulus of Rupture (Pa)
618!$OMP THREADPRIVATE(overturning_free_draining_shallow_leafless)
619  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_deep              !! Modulus of Rupture (Pa)
620!$OMP THREADPRIVATE(overturning_free_draining_deep)
621  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_deep_leafless     !! Modulus of Rupture (Pa)
622!$OMP THREADPRIVATE(overturning_free_draining_deep_leafless)
623  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_average           !! Modulus of Rupture (Pa)
624!$OMP THREADPRIVATE(overturning_free_draining_average)
625  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_free_draining_average_leafless  !! Modulus of Rupture (Pa)
626!$OMP THREADPRIVATE(overturning_free_draining_average_leafless)
627  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_shallow                  !! Modulus of Rupture (Pa)
628!$OMP THREADPRIVATE(overturning_gleyed_shallow)
629  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_shallow_leafless         !! Modulus of Rupture (Pa)
630!$OMP THREADPRIVATE(overturning_gleyed_shallow_leafless)
631  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_deep                     !! Modulus of Rupture (Pa)
632!$OMP THREADPRIVATE(overturning_gleyed_deep)
633  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_deep_leafless            !! Modulus of Rupture (Pa)
634!$OMP THREADPRIVATE(overturning_gleyed_deep_leafless)
635  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_average                  !! Modulus of Rupture (Pa)
636!$OMP THREADPRIVATE(overturning_gleyed_average)
637  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_gleyed_average_leafless         !! Modulus of Rupture (Pa)
638!$OMP THREADPRIVATE(overturning_gleyed_average_leafless)
639  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_shallow                   !! Modulus of Rupture (Pa)
640!$OMP THREADPRIVATE(overturning_peaty_shallow)
641  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_shallow_leafless          !! Modulus of Rupture (Pa)
642!$OMP THREADPRIVATE(overturning_peaty_shallow_leafless)
643  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_deep                      !! Modulus of Rupture (Pa)
644!$OMP THREADPRIVATE(overturning_peaty_deep)
645  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_deep_leafless             !! Modulus of Rupture (Pa)
646!$OMP THREADPRIVATE(overturning_peaty_deep_leafless)
647  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_average                   !! Modulus of Rupture (Pa)
648!$OMP THREADPRIVATE(overturning_peaty_average)
649  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peaty_average_leafless          !! Modulus of Rupture (Pa)
650!$OMP THREADPRIVATE(overturning_peaty_average_leafless)
651  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_shallow                    !! Modulus of Rupture (Pa)
652!$OMP THREADPRIVATE(overturning_peat_shallow)
653  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_shallow_leafless           !! Modulus of Rupture (Pa)
654!$OMP THREADPRIVATE(overturning_peat_shallow_leafless)
655  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_deep                       !! Modulus of Rupture (Pa)
656!$OMP THREADPRIVATE(overturning_peat_deep)
657  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_deep_leafless              !! Modulus of Rupture (Pa)
658!$OMP THREADPRIVATE(overturning_peat_deep_leafless)
659  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_average                    !! Modulus of Rupture (Pa)
660!$OMP THREADPRIVATE(overturning_peat_average)
661  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: overturning_peat_average_leafless           !! Modulus of Rupture (Pa)
662!$OMP THREADPRIVATE(overturning_peat_average_leafless)
663
664  !
665  ! FIRE (stomate)
666  !
667  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
668                                                                    !! capacity (0-1, unitless)
669!$OMP THREADPRIVATE(flam)
670
671  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
672!$OMP THREADPRIVATE(resist)
673
674
675  !
676  ! FLUX - LUC (Land Use Change)
677  !
678  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_s   !! Coeff of biomass export for the year (unitless)
679!$OMP THREADPRIVATE(coeff_lcchange_s)
680
681  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_m  !! Coeff of biomass export for the decade (unitless)
682!$OMP THREADPRIVATE(coeff_lcchange_m)
683
684  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_l !! Coeff of biomass export for the century (unitless)
685!$OMP THREADPRIVATE(coeff_lcchange_l)
686 
687 
688  !
689  ! PHENOLOGY
690  !
691  !-
692  ! 1. Stomate
693  !-
694  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
695!$OMP THREADPRIVATE(lai_max)
696
697  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
698                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
699                                                                    !! 3=raingreen,  4=perennial
700                                                                    !! For the moment, the bare ground phenotype is not managed,
701                                                                    !! so it is considered as "evergreen"
702!$OMP THREADPRIVATE(pheno_type)
703
704  !-
705  ! 2. Leaf Onset
706  !-
707  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
708!$OMP THREADPRIVATE(pheno_gdd_crit)
709
710  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
711                                                                     !! constant c of aT^2+bT+c (unitless)
712!$OMP THREADPRIVATE(pheno_gdd_crit_c)
713
714  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
715                                                                     !! constant b of aT^2+bT+c (unitless)
716!$OMP THREADPRIVATE(pheno_gdd_crit_b)
717
718  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
719                                                                     !! constant a of aT^2+bT+c (unitless)
720!$OMP THREADPRIVATE(pheno_gdd_crit_a)
721
722  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
723!$OMP THREADPRIVATE(ngd_crit)
724
725  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: opti_kpheno_crit   !! multiplicative factor to use optimised gdd_crit (Natasha MacBean)
726                                                                     !! (unitless)
727!$OMP THREADPRIVATE(opti_kpheno_crit)
728
729  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
730                                                                     !! in phenology (C)
731!$OMP THREADPRIVATE(ncdgdd_temp)
732
733  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
734                                                                     !! (0-1, unitless)
735!$OMP THREADPRIVATE(hum_frac)
736
737  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
738!$OMP THREADPRIVATE(hum_min_time)
739
740  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! turnover sapwood -> heartwood conversion time (1/days)
741!$OMP THREADPRIVATE(tau_sap)
742
743  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit turnover (1/days)
744!$OMP THREADPRIVATE(tau_fruit)
745
746  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_root           !! root turnover (1/days)
747!$OMP THREADPRIVATE(tau_root)
748
749  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leaf           !! leaf turnover (1/years)
750!$OMP THREADPRIVATE(tau_leaf)
751
752  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit       !! time to attain the initial foliage using the carbohydrate reserve
753!$OMP THREADPRIVATE(tau_leafinit)
754
755  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
756                                                                     !! into reserve (0-1, unitless)
757!$OMP THREADPRIVATE(ecureuil)
758
759  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
760!$OMP THREADPRIVATE(alloc_min)
761
762  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
763!$OMP THREADPRIVATE(alloc_max)
764
765  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
766!$OMP THREADPRIVATE(demi_alloc)
767
768
769  !-
770  ! 3. Senescence
771  !-
772  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
773!$OMP THREADPRIVATE(leaffall)
774
775  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
776                                                                        !! List of avaible types of senescence :
777                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
778!$OMP THREADPRIVATE(senescence_type)
779
780  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
781                                                                        !! (0-1, unitless)
782!$OMP THREADPRIVATE(senescence_hum)
783
784  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
785                                                                        !! no humidity-related senescence (0-1, unitless)
786!$OMP THREADPRIVATE(nosenescence_hum)
787
788  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
789!$OMP THREADPRIVATE(max_turnover_time)
790
791  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
792!$OMP THREADPRIVATE(min_turnover_time)
793
794  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
795!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
796
797  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
798                                                                        !! used in the code
799!$OMP THREADPRIVATE(senescence_temp)
800
801  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
802                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
803!$OMP THREADPRIVATE(senescence_temp_c)
804
805  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
806                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
807!$OMP THREADPRIVATE(senescence_temp_b)
808
809  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
810                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
811!$OMP THREADPRIVATE(senescence_temp_a)
812
813  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
814!$OMP THREADPRIVATE(gdd_senescence)
815
816  !
817  ! DGVM
818  !
819
820  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time    !! residence time of trees (y)
821!$OMP THREADPRIVATE(residence_time)
822
823  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit         !! critical tmin, tabulated (C)
824!$OMP THREADPRIVATE(tmin_crit)
825
826  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit          !! critical tcm, tabulated (C)
827!$OMP THREADPRIVATE(tcm_crit)
828
829REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: mortality_min     !! Asymptotic mortality if plant growth exceeds long term
830                                                                    !! NPP @tex $(year^{-1})$ @endtex
831!$OMP THREADPRIVATE(mortality_min)
832
833REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: mortality_max     !! Maximum mortality if plants hardly grows
834                                                                    !! @tex $(year^{-1})$ @endtex
835!$OMP THREADPRIVATE(mortality_max)
836
837REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: ref_mortality     !! Reference mortality rate used to calculate mortality
838                                                                    !! as a function of the plant vigor @tex $(year^{-1})$ @endtex
839!$OMP THREADPRIVATE(ref_mortality)
840
841  !
842  ! Seasonal average
843  !
844  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_hum_growingseason !! Time integral to calculate the mean growingseason
845                                                                        !! plant available soilmoisture (days)
846!$OMP THREADPRIVATE(tau_hum_growingseason)
847
848
849  !
850  ! Biogenic Volatile Organic Compounds
851  !
852
853  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
854                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
855!$OMP THREADPRIVATE(em_factor_isoprene)
856
857  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
858                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
859!$OMP THREADPRIVATE(em_factor_monoterpene)
860
861  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
862                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
863!$OMP THREADPRIVATE(em_factor_ORVOC)
864
865  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
866                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
867!$OMP THREADPRIVATE(em_factor_OVOC)
868
869  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
870                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
871!$OMP THREADPRIVATE(em_factor_MBO)
872
873  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
874                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
875!$OMP THREADPRIVATE(em_factor_methanol)
876
877  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
878                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
879!$OMP THREADPRIVATE(em_factor_acetone)
880
881  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
882                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
883!$OMP THREADPRIVATE(em_factor_acetal)
884
885  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
886                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
887!$OMP THREADPRIVATE(em_factor_formal)
888
889  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
890                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
891!$OMP THREADPRIVATE(em_factor_acetic)
892
893  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
894                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
895!$OMP THREADPRIVATE(em_factor_formic)
896
897  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
898                                                                           !! exponential dependancy factor for wet soils
899                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
900!$OMP THREADPRIVATE(em_factor_no_wet)
901
902  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
903                                                                           !! exponential dependancy factor for dry soils
904                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
905!$OMP THREADPRIVATE(em_factor_no_dry)
906
907  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
908!$OMP THREADPRIVATE(Larch)
909
910  !
911  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
912  !
913
914  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
915                                                                !! @tex $(m^2.m^{-2})$ @endtex
916!$OMP THREADPRIVATE(lai_initmin)
917
918  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl_old   !! sapling biomass for the OLD allocation
919                                                                    !! @tex $(gC.ind^{-1})$ @endtex
920!$OMP THREADPRIVATE(bm_sapl_old)
921
922  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
923!$OMP THREADPRIVATE(migrate)
924
925  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
926                                                                !! increases (m)
927!$OMP THREADPRIVATE(maxdia)
928
929  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
930!$OMP THREADPRIVATE(cn_sapl)
931
932  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
933!$OMP THREADPRIVATE(leaf_timecst)
934 
935  !
936  ! FOREST MANAGEMENT
937  !
938
939  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)     :: plantation        !!
940!$OMP THREADPRIVATE(plantation)
941
942  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_a         !!
943!$OMP THREADPRIVATE(fm_allo_a)
944
945  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_c         !!
946!$OMP THREADPRIVATE(fm_allo_c)
947
948  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_d         !!
949!$OMP THREADPRIVATE(fm_allo_d)
950
951  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_p         !!
952!$OMP THREADPRIVATE(fm_allo_p)
953
954  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_q         !!
955!$OMP THREADPRIVATE(fm_allo_q)
956
957  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: allo_crown_a0     !!
958!$OMP THREADPRIVATE(allo_crown_a0)
959
960  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: allo_crown_a1     !!
961!$OMP THREADPRIVATE(allo_crown_a1)
962
963  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: allo_crown_a2     !!
964!$OMP THREADPRIVATE(allo_crown_a2)
965
966  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_first           !!
967!$OMP THREADPRIVATE(h_first)
968
969  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nmaxtrees      !! Intial number of seedlings per hectare. Used
970                                                                    !! in prescribe to initialize the model and after
971                                                                    !! every clearcut
972!$OMP THREADPRIVATE(nmaxtrees)
973
974! The following two variables are used to define the range of sapling heights for a newly cleared plot
975  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_init_min   !! The minimum height of a tree sapling when a forest
976                                                                    !! stand is established. Owing to the allometric
977                                                                    !! relationship this setting determines all
978                                                                    !! biomass components of a newly establised stand
979                                                                    !! @tex $(m)$ @endtex
980!$OMP THREADPRIVATE(height_init_min)
981  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_init_max   !! The maximum height of a tree sapling when a forest
982                                                                    !! stand is established.
983                                                                    !! @tex $(m)$ @endtex
984!$OMP THREADPRIVATE(height_init_max)
985
986  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_self_thinning !! Coefficient of the self-thinning relationship D=alpha*N^beta
987                                                                    !! estimated from German, French, Spanish and Swedish
988                                                                    !! forest inventories
989!$OMP THREADPRIVATE(alpha_self_thinning)
990 
991  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beta_self_thinning!! Exponent of the self-thinning relationship D=alpha*N^beta
992                                                                    !! estimated from German, French, Spanish and swedish
993                                                                    !! forest inventories
994!$OMP THREADPRIVATE(beta_self_thinning)
995
996  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fuelwood_diameter !! Diameter below which the wood harvest is used as fuelwood (m)
997                                                                    !! Affects the way the wood is used in the dim_product_use
998                                                                    !! subroutine         
999!$OMP THREADPRIVATE(fuelwood_diameter)
1000
1001  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coppice_kill_be_wood !! Diameter below which the wood harvest is used as fuelwood (m)
1002!$OMP THREADPRIVATE(coppice_kill_be_wood)
1003
1004  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: thinstrat         !! The thinning strategy used for forest management.
1005                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
1006                                                                    !! @tex $(unitless)$ @endtex
1007!$OMP THREADPRIVATE(thinstrat)
1008  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: taumin            !! Minimum tree death probability. stomate_forest.f90
1009                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
1010                                                                    !! @tex $(unitless)$ @endtex
1011!$OMP THREADPRIVATE(taumin)
1012  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: taumax            !! Maximum tree death probability. stomate_forest.f90
1013                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
1014                                                                    !! @tex $(unitless)$ @endtex
1015!$OMP THREADPRIVATE(taumax)
1016  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_rdi_upper   !! Coefficient of the yield-table derived thinning relationship
1017                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1018!$OMP THREADPRIVATE(alpha_rdi_upper)
1019  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beta_rdi_upper    !! Coefficient of the yield-table derived thinning relationship
1020                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1021!$OMP THREADPRIVATE(beta_rdi_upper)
1022  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_rdi_lower   !! Coefficient of the yield-table derived thinning relationship
1023                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1024!$OMP THREADPRIVATE(alpha_rdi_lower)
1025  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beta_rdi_lower    !! Coefficient of the yield-table derived thinning relationship
1026                                                                    !! D=alpha*N^beta estimated from JRC yield table database
1027!$OMP THREADPRIVATE(beta_rdi_lower)
1028  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: dens_target       !! The minimum density of trees in a stand before
1029                                                                    !! they all die off and we replant.  This is to prevent
1030                                                                    !! the stand from becoming just one large tree.
1031                                                                    !! @tex $(trees ha{-1})$ @endtex
1032!$OMP THREADPRIVATE(dens_target)
1033   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: largest_tree_dia !! The diameter at which we decide to clearcut
1034                                                                    !! a stand because our equipment cannot handle
1035                                                                    !! trees larger than this.
1036                                                                    !! @tex $(cm)$ @endtex
1037!$OMP THREADPRIVATE(largest_tree_dia)
1038                                 
1039  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: branch_ratio      !! branches/total aboveground biomass ratio
1040                                                                    !! (cf carbofor for CITEPA inventory, these
1041                                                                    !! Guerric, Lim 2004, Peischl 2007,
1042                                                                    !! Schulp 2008: 15-30% slash after harvest,
1043                                                                    !! Zaehle 2007: 30% slash after harvest)
1044!$OMP THREADPRIVATE(branch_ratio)
1045  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: branch_harvest    !! The fraction of branches which are harvested
1046                                                                    !! during thinning and clearcut operations on
1047                                                                    !! forests.  1.0 means all branches are taken offsite,
1048                                                                    !! 0.0 means all branches are left onsite and go
1049                                                                    !! into the litter pool.  This number is not
1050                                                                    !! based on any data.
1051!$OMP THREADPRIVATE(branch_harvest)
1052
1053  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: decl_factor       !! Age_decline factor in fraction of vmax decline per year
1054                                                                    !! (yield tables > 130 years : inc90=0.8inc50,
1055                                                                    !! inc130=0.55inc50,
1056                                                                    !! same for broadleaves and coniferous.
1057                                                                    !! For temperate pfts, calibration on one site to get a 0.55
1058                                                                    !! increment decrease.
1059                                                                    !! For boreal pfts, calibration to get an average 0.55
1060                                                                    !! increment decrease over 25,7 and 2 sites: Adam Wolf dataset)
1061!$OMP THREADPRIVATE(decl_factor)
1062
1063  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: opt_factor     !! Optimisation factor for vcmax and vjmax
1064!$OMP THREADPRIVATE(opt_factor)                   
1065
1066  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: coppice_diameter !! The trunk diameter at which a coppice will be cut.
1067                                                                    !! @tex $(m)$ @endtex
1068!$OMP THREADPRIVATE(coppice_diameter) 
1069  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: shoots_per_stool !! The number of shoots that regrow per stool after
1070                                                                    !! the first coppice cut
1071                                                                    !! @tex $-$ @endtex
1072!$OMP THREADPRIVATE(shoots_per_stool)
1073  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: src_rot_length !! The number of years between cuttings for short
1074                                                                    !! rotation coppices.
1075                                                                    !! @tex $-$ @endtex
1076!$OMP THREADPRIVATE(src_rot_length)
1077  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: src_nrots      !! The number of rotations for short rotations coppices
1078                                                                    !! before the roots are killed and replanted.
1079                                                                    !! @tex $-$ @endtex
1080!$OMP THREADPRIVATE(src_nrots)
1081
1082  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_a      !! intercept of the intra-tree competition within a stand
1083                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1084                                                                    !! Used when n_circ > 6
1085!$OMP THREADPRIVATE(deleuze_a)
1086
1087  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_b      !! slope of the intra-tree competition within a stand
1088                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1089                                                                    !! Used when n_circ > 6
1090!$OMP THREADPRIVATE(deleuze_b)
1091
1092  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_p_all  !! Percentile of the circumferences that receives photosynthates
1093                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1094                                                                    !! Used when n_circ > 6 for FM1, FM2 and FM4
1095!$OMP THREADPRIVATE(deleuze_p_all)
1096
1097  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_p_coppice  !! Percentile of the circumferences that receives photosynthates
1098                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1099                                                                    !! Used when n_circ > 6 for FM3
1100!$OMP THREADPRIVATE(deleuze_p_coppice)
1101
1102
1103! SAPIENS - CROP MANAGEMENT
1104
1105  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: harvest_ratio  !! Share of biomass that is removed from the site during harvest
1106                                                                    !! A high value indicates a high harvest efficiency and thus a
1107                                                                    !! input of residuals. (unitless, 0-1).
1108
1109!$OMP THREADPRIVATE(harvest_ratio)
1110
1111
1112! STOMATE - Age classes
1113
1114  INTEGER(i_std), SAVE                            :: nvmap          !! The number of PFTs we have if we ignore age classes.
1115                                                                    !! @tex $-$ @endtex
1116!$OMP THREADPRIVATE(nvmap)
1117  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: agec_group     !! The age class group that this PFT belongs to.
1118                                                                    !! If you're not using age classes, this will just be
1119                                                                    !! set to the number of the PFT and should be ignored
1120                                                                    !! in the code.
1121                                                                    !! @tex $-$ @endtex
1122!$OMP THREADPRIVATE(agec_group)
1123! I do not like the location of these next two variables.  They are computed
1124! after agec_group is read in.  Ideally, they would be passed around
1125! as arguments or in a structure, since they are not really
1126! parameters read in from the input file.
1127  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: start_index    !! Gives the index that this real PFT starts
1128                                                                    !! on, ignoring age classes
1129                                                                    !! @tex $-$ @endtex
1130!$OMP THREADPRIVATE(start_index)
1131  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nagec_pft      !! The number of age classes for each PFT.
1132                                                                    !! Only 1 or nagec are supported right now.
1133                                                                    !! @tex $-$ @endtex
1134!$OMP THREADPRIVATE(nagec_pft)
1135
1136
1137END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.