source: branches/publications/ORCHIDEE_CAN_r2290/src_parameters/pft_parameters_var.f90 @ 7193

Last change on this file since 7193 was 2280, checked in by sebastiaan.luyssaert, 10 years ago

DEV: NOT tested yet. Committed to transfer the code between curie and asterix. Introduced diameter-based product pools

  • Property svn:keywords set to Date Revision
File size: 64.7 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
279  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_opt     !! Maximum rate of carboxylation
280                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
281!$OMP THREADPRIVATE(vcmax_opt)
282
283  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vjmax_opt     !! Maximum rate of RUbp regeneration
284                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
285!$OMP THREADPRIVATE(vjmax_opt)
286
287  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min_a  !! minimum photosynthesis temperature,
288                                                                !! constant a of ax^2+bx+c (deg C),tabulated (unitless)
289!$OMP THREADPRIVATE(tphoto_min_a)
290
291  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min_b  !! minimum photosynthesis temperature,
292                                                                !! constant b of ax^2+bx+c (deg C),tabulated (unitless)
293!$OMP THREADPRIVATE(tphoto_min_b)
294
295  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min_c  !! minimum photosynthesis temperature,
296                                                                !! constant c of ax^2+bx+c (deg C),tabulated (unitless)
297!$OMP THREADPRIVATE(tphoto_min_c)
298
299  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_opt_a  !! optimum photosynthesis temperature,
300                                                                !! constant a of ax^2+bx+c (deg C),tabulated (unitless)
301!$OMP THREADPRIVATE(tphoto_opt_a)
302
303  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_opt_b  !! optimum photosynthesis temperature,
304                                                                !! constant b of ax^2+bx+c (deg C),tabulated (unitless)
305!$OMP THREADPRIVATE(tphoto_opt_b)
306
307  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_opt_c  !! optimum photosynthesis temperature,
308                                                                !! constant c of ax^2+bx+c (deg C),tabulated (unitless)
309!$OMP THREADPRIVATE(tphoto_opt_c)
310
311  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max_a  !! maximum photosynthesis temperature,
312                                                                !! constant a of ax^2+bx+c (deg C), tabulated (unitless)
313!$OMP THREADPRIVATE(tphoto_max_a)
314
315  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max_b  !! maximum photosynthesis temperature,
316                                                                !! constant b of ax^2+bx+c (deg C), tabulated (unitless)
317!$OMP THREADPRIVATE(tphoto_max_b)
318
319  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max_c  !! maximum photosynthesis temperature,
320                                                                !! constant c of ax^2+bx+c (deg C), tabulated (unitless)
321!$OMP THREADPRIVATE(tphoto_max_c)
322
323 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC         !! Energy of activation for KmC (J mol-1)
324!$OMP THREADPRIVATE(E_KmC)                                                               
325  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO         !! Energy of activation for KmO (J mol-1)
326!$OMP THREADPRIVATE(E_KmO)         
327  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star  !! Energy of activation for gamma_star (J mol-1)
328!$OMP THREADPRIVATE(E_gamma_star)   
329  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax       !! Energy of activation for Vcmax (J mol-1)
330!$OMP THREADPRIVATE(E_Vcmax)                                                             
331  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax        !! Energy of activation for Jmax (J mol-1)
332!$OMP THREADPRIVATE(E_Jmax)
333  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)
334!$OMP THREADPRIVATE(aSV)   
335  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)
336!$OMP THREADPRIVATE(bSV)
337  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min   !! minimum photosynthesis temperature (deg C)
338!$OMP THREADPRIVATE(tphoto_min)
339  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max   !! maximum photosynthesis temperature (deg C)
340!$OMP THREADPRIVATE(tphoto_max)
341  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)
342!$OMP THREADPRIVATE(aSJ)   
343  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)
344!$OMP THREADPRIVATE(bSJ)   
345  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax       !! Energy of deactivation for Vcmax (J mol-1)
346!$OMP THREADPRIVATE(D_Vcmax)                     
347  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax        !! Energy of deactivation for Jmax (J mol-1)
348!$OMP THREADPRIVATE(D_Jmax)                                   
349  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd          !! Energy of activation for Rd (J mol-1)
350!$OMP THREADPRIVATE(E_Rd)                                     
351  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25       !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
352                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
353!$OMP THREADPRIVATE(Vcmax25)
354 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)
355!$OMP THREADPRIVATE(arJV)
356  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)
357!$OMP THREADPRIVATE(brJV)
358  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25         !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
359!$OMP THREADPRIVATE(KmC25)                                     
360  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25         !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
361!$OMP THREADPRIVATE(KmO25)               
362  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25  !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
363!$OMP THREADPRIVATE(gamma_star25)       
364  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a1            !! Empirical factor involved in the calculation of fvpd (-)
365!$OMP THREADPRIVATE(a1)                                       
366  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b1            !! Empirical factor involved in the calculation of fvpd (-)
367!$OMP THREADPRIVATE(b1)                                       
368  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: g0            !! Residual stomatal conductance when irradiance approaches zero (mol m−2 s−1 bar−1)
369!$OMP THREADPRIVATE(g0)                                       
370  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_protons     !! Number of protons required to produce one ATP (mol mol-1)
371!$OMP THREADPRIVATE(h_protons)                                 
372  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpsir         !! Fraction of PSII e− transport rate partitioned to the C4 cycle (-)
373!$OMP THREADPRIVATE(x)                                         
374  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
375!$OMP THREADPRIVATE(fQ)                                       
376  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpseudo       !! Fraction of electrons at PSI that follow  pseudocyclic transport (-) - Values for C3 platns are not used
377!$OMP THREADPRIVATE(fpseudo)                                   
378  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kp            !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
379!$OMP THREADPRIVATE(kp)                                       
380  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha         !! Fraction of PSII activity in the bundle sheath (-)
381!$OMP THREADPRIVATE(alpha)                                     
382  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gbs           !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
383!$OMP THREADPRIVATE(gbs)                                       
384  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: theta         !! Convexity factor for response of J to irradiance (-)
385!$OMP THREADPRIVATE(theta)                                     
386  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_LL      !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
387!$OMP THREADPRIVATE(alpha_LL)
388                                                                                                                                                                             
389  !
390  ! ALLOCATION (stomate)
391  !
392  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0            !! Default sapwood allocation (0-1, unitless)
393!$OMP THREADPRIVATE(S0)
394  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0            !! Default leaf allocation (0-1, unitless)
395!$OMP THREADPRIVATE(L0)
396
397
398  !
399  ! RESPIRATION (stomate)
400  !
401  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient
402                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
403!$OMP THREADPRIVATE(maint_resp_slope)
404
405  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
406                                                                      !! constant c of aT^2+bT+c , tabulated
407!$OMP THREADPRIVATE(maint_resp_slope_c)
408
409  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K),
410                                                                      !! constant b of aT^2+bT+c , tabulated
411!$OMP THREADPRIVATE(maint_resp_slope_b)
412
413  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K),
414                                                                      !! constant a of aT^2+bT+c , tabulated
415!$OMP THREADPRIVATE(maint_resp_slope_a)
416
417  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: coeff_maint_zero  !! maintenance respiration coefficient at 0 deg C,
418                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
419!$OMP THREADPRIVATE(coeff_maint_zero)
420
421  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_leaf        !! maintenance respiration coefficient at 0 deg C,
422                                                                      !! for leaves, tabulated
423                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
424!$OMP THREADPRIVATE(cm_zero_leaf)
425
426  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapabove    !! maintenance respiration coefficient at 0 deg C,
427                                                                      !! for sapwood above, tabulated
428                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
429!$OMP THREADPRIVATE(cm_zero_sapabove)
430
431  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapbelow    !! maintenance respiration coefficient at 0 deg C,
432                                                                      !! for sapwood below, tabulated
433                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
434!$OMP THREADPRIVATE(cm_zero_sapbelow)
435
436  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartabove  !! maintenance respiration coefficient at 0 deg C
437                                                                      !! for heartwood above, tabulated
438                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
439!$OMP THREADPRIVATE(cm_zero_heartabove)
440
441  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartbelow  !! maintenance respiration coefficient at 0 deg C,
442                                                                      !! for heartwood below, tabulated
443                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
444!$OMP THREADPRIVATE(cm_zero_heartbelow)
445
446  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_root        !! maintenance respiration coefficient at 0 deg C,
447                                                                      !! for roots, tabulated
448                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
449!$OMP THREADPRIVATE(cm_zero_root)
450
451  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_fruit       !! maintenance respiration coefficient  at 0 deg C,
452                                                                      !! for fruits, tabulated
453                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
454!$OMP THREADPRIVATE(cm_zero_fruit)
455
456  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_carbres     !! maintenance respiration coefficient at 0 deg C,
457                                                                      !! for carbohydrate reserve, tabulated
458                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
459!$OMP THREADPRIVATE(cm_zero_carbres)
460
461  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_labile      !! maintenance respiration coefficient at 0 deg C,
462                                                                      !! for the labile pool, tabulated
463                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
464!$OMP THREADPRIVATE(cm_zero_labile)
465
466  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_maint_init    !! initial value for maintenance respiration
467                                                                      !! coefficient at 0 deg C used in functional allocation
468                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
469!$OMP THREADPRIVATE(coeff_maint_init)
470
471  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp     !! Fraction of growth respiration expressed as
472                                                                      !! share of the total C that is to be allocated
473                                                                      !! (0-1).
474!$OMP THREADPRIVATE(frac_growthresp)
475
476 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gpp_to_labile        !! The size of the labile pool as a fraction of the
477                                                                      !! weekly gpp (-). For example, 3 indicates that the
478                                                                      !! is 3 times the weekly gpp.
479!$OMP THREADPRIVATE(gpp_to_labile)
480
481
482  !
483  ! STAND STRUCTURE (stomate)
484  !
485  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_density        !! Wood density in @tex $(gC.m^{-3})$ @endtex
486!$OMP THREADPRIVATE(pipe_density)
487
488  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune1          !! crown area = pipe_tune1*stem diameter**pipe_tune_exp_coeff
489!$OMP THREADPRIVATE(pipe_tune1)
490 
491  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune2          !! height=pipe_tune2 * diameter**pipe_tune3
492!$OMP THREADPRIVATE(pipe_tune2)
493
494  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tree_ff             !! Volume reduction factor from cylinder to real tree shape (inc.branches)
495!$OMP THREADPRIVATE(tree_ff)
496 
497  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune3          !! height=pipe_tune2 * diameter**pipe_tune3
498!$OMP THREADPRIVATE(pipe_tune3)     
499 
500  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune4          !! ???needed for stem diameter
501!$OMP THREADPRIVATE(pipe_tune4)     
502 
503  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_k1             !! ???
504!$OMP THREADPRIVATE(pipe_k1)       
505 
506  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune_exp_coeff !! crown area = pipe_tune1*stem diameter**pipe_tune_exp_coeff
507!$OMP THREADPRIVATE(pipe_tune_exp_coeff)     
508 
509  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: mass_ratio_heart_sap!! mass ratio (heartwood+sapwood)/heartwood
510!$OMP THREADPRIVATE(mass_ratio_heart_sap)
511
512  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_to_height       !! Covert lai into vegetation height for grasses and crops
513!$OMP THREADPRIVATE(lai_to_height)   
514
515  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: canopy_cover        !! Canopy cover - current values are guesses for testing
516                                                                      !! could tune this variable to match MODIS albedo
517!$OMP THREADPRIVATE(canopy_cover)
518 
519
520  !
521  ! GROWTH (resource limitation - stomate)
522 
523 
524  !
525  ! GROWTH (functional allocation - stomate)
526 
527  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_prescribed  !! CN of foliage for allocation, according to stich et al 2003
528!$OMP THREADPRIVATE(cn_leaf_prescribed)
529
530  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_wood            !! CN of wood for allocation, relative to leaf CN according
531                                                                      !! to stich et al 2003
532!$OMP THREADPRIVATE(fcn_wood)
533
534  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_root            !! CN of roots for allocation, relative to leaf CN according
535                                                                      !! to stich et al 2003
536!$OMP THREADPRIVATE(fcn_root)
537
538  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_max       !! Maximum leaf-to-sapwood area ratio (unitless)
539!$OMP THREADPRIVATE(k_latosa_max)
540
541  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_min       !! Minimum leaf-to-sapwood area ratio (unitless)
542!$OMP THREADPRIVATE(k_latosa_min)
543
544  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fruit_alloc         !! Fraction of biomass allocated to fruit production (0-1)
545
546!$OMP THREADPRIVATE(fruit_alloc)
547
548  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: m_dv                !! Parameter in the Deleuze & Dhote allocation rule that
549                                                                      !! relaxes the cut-off imposed by ::sigma. Owing to m_relax
550                                                                      !! trees still grow a little when their ::circ is below
551                                                                      !! ::sigma
552!$OMP THREADPRIVATE(m_dv)
553
554  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy    !! Multiplicative factor of lai_max that determines
555                                                                      !! the threshold value of LAI below which the carbohydrate
556                                                                      !! reserve is used.
557                                                       
558!$OMP THREADPRIVATE(lai_max_to_happy)
559
560  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_root              !! Fine root specific conductivity
561                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
562!$OMP THREADPRIVATE(k_root)
563 
564  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_sap               !! Sapwood specific conductivity
565                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
566!$OMP THREADPRIVATE(k_sap)
567
568  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_leaf              !! Leaf conductivity @tex $(m s^{-1} MPa^{-1})$ @endtex
569!$OMP THREADPRIVATE(k_leaf)
570
571  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phi_leaf            !! Minimal leaf water potential @tex $(m s^{-1} MPa^{-1})$ @endtex
572!$OMP THREADPRIVATE(phi_leaf)
573 
574  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phi_50              !! Sapwood leaf water potential that causes 50% loss of xylem
575                                                                      !! conductivity through cavitation @tex $(m s^{-1} MPa^{-1})$ @endtex
576!$OMP THREADPRIVATE(phi_50)
577
578  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: c_cavitation        !! Shape parameter for loss of conductance Machado & Tyree, 1994 (unitless)         
579!$OMP THREADPRIVATE(c_cavitation)
580
581  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phi_soil_tune       !! Additive tuning parameter to account for soil-root interaction
582                                                                      !! @tex $(MPa)$ @endtex       
583!$OMP THREADPRIVATE(phi_soil_tune)
584
585  !
586  ! PRESCRIBE (stomate)
587  !
588  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tune_reserves_in_sapling  !! A factor to scale the reserve pool of newly
589                                                                      !! planted saplings.  This is required by some deciduous
590                                                                      !! trees in order to survive the first year until budburst,
591                                                                      !! but it has no physical basis.
592                                                                      !! (unitless)
593
594!$OMP THREADPRIVATE(tune_reserves_in_sapling)
595
596  !
597  ! MORTALITY (stomate)
598  !
599  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) &
600                          :: death_distribution_factor              !! The scale factor between the smallest and largest
601                                                                    !! circ class for tree mortality in lpj_kill.
602                                                                    !! (unitless)
603!$OMP THREADPRIVATE(death_distribution_factor)
604  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) &
605                          :: npp_reset_value                        !! The value of the NPP that the long-term value is
606                                                                    !! reset to after a PFT dies in stomate_kill.  This
607                                                                    !! only seems to be used for non-trees.
608                                                                    !! @tex $(gC m^{-2})$ @endtex
609!$OMP THREADPRIVATE(npp_reset_value)
610
611  !
612  ! FIRE (stomate)
613  !
614  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
615                                                                    !! capacity (0-1, unitless)
616!$OMP THREADPRIVATE(flam)
617
618  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
619!$OMP THREADPRIVATE(resist)
620
621
622  !
623  ! FLUX - LUC (Land Use Change)
624  !
625  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_s   !! Coeff of biomass export for the year (unitless)
626!$OMP THREADPRIVATE(coeff_lcchange_s)
627
628  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_m  !! Coeff of biomass export for the decade (unitless)
629!$OMP THREADPRIVATE(coeff_lcchange_m)
630
631  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_l !! Coeff of biomass export for the century (unitless)
632!$OMP THREADPRIVATE(coeff_lcchange_l)
633 
634 
635  !
636  ! PHENOLOGY
637  !
638  !-
639  ! 1. Stomate
640  !-
641  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
642!$OMP THREADPRIVATE(lai_max)
643
644  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
645                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
646                                                                    !! 3=raingreen,  4=perennial
647                                                                    !! For the moment, the bare ground phenotype is not managed,
648                                                                    !! so it is considered as "evergreen"
649!$OMP THREADPRIVATE(pheno_type)
650
651  !-
652  ! 2. Leaf Onset
653  !-
654  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
655!$OMP THREADPRIVATE(pheno_gdd_crit)
656
657  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
658                                                                     !! constant c of aT^2+bT+c (unitless)
659!$OMP THREADPRIVATE(pheno_gdd_crit_c)
660
661  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
662                                                                     !! constant b of aT^2+bT+c (unitless)
663!$OMP THREADPRIVATE(pheno_gdd_crit_b)
664
665  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
666                                                                     !! constant a of aT^2+bT+c (unitless)
667!$OMP THREADPRIVATE(pheno_gdd_crit_a)
668
669  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
670!$OMP THREADPRIVATE(ngd_crit)
671
672  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: opti_kpheno_crit   !! multiplicative factor to use optimised gdd_crit (Natasha MacBean)
673                                                                     !! (unitless)
674!$OMP THREADPRIVATE(opti_kpheno_crit)
675
676  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
677                                                                     !! in phenology (C)
678!$OMP THREADPRIVATE(ncdgdd_temp)
679
680  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
681                                                                     !! (0-1, unitless)
682!$OMP THREADPRIVATE(hum_frac)
683
684  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
685!$OMP THREADPRIVATE(hum_min_time)
686
687  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! turnover sapwood -> heartwood conversion time (1/days)
688!$OMP THREADPRIVATE(tau_sap)
689
690  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit turnover (1/days)
691!$OMP THREADPRIVATE(tau_fruit)
692
693  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_root           !! root turnover (1/days)
694!$OMP THREADPRIVATE(tau_root)
695
696  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leaf           !! leaf turnover (1/years)
697!$OMP THREADPRIVATE(tau_leaf)
698
699  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
700                                                                     !! into reserve (0-1, unitless)
701!$OMP THREADPRIVATE(ecureuil)
702
703  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
704!$OMP THREADPRIVATE(alloc_min)
705
706  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
707!$OMP THREADPRIVATE(alloc_max)
708
709  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
710!$OMP THREADPRIVATE(demi_alloc)
711
712
713  !-
714  ! 3. Senescence
715  !-
716  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
717!$OMP THREADPRIVATE(leaffall)
718
719  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
720                                                                        !! List of avaible types of senescence :
721                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
722!$OMP THREADPRIVATE(senescence_type)
723
724  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
725                                                                        !! (0-1, unitless)
726!$OMP THREADPRIVATE(senescence_hum)
727
728  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
729                                                                        !! no humidity-related senescence (0-1, unitless)
730!$OMP THREADPRIVATE(nosenescence_hum)
731
732  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
733!$OMP THREADPRIVATE(max_turnover_time)
734
735  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
736!$OMP THREADPRIVATE(min_turnover_time)
737
738  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
739!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
740
741  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
742                                                                        !! used in the code
743!$OMP THREADPRIVATE(senescence_temp)
744
745  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
746                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
747!$OMP THREADPRIVATE(senescence_temp_c)
748
749  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
750                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
751!$OMP THREADPRIVATE(senescence_temp_b)
752
753  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
754                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
755!$OMP THREADPRIVATE(senescence_temp_a)
756
757  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
758!$OMP THREADPRIVATE(gdd_senescence)
759
760  !
761  ! DGVM
762  !
763
764  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time    !! residence time of trees (y)
765!$OMP THREADPRIVATE(residence_time)
766
767  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit         !! critical tmin, tabulated (C)
768!$OMP THREADPRIVATE(tmin_crit)
769
770  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit          !! critical tcm, tabulated (C)
771!$OMP THREADPRIVATE(tcm_crit)
772
773REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: mortality_min     !! Asymptotic mortality if plant growth exceeds long term
774                                                                    !! NPP @tex $(year^{-1})$ @endtex
775!$OMP THREADPRIVATE(mortality_min)
776
777REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: mortality_max     !! Maximum mortality if plants hardly grows
778                                                                    !! @tex $(year^{-1})$ @endtex
779!$OMP THREADPRIVATE(mortality_max)
780
781REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)   :: ref_mortality     !! Reference mortality rate used to calculate mortality
782                                                                    !! as a function of the plant vigor @tex $(year^{-1})$ @endtex
783!$OMP THREADPRIVATE(ref_mortality)
784
785  !
786  ! Seasonal average
787  !
788  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_hum_growingseason !! Time integral to calculate the mean growingseason
789                                                                        !! plant available soilmoisture (days)
790!$OMP THREADPRIVATE(tau_hum_growingseason)
791
792
793  !
794  ! Biogenic Volatile Organic Compounds
795  !
796
797  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
798                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
799!$OMP THREADPRIVATE(em_factor_isoprene)
800
801  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
802                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
803!$OMP THREADPRIVATE(em_factor_monoterpene)
804
805  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
806                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
807!$OMP THREADPRIVATE(em_factor_ORVOC)
808
809  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
810                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
811!$OMP THREADPRIVATE(em_factor_OVOC)
812
813  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
814                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
815!$OMP THREADPRIVATE(em_factor_MBO)
816
817  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
818                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
819!$OMP THREADPRIVATE(em_factor_methanol)
820
821  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
822                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
823!$OMP THREADPRIVATE(em_factor_acetone)
824
825  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
826                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
827!$OMP THREADPRIVATE(em_factor_acetal)
828
829  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
830                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
831!$OMP THREADPRIVATE(em_factor_formal)
832
833  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
834                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
835!$OMP THREADPRIVATE(em_factor_acetic)
836
837  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
838                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
839!$OMP THREADPRIVATE(em_factor_formic)
840
841  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
842                                                                           !! exponential dependancy factor for wet soils
843                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
844!$OMP THREADPRIVATE(em_factor_no_wet)
845
846  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
847                                                                           !! exponential dependancy factor for dry soils
848                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
849!$OMP THREADPRIVATE(em_factor_no_dry)
850
851  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
852!$OMP THREADPRIVATE(Larch)
853
854  !
855  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
856  !
857
858  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
859                                                                !! @tex $(m^2.m^{-2})$ @endtex
860!$OMP THREADPRIVATE(lai_initmin)
861
862  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl_old   !! sapling biomass for the OLD allocation
863                                                                    !! @tex $(gC.ind^{-1})$ @endtex
864!$OMP THREADPRIVATE(bm_sapl_old)
865
866  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
867!$OMP THREADPRIVATE(migrate)
868
869  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
870                                                                !! increases (m)
871!$OMP THREADPRIVATE(maxdia)
872
873  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
874!$OMP THREADPRIVATE(cn_sapl)
875
876  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
877!$OMP THREADPRIVATE(leaf_timecst)
878 
879  !
880  ! FOREST MANAGEMENT
881  !
882
883  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:)     :: plantation        !!
884!$OMP THREADPRIVATE(plantation)
885
886  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_a         !!
887!$OMP THREADPRIVATE(fm_allo_a)
888
889  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_c         !!
890!$OMP THREADPRIVATE(fm_allo_c)
891
892  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_d         !!
893!$OMP THREADPRIVATE(fm_allo_d)
894
895  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_p         !!
896!$OMP THREADPRIVATE(fm_allo_p)
897
898  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fm_allo_q         !!
899!$OMP THREADPRIVATE(fm_allo_q)
900
901  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: allo_crown_a0     !!
902!$OMP THREADPRIVATE(fm_allo_a0)
903
904  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: allo_crown_a1     !!
905!$OMP THREADPRIVATE(fm_allo_a1)
906
907  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: allo_crown_a2     !!
908!$OMP THREADPRIVATE(fm_allo_a2)
909
910  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_first           !!
911!$OMP THREADPRIVATE(h_first)
912
913  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nmaxtrees      !! Intial number of seedlings per hectare. Used
914                                                                    !! in prescribe to initialize the model and after
915                                                                    !! every clearcut
916!$OMP THREADPRIVATE(nmaxtrees)
917
918! The following two variables are used to define the range of sapling heights for a newly cleared plot
919  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_init_min   !! The minimum height of a tree sapling when a forest
920                                                                    !! stand is established. Owing to the allometric
921                                                                    !! relationship this setting determines all
922                                                                    !! biomass components of a newly establised stand
923                                                                    !! @tex $(m)$ @endtex
924!$OMP THREADPRIVATE(height_init_min)
925  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_init_max   !! The maximum height of a tree sapling when a forest
926                                                                    !! stand is established.
927                                                                    !! @tex $(m)$ @endtex
928!$OMP THREADPRIVATE(height_init_max)
929
930  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_self_thinning !! Coefficient of the self-thinning relationship D=alpha*N^beta
931                                                                    !! estimated from German, French, Spanish and Swedish
932                                                                    !! forest inventories
933!$OMP THREADPRIVATE(alpha_self_thinning)
934 
935  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beta_self_thinning!! Exponent of the self-thinning relationship D=alpha*N^beta
936                                                                    !! estimated from German, French, Spanish and swedish
937                                                                    !! forest inventories
938!$OMP THREADPRIVATE(beta_self_thinning)
939
940  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fuelwood_diameter !! Diameter below which the wood harvest is used as fuelwood (m)
941                                                                    !! Affects the way the wood is used in the dim_product_use
942                                                                    !! subroutine         
943!$OMP THREADPRIVATE(fuelwood_diameter)
944
945  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: thinstrat         !! The thinning strategy used for forest management.
946                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
947                                                                    !! @tex $(unitless)$ @endtex
948!$OMP THREADPRIVATE(thinstrat)
949  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: taumin            !! Minimum tree death probability. stomate_forest.f90
950                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
951                                                                    !! @tex $(unitless)$ @endtex
952!$OMP THREADPRIVATE(taumin)
953  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: taumax            !! Maximum tree death probability. stomate_forest.f90
954                                                                    !! Comes from Eq. 12 of Bellassen et al (2010)
955                                                                    !! @tex $(unitless)$ @endtex
956!$OMP THREADPRIVATE(taumax)
957  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_rdi_upper   !! Coefficient of the yield-table derived thinning relationship
958                                                                    !! D=alpha*N^beta estimated from JRC yield table database
959!$OMP THREADPRIVATE(alpha_rdi_upper)
960  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beta_rdi_upper    !! Coefficient of the yield-table derived thinning relationship
961                                                                    !! D=alpha*N^beta estimated from JRC yield table database
962!$OMP THREADPRIVATE(beta_rdi_upper)
963  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_rdi_lower   !! Coefficient of the yield-table derived thinning relationship
964                                                                    !! D=alpha*N^beta estimated from JRC yield table database
965!$OMP THREADPRIVATE(alpha_rdi_lower)
966  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: beta_rdi_lower    !! Coefficient of the yield-table derived thinning relationship
967                                                                    !! D=alpha*N^beta estimated from JRC yield table database
968!$OMP THREADPRIVATE(beta_rdi_lower)
969  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: dens_target       !! The minimum density of trees in a stand before
970                                                                    !! they all die off and we replant.  This is to prevent
971                                                                    !! the stand from becoming just one large tree.
972                                                                    !! @tex $(trees ha{-1})$ @endtex
973!$OMP THREADPRIVATE(dens_target)
974  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ntrees_dia_profit !! The number of trees above a certain diameter
975                                                                    !! that have to be present in a stand before we
976                                                                    !! decide to clearcut it for profit.
977                                                                    !! @tex $(trees ha{-1})$ @endtex
978!$OMP THREADPRIVATE(ntrees_dia_profit)
979   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: largest_tree_dia !! The diameter at which we decide to clearcut
980                                                                    !! a stand because our equipment cannot handle
981                                                                    !! trees larger than this.
982                                                                    !! @tex $(cm)$ @endtex
983!$OMP THREADPRIVATE(largest_tree_dia)
984                                 
985  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: branch_ratio      !! branches/total aboveground biomass ratio
986                                                                    !! (cf carbofor for CITEPA inventory, these
987                                                                    !! Guerric, Lim 2004, Peischl 2007,
988                                                                    !! Schulp 2008: 15-30% slash after harvest,
989                                                                    !! Zaehle 2007: 30% slash after harvest)
990!$OMP THREADPRIVATE(branch_ratio)
991
992  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: decl_factor       !! Age_decline factor in fraction of vmax decline per year
993                                                                    !! (yield tables > 130 years : inc90=0.8inc50,
994                                                                    !! inc130=0.55inc50,
995                                                                    !! same for broadleaves and coniferous.
996                                                                    !! For temperate pfts, calibration on one site to get a 0.55
997                                                                    !! increment decrease.
998                                                                    !! For boreal pfts, calibration to get an average 0.55
999                                                                    !! increment decrease over 25,7 and 2 sites: Adam Wolf dataset)
1000!$OMP THREADPRIVATE(decl_factor)
1001
1002  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: opt_factor     !! Optimisation factor for vcmax and vjmax
1003!$OMP THREADPRIVATE(opt_factor)                   
1004
1005  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: coppice_diameter !! The trunk diameter at which a coppice will be cut.
1006                                                                    !! @tex $(m)$ @endtex
1007!$OMP THREADPRIVATE(coppice_diameter) 
1008  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: shoots_per_stool !! The number of shoots that regrow per stool after
1009                                                                    !! the first coppice cut
1010                                                                    !! @tex $-$ @endtex
1011!$OMP THREADPRIVATE(shoots_per_stool)
1012  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: src_rot_length !! The number of years between cuttings for short
1013                                                                    !! rotation coppices.
1014                                                                    !! @tex $-$ @endtex
1015!$OMP THREADPRIVATE(src_rot_length)
1016  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: src_nrots      !! The number of rotations for short rotations coppices
1017                                                                    !! before the roots are killed and replanted.
1018                                                                    !! @tex $-$ @endtex
1019!$OMP THREADPRIVATE(src_nrots)
1020
1021  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_a      !! intercept of the intra-tree competition within a stand
1022                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1023                                                                    !! Used when n_circ > 6
1024!$OMP THREADPRIVATE(deleuze_a)
1025
1026  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_b      !! slope of the intra-tree competition within a stand
1027                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1028                                                                    !! Used when n_circ > 6
1029!$OMP THREADPRIVATE(deleuze_b)
1030
1031  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_p      !! Percentile of the circumferences that receives photosynthates
1032                                                                    !! based on the competion rule of Deleuze and Dhote 2004
1033                                                                    !! Used when n_circ > 6 
1034!$OMP THREADPRIVATE(deleuze_p)
1035
1036
1037! SAPIENS - CROP MANAGEMENT
1038
1039  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: harvest_ratio  !! Share of biomass that is removed from the site during harvest
1040                                                                    !! A high value indicates a high harvest efficiency and thus a
1041                                                                    !! input of residuals. (unitless, 0-1).
1042
1043!$OMP THREADPRIVATE(harvest_ratio)
1044
1045
1046! STOMATE - Age classes
1047
1048  INTEGER(i_std), SAVE                            :: nvmap          !! The number of PFTs we have if we ignore age classes.
1049                                                                    !! @tex $-$ @endtex
1050!$OMP THREADPRIVATE(nvmap)
1051  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: agec_group     !! The age class group that this PFT belongs to.
1052                                                                    !! If you're not using age classes, this will just be
1053                                                                    !! set to the number of the PFT and should be ignored
1054                                                                    !! in the code.
1055                                                                    !! @tex $-$ @endtex
1056!$OMP THREADPRIVATE(agec_groups)
1057! I do not like the location of these next two variables.  They are computed
1058! after agec_group is read in.  Ideally, they would be passed around
1059! as arguments or in a structure, since they are not really
1060! parameters read in from the input file.
1061  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: start_index    !! Gives the index that this real PFT starts
1062                                                                    !! on, ignoring age classes
1063                                                                    !! @tex $-$ @endtex
1064!$OMP THREADPRIVATE(start_index)
1065  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nagec_pft      !! The number of age classes for each PFT.
1066                                                                    !! Only 1 or nagec are supported right now.
1067                                                                    !! @tex $-$ @endtex
1068!$OMP THREADPRIVATE(nagec_pft)
1069
1070
1071END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.