source: branches/publications/ORCHIDEE_CAMEO_gmd_2022/src_parameters/pft_parameters_var.f90

Last change on this file was 7181, checked in by maureen.beaudor, 3 years ago

correction in benchmark version

  • Property svn:keywords set to Date Revision
File size: 52.6 KB
Line 
1! =================================================================================================================================
2! MODULE       : pft_parameters_var
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module contains the variables in function of plant funtional type (pft).
10!!
11!!\n DESCRIPTION: This module contains the declarations for the externalized variables in function of the
12!!                plant foncional type(pft). \n
13!!                The module is already USE in module pft_parameters. Therefor no need to USE it seperatly except
14!!                if the subroutines in module pft_parameters are not needed.\n
15!!
16!! RECENT CHANGE(S): None
17!!
18!! REFERENCE(S) : None
19!!
20!! SVN          :
21!! $HeadURL: $
22!! $Date$
23!! $Revision$
24!! \n
25!_ ================================================================================================================================
26
27MODULE pft_parameters_var
28
29  USE defprec
30 
31  IMPLICIT NONE
32
33
34  !
35  ! PFT GLOBAL
36  !
37  INTEGER(i_std), SAVE :: nvm = 13                               !! Number of vegetation types (2-N, unitless)
38!$OMP THREADPRIVATE(nvm)
39
40  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pft_to_mtc  !! Table of conversion : we associate one pft to one metaclass
41                                                                 !! (1-13, unitless)
42!$OMP THREADPRIVATE(pft_to_mtc)
43
44  CHARACTER(LEN=34), ALLOCATABLE, SAVE, DIMENSION(:) :: PFT_name !! Description of the PFT (unitless)
45!$OMP THREADPRIVATE(PFT_name)
46
47  LOGICAL, SAVE   :: l_first_pft_parameters = .TRUE.             !! To keep first call trace of the module (true/false)
48!$OMP THREADPRIVATE(l_first_pft_parameters)
49
50  !
51  ! VEGETATION STRUCTURE
52  !
53  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_tab       !! leaf type (1-4, unitless)
54                                                                    !! 1=broad leaved tree, 2=needle leaved tree,
55                                                                    !! 3=grass 4=bare ground
56!$OMP THREADPRIVATE(leaf_tab)
57
58  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_model  !! which phenology model is used? (tabulated) (unitless)
59!$OMP THREADPRIVATE(pheno_model)
60
61  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tree               !! Is the vegetation type a tree ? (true/false)
62!$OMP THREADPRIVATE(is_tree)
63
64  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_deciduous          !! Is PFT deciduous ? (true/false)
65!$OMP THREADPRIVATE(is_deciduous)
66
67  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_evergreen          !! Is PFT evegreen ? (true/false)
68!$OMP THREADPRIVATE(is_evergreen)
69
70  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_needleleaf         !! Is PFT needleleaf ? (true/false)
71!$OMP THREADPRIVATE(is_needleleaf)
72 
73  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tropical           !! Is PFT tropical ? (true/false)
74!$OMP THREADPRIVATE(is_tropical)
75
76  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: natural               !! natural? (true/false)
77!$OMP THREADPRIVATE(natural)
78
79  CHARACTER(len=5), ALLOCATABLE, SAVE, DIMENSION(:) :: type_of_lai  !! Type of behaviour of the LAI evolution algorithm
80                                                                    !! for each vegetation type.
81                                                                    !! Value of type_of_lai, one for each vegetation type :
82                                                                    !! mean or interp
83!$OMP THREADPRIVATE(type_of_lai)
84
85  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: veget_ori_fixed_test_1 !! Value for veget_ori for tests in 0-dim simulations
86                                                                         !! (0-1, unitless)
87!$OMP THREADPRIVATE(veget_ori_fixed_test_1)
88
89  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimax                !! laimax for maximum lai see also type of lai
90                                                                         !! interpolation
91                                                                         !! @tex $(m^2.m^{-2})$ @endtex
92!$OMP THREADPRIVATE(llaimax)
93
94  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimin                !! laimin for minimum lai see also type of lai
95                                                                         !! interpolation
96                                                                         !! @tex $(m^2.m^{-2})$ @endtex
97!$OMP THREADPRIVATE(llaimin)
98
99  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_presc           !! prescribed height of vegetation.(m)
100                                                                         !! Value for height_presc : one for each vegetation type
101!$OMP THREADPRIVATE(height_presc)
102
103  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: z0_over_height        !! Factor to calculate roughness height from
104                                                                        !! vegetation height (unitless)   
105!$OMP THREADPRIVATE(z0_over_height)
106
107  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ratio_z0m_z0h         !! Ratio between z0m and z0h
108!$OMP THREADPRIVATE(ratio_z0m_z0h)
109
110  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) ::  rveg_pft              !! Potentiometer to set vegetation resistance (unitless)
111                                                                         !! Nathalie on March 28th, 2006 - from Fred Hourdin,
112!$OMP THREADPRIVATE(rveg_pft)
113
114  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sla                    !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
115!$OMP THREADPRIVATE(sla)
116
117  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: slainit                !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
118!$OMP THREADPRIVATE(slainit)
119
120  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: availability_fact      !! calculate dynamic mortality in lpj_gap
121!$OMP THREADPRIVATE(availability_fact)
122
123  !
124  ! EVAPOTRANSPIRATION (sechiba)
125  !
126  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const          !! Structural resistance.
127                                                                         !! Value for rstruct_const : one for each vegetation type
128                                                                         !! @tex $(s.m^{-1})$ @endtex
129!$OMP THREADPRIVATE(rstruct_const)
130
131  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero                  !! A vegetation dependent constant used in the calculation
132                                                                         !! of the surface resistance.
133                                                                         !! Value for kzero one for each vegetation type
134                                                                         !! @tex $(kg.m^2.s^{-1})$ @endtex
135!$OMP THREADPRIVATE(kzero)
136
137  !
138  ! WATER (sechiba)
139  !
140  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wmax_veg  !! Volumetric available soil water capacity in each PFT
141                                                            !! @tex $(kg.m^{-3} of soil)$ @endtex
142!$OMP THREADPRIVATE(wmax_veg)
143
144  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: humcste   !! Root profile description for the different vegetation types.
145                                                            !! These are the factor in the exponential which gets
146                                                            !! the root density as a function of depth
147                                                            !! @tex $(m^{-1})$ @endtex
148!$OMP THREADPRIVATE(humcste)
149
150  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft !! Percent by PFT of precip that is not intercepted by the canopy
151!$OMP THREADPRIVATE(throughfall_by_pft)
152
153  !
154  ! ALBEDO (sechiba)
155  !
156  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_vis !! Minimum snow albedo value for each vegetation type
157                                                                 !! after aging (dirty old snow), visible albedo (unitless)
158                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
159!$OMP THREADPRIVATE(snowa_aged_vis)
160
161  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_nir !! Minimum snow albedo value for each vegetation type
162                                                                 !! after aging (dirty old snow), near infrared albedo (unitless)
163                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
164!$OMP THREADPRIVATE(snowa_aged_nir)
165
166  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_vis  !! Decay rate of snow albedo value for each vegetation type
167                                                                 !! as it will be used in condveg_snow, visible albedo (unitless)
168                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
169!$OMP THREADPRIVATE(snowa_dec_vis)
170
171  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_nir  !! Decay rate of snow albedo value for each vegetation type
172                                                                 !! as it will be used in condveg_snow, near infrared albedo (unitless)
173                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
174!$OMP THREADPRIVATE(snowa_dec_nir)
175
176  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis  !! leaf albedo of vegetation type, visible albedo (unitless)
177!$OMP THREADPRIVATE(alb_leaf_vis)
178
179  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir  !! leaf albedo of vegetation type, near infrared albedo (unitless)
180!$OMP THREADPRIVATE(alb_leaf_nir)
181
182  !
183  ! SOIL - VEGETATION
184  !
185  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg      !! Table which contains the correlation between the soil
186                                                                        !! types and vegetation type. Two modes exist :
187                                                                        !! 1) pref_soil_veg = 0 then we have an equidistribution
188                                                                        !!    of vegetation on soil types
189                                                                        !! 2) Else for each pft the prefered soil type is given :
190                                                                        !!    1=sand, 2=loan, 3=clay
191                                                                        !! This variable is initialized in slowproc.(1-3, unitless)
192!$OMP THREADPRIVATE(pref_soil_veg)
193
194  !
195  ! PHOTOSYNTHESIS
196  !
197  !-
198  ! 1. CO2
199  !-
200  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4             !! flag for C4 vegetation types (true/false)
201!$OMP THREADPRIVATE(is_c4)
202
203  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix     !! values used for vcmax when STOMATE is not activated
204                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
205!$OMP THREADPRIVATE(vcmax_fix)
206
207  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation (unitless)
208!$OMP THREADPRIVATE(downregulation_co2_coeff)
209
210  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC         !! Energy of activation for KmC (J mol-1)
211!$OMP THREADPRIVATE(E_KmC)                                                               
212  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO         !! Energy of activation for KmO (J mol-1)
213!$OMP THREADPRIVATE(E_KmO)         
214REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Sco           !! Energy of activation for Sco (J mol-1)
215!$OMP THREADPRIVATE(E_Sco)           
216  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star  !! Energy of activation for gamma_star (J mol-1)
217!$OMP THREADPRIVATE(E_gamma_star)   
218  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax       !! Energy of activation for Vcmax (J mol-1)
219!$OMP THREADPRIVATE(E_Vcmax)                                                             
220  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax        !! Energy of activation for Jmax (J mol-1)
221!$OMP THREADPRIVATE(E_Jmax)
222  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)
223!$OMP THREADPRIVATE(aSV)   
224  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)
225!$OMP THREADPRIVATE(bSV)
226  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min   !! minimum photosynthesis temperature (deg C)
227!$OMP THREADPRIVATE(tphoto_min)
228  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max   !! maximum photosynthesis temperature (deg C)
229!$OMP THREADPRIVATE(tphoto_max)
230  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)
231!$OMP THREADPRIVATE(aSJ)   
232  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)
233!$OMP THREADPRIVATE(bSJ)   
234  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax       !! Energy of deactivation for Vcmax (J mol-1)
235!$OMP THREADPRIVATE(D_Vcmax)                     
236  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax        !! Energy of deactivation for Jmax (J mol-1)
237!$OMP THREADPRIVATE(D_Jmax)                           
238
239  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gm          !! Energy of activation for gm (J mol-1)
240!$OMP THREADPRIVATE(E_gm)                                       
241  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S_gm          !! Entropy term for gm (J K-1 mol-1)
242!$OMP THREADPRIVATE(S_gm)                                       
243  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_gm          !! Energy of deactivation for gm (J mol-1)
244!$OMP THREADPRIVATE(D_gm)                                       
245         
246  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd          !! Energy of activation for Rd (J mol-1)
247!$OMP THREADPRIVATE(E_Rd)                                     
248  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25       !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
249                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
250!$OMP THREADPRIVATE(Vcmax25)
251  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)
252!$OMP THREADPRIVATE(arJV)
253  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)
254!$OMP THREADPRIVATE(brJV)
255  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25         !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
256!$OMP THREADPRIVATE(KmC25)                                     
257  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25         !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
258!$OMP THREADPRIVATE(KmO25)               
259REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Sco25           !! Relative CO2 /O2 specificity factor for Rubisco at 25°C (bar bar-1)
260!$OMP THREADPRIVATE(Sco25)     
261  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25  !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
262!$OMP THREADPRIVATE(gamma_star25)       
263  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gm25         !! Mesophyll diffusion conductance at 25°C (mol m−2 s−1 bar−1)
264!$OMP THREADPRIVATE(gm25)     
265  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a1            !! Empirical factor involved in the calculation of fvpd (-)
266!$OMP THREADPRIVATE(a1)                                       
267  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b1            !! Empirical factor involved in the calculation of fvpd (-)
268!$OMP THREADPRIVATE(b1)                                       
269  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: g0            !! Residual stomatal conductance when irradiance approaches zero (mol m−2 s−1 bar−1)
270!$OMP THREADPRIVATE(g0)                                       
271  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_protons     !! Number of protons required to produce one ATP (mol mol-1)
272!$OMP THREADPRIVATE(h_protons)                                 
273  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpsir         !! Fraction of PSII e− transport rate partitioned to the C4 cycle (-)
274!$OMP THREADPRIVATE(fpsir)                                         
275  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
276!$OMP THREADPRIVATE(fQ)                                       
277  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpseudo       !! Fraction of electrons at PSI that follow  pseudocyclic transport (-) - Values for C3 platns are not used
278!$OMP THREADPRIVATE(fpseudo)                                   
279  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kp            !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
280!$OMP THREADPRIVATE(kp)                                       
281  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha         !! Fraction of PSII activity in the bundle sheath (-)
282!$OMP THREADPRIVATE(alpha)                                     
283  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gbs           !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
284!$OMP THREADPRIVATE(gbs)                                       
285  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: theta         !! Convexity factor for response of J to irradiance (-)
286!$OMP THREADPRIVATE(theta)                                     
287  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_LL      !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
288!$OMP THREADPRIVATE(alpha_LL)
289  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_vcmax  !! Stress on vcmax
290!$OMP THREADPRIVATE(stress_vcmax)
291  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gs     !! Stress on vcmax
292!$OMP THREADPRIVATE(stress_gs)
293  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gm     !! Stress on vcmax
294!$OMP THREADPRIVATE(stress_gm)
295
296  !-
297  ! 2. Stomate
298  !-
299  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff     !! extinction coefficient of the Monsi&Saeki relationship (1953)
300                                                                !! (unitless)
301!$OMP THREADPRIVATE(ext_coeff)
302  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff_vegetfrac     !! extinction coefficient used for the calculation of the
303                                                                !! bare soil fraction (unitless)
304!$OMP THREADPRIVATE(ext_coeff_vegetfrac)
305
306  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff_N   !! extinction coefficient of the leaf N content profile within the canopy
307                                                                !! ((m2[ground]) (m-2[leaf]))
308                                                                !! based on Dewar et al. (2012, value of 0.18), on Carswell et al. (2000, value of 0.11 used in OCN)
309!$OMP THREADPRIVATE(ext_coeff_N)
310  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nue_opt       !! Nitrogen use efficiency of Vcmax
311                                                                !! ((mumol[CO2] s-1) (gN[leaf])-1)
312                                                                !! based on the work of Kattge et al. (2009, GCB)
313!$OMP THREADPRIVATE(nue_opt)
314
315
316
317  !
318  ! ALLOCATION (stomate)
319  !
320  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: R0            !! Default root allocation (0-1, unitless)
321!$OMP THREADPRIVATE(R0)
322  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0            !! Default sapwood allocation (0-1, unitless)
323!$OMP THREADPRIVATE(S0)
324  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0            !! Default leaf allocation (0-1, unitless)
325!$OMP THREADPRIVATE(L0)
326
327
328  !
329  ! RESPIRATION (stomate)
330  !
331  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp  !! fraction of GPP which is lost as growth respiration
332
333!$OMP THREADPRIVATE(frac_growthresp)
334
335  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_maint_init    !! maintenance respiration coefficient at 10 deg C,
336                                                                      !! @tex $(gC.gN^{-1}.day^{-1})$ @endtex
337!$OMP THREADPRIVATE(coeff_maint_init)
338
339  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tref_maint_resp     !! maintenance respiration Temperature coefficient,
340                                                                      !! @tex $(degC)$ @endtex
341!$OMP THREADPRIVATE(tref_maint_resp)
342
343  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_maint_resp     !! maintenance respiration Temperature coefficient,
344                                                                      !! @tex $(degC)$ @endtex
345!$OMP THREADPRIVATE(tmin_maint_resp)
346
347  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: e0_maint_resp     !! maintenance respiration Temperature coefficient,
348                                                                      !! @tex $(unitless)$ @endtex
349!$OMP THREADPRIVATE(e0_maint_resp)
350
351 
352  !
353  ! FIRE (stomate)
354  !
355  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
356                                                                    !! capacity (0-1, unitless)
357!$OMP THREADPRIVATE(flam)
358
359  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
360!$OMP THREADPRIVATE(resist)
361
362
363  !
364  ! FLUX - LUC (Land Use Change)
365  !
366  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1   !! Coeff of biomass export for the year (unitless)
367!$OMP THREADPRIVATE(coeff_lcchange_1)
368
369  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10  !! Coeff of biomass export for the decade (unitless)
370!$OMP THREADPRIVATE(coeff_lcchange_10)
371
372  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless)
373!$OMP THREADPRIVATE(coeff_lcchange_100)
374 
375 
376  !
377  ! PHENOLOGY
378  !
379  !-
380  ! 1. Stomate
381  !-
382  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy  !! threshold of LAI below which plant uses carbohydrate reserves
383!$OMP THREADPRIVATE(lai_max_to_happy)
384
385  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
386!$OMP THREADPRIVATE(lai_max)
387
388  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
389                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
390                                                                    !! 3=raingreen,  4=perennial
391                                                                    !! For the moment, the bare ground phenotype is not managed,
392                                                                    !! so it is considered as "evergreen"
393!$OMP THREADPRIVATE(pheno_type)
394
395  !-
396  ! 2. Leaf Onset
397  !-
398  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
399!$OMP THREADPRIVATE(pheno_gdd_crit)
400
401  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
402                                                                     !! constant c of aT^2+bT+c (unitless)
403!$OMP THREADPRIVATE(pheno_gdd_crit_c)
404
405  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
406                                                                     !! constant b of aT^2+bT+c (unitless)
407!$OMP THREADPRIVATE(pheno_gdd_crit_b)
408
409  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
410                                                                     !! constant a of aT^2+bT+c (unitless)
411!$OMP THREADPRIVATE(pheno_gdd_crit_a)
412
413  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C)
414!$OMP THREADPRIVATE(pheno_moigdd_t_crit)
415
416  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
417!$OMP THREADPRIVATE(ngd_crit)
418
419  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
420                                                                     !! in phenology (C)
421!$OMP THREADPRIVATE(ncdgdd_temp)
422
423  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
424                                                                     !! (0-1, unitless)
425!$OMP THREADPRIVATE(hum_frac)
426
427  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
428!$OMP THREADPRIVATE(hum_min_time)
429
430  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! sapwood -> heartwood conversion time (days)
431!$OMP THREADPRIVATE(tau_sap)
432
433  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit lifetime (days)
434!$OMP THREADPRIVATE(tau_fruit)
435
436  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_root           !! root turnover (1/days)
437!$OMP THREADPRIVATE(tau_root)
438
439  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit  !! time to attain the initial foliage using the carbohydrate reserve
440!$OMP THREADPRIVATE(tau_leafinit)
441
442  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
443                                                                     !! into reserve (0-1, unitless)
444!$OMP THREADPRIVATE(ecureuil)
445
446  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
447!$OMP THREADPRIVATE(alloc_min)
448
449  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
450!$OMP THREADPRIVATE(alloc_max)
451
452  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
453!$OMP THREADPRIVATE(demi_alloc)
454
455  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaflife_tab       !! leaf longevity, tabulated (??units??)
456!$OMP THREADPRIVATE(leaflife_tab)
457
458  !-
459  ! 3. Senescence
460  !-
461  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
462!$OMP THREADPRIVATE(leaffall)
463
464  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leafagecrit           !! critical leaf age,tabulated (days)
465!$OMP THREADPRIVATE(leafagecrit)
466
467  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
468                                                                        !! List of avaible types of senescence :
469                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
470!$OMP THREADPRIVATE(senescence_type)
471
472  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
473                                                                        !! (0-1, unitless)
474!$OMP THREADPRIVATE(senescence_hum)
475
476  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
477                                                                        !! no humidity-related senescence (0-1, unitless)
478!$OMP THREADPRIVATE(nosenescence_hum)
479
480  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
481!$OMP THREADPRIVATE(max_turnover_time)
482
483  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
484!$OMP THREADPRIVATE(min_turnover_time)
485
486  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: recycle_leaf          !! Fraction of N leaf that is recycled when leaves are senescent
487!$OMP THREADPRIVATE(recycle_leaf)
488
489  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: recycle_root          !! Fraction of N root that is recycled when leaves are senescent
490!$OMP THREADPRIVATE(recycle_root)
491
492
493REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Mrecycle_leaf          !! Fraction of N leaf that is recycled when leaves are senescent
494!$OMP THREADPRIVATE(Mrecycle_leaf)                                     !! after manure management
495
496  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Mrecycle_root          !! Fraction of N root that is recycled when leaves are senescent
497!$OMP THREADPRIVATE(Mrecycle_root)                                       !! after manure management
498
499  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
500!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
501
502  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
503                                                                        !! used in the code
504!$OMP THREADPRIVATE(senescence_temp)
505
506  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
507                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
508!$OMP THREADPRIVATE(senescence_temp_c)
509
510  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
511                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
512!$OMP THREADPRIVATE(senescence_temp_b)
513
514  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
515                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
516!$OMP THREADPRIVATE(senescence_temp_a)
517
518  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
519!$OMP THREADPRIVATE(gdd_senescence)
520
521  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: always_init               !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
522!$OMP THREADPRIVATE(always_init)
523
524  !-
525  ! 4. N cycle
526  !-
527  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_min           !! minimum CN ratio of leaves (gC/gN)
528!$OMP THREADPRIVATE(cn_leaf_min)
529
530  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_max           !! maximum CN ratio of leaves (gC/gN)
531!$OMP THREADPRIVATE(cn_leaf_max)
532
533  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_soil_n_bnf        !! Value of total N (NH4+NO3)
534                                                                        !! above which we stop adding N via BNF
535                                                                        !! (gN/m**2)
536!$OMP THREADPRIVATE(max_soil_n_bnf)
537
538  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: manure_pftweight      ! Weight of the distribution of manure over the PFT surface
539!$OMP THREADPRIVATE(manure_pftweight)
540
541REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: manure_graz_pftweight      ! Weight of the distribution of manure during grazing over the PFT surface
542!$OMP THREADPRIVATE(manure_graz_pftweight)
543
544  !
545  ! DGVM
546  !
547
548  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time        !! residence time of trees (y)
549!$OMP THREADPRIVATE(residence_time)
550
551  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit             !! critical tmin, tabulated (C)
552!$OMP THREADPRIVATE(tmin_crit)
553
554  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit              !! critical tcm, tabulated (C)
555!$OMP THREADPRIVATE(tcm_crit)
556
557  !
558  ! Biogenic Volatile Organic Compounds
559  !
560
561  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
562                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
563!$OMP THREADPRIVATE(em_factor_isoprene)
564
565  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
566                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
567!$OMP THREADPRIVATE(em_factor_monoterpene)
568
569  REAL(r_std), SAVE :: LDF_mono                                            !! monoterpenes fraction dependancy to light
570!$OMP THREADPRIVATE(LDF_mono)
571  REAL(r_std), SAVE :: LDF_sesq                                            !! sesquiterpenes fraction dependancy to light
572!$OMP THREADPRIVATE(LDF_sesq)
573  REAL(r_std), SAVE :: LDF_meth                                            !! methanol fraction dependancy to light
574!$OMP THREADPRIVATE(LDF_meth)
575  REAL(r_std), SAVE :: LDF_acet                                            !! acetone fraction dependancy to light
576!$OMP THREADPRIVATE(LDF_acet)
577  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene        !! Alfa pinene emission factor
578                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
579!$OMP THREADPRIVATE(em_factor_apinene)
580
581  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene        !! Beta pinene emission factor
582                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
583!$OMP THREADPRIVATE(em_factor_bpinene)
584
585  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene       !! Limonene emission factor
586                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
587!$OMP THREADPRIVATE(em_factor_limonene)
588
589  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene        !! Myrcene emission factor
590                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
591!$OMP THREADPRIVATE(em_factor_myrcene)
592
593  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene       !! Sabinene emission factor
594                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
595!$OMP THREADPRIVATE(em_factor_sabinene)
596
597  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene       !! Camphene emission factor
598                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
599!$OMP THREADPRIVATE(em_factor_camphene)
600
601  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene        !! 3-carene emission factor
602                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
603!$OMP THREADPRIVATE(em_factor_3carene)
604
605  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene      !! T-beta-ocimene emission factor
606                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
607!$OMP THREADPRIVATE(em_factor_tbocimene)
608
609  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot     !! Other monoterpenes emission factor
610                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
611!$OMP THREADPRIVATE(em_factor_othermonot)
612
613  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp     !! Sesquiterpene emission factor
614                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
615!$OMP THREADPRIVATE(em_factor_sesquiterp)
616
617  REAL(r_std), SAVE :: beta_mono                                           !! Monoterpenes temperature dependency coefficient
618!$OMP THREADPRIVATE(beta_mono)
619  REAL(r_std), SAVE :: beta_sesq                                           !! Sesquiterpenes temperature dependency coefficient
620!$OMP THREADPRIVATE(beta_sesq)
621  REAL(r_std), SAVE :: beta_meth                                           !! Methanol temperature dependency coefficient
622!$OMP THREADPRIVATE(beta_meth)
623  REAL(r_std), SAVE :: beta_acet                                           !! Acetone temperature dependency coefficient
624!$OMP THREADPRIVATE(beta_acet)
625  REAL(r_std), SAVE :: beta_oxyVOC                                         !! Other oxygenated BVOC temperature dependency coefficient
626!$OMP THREADPRIVATE(beta_oxyVOC)
627
628  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
629                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
630!$OMP THREADPRIVATE(em_factor_ORVOC)
631
632  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
633                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
634!$OMP THREADPRIVATE(em_factor_OVOC)
635
636  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
637                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
638!$OMP THREADPRIVATE(em_factor_MBO)
639
640  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
641                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
642!$OMP THREADPRIVATE(em_factor_methanol)
643
644  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
645                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
646!$OMP THREADPRIVATE(em_factor_acetone)
647
648  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
649                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
650!$OMP THREADPRIVATE(em_factor_acetal)
651
652  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
653                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
654!$OMP THREADPRIVATE(em_factor_formal)
655
656  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
657                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
658!$OMP THREADPRIVATE(em_factor_acetic)
659
660  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
661                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
662!$OMP THREADPRIVATE(em_factor_formic)
663
664  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
665                                                                           !! exponential dependancy factor for wet soils
666                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
667!$OMP THREADPRIVATE(em_factor_no_wet)
668
669  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
670                                                                           !! exponential dependancy factor for dry soils
671                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
672!$OMP THREADPRIVATE(em_factor_no_dry)
673
674  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
675!$OMP THREADPRIVATE(Larch)
676
677  !
678  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
679  !
680
681  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
682                                                                !! @tex $(m^2.m^{-2})$ @endtex
683!$OMP THREADPRIVATE(lai_initmin)
684
685  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl   !! sapling biomass @tex $(gC.ind^{-1})$ @endtex
686!$OMP THREADPRIVATE(bm_sapl)
687
688  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
689!$OMP THREADPRIVATE(migrate)
690
691  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
692                                                                !! increases (m)
693!$OMP THREADPRIVATE(maxdia)
694
695  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
696!$OMP THREADPRIVATE(cn_sapl)
697
698  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
699!$OMP THREADPRIVATE(leaf_timecst)
700
701  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_max       !! Maximum leaf-to-sapwood area ratio (unitless)
702!$OMP THREADPRIVATE(k_latosa_max)
703
704  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_latosa_min       !! Minimum leaf-to-sapwood area ratio (unitless)
705!$OMP THREADPRIVATE(k_latosa_min)
706
707 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: LC                 !! Lignin/C ratio of the different biomass pools and PFTs (unitless)
708                                                                      !! based on CN from White et al. (2000)
709!$OMP THREADPRIVATE(LC)
710
711 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_leaf              !! Lignin/C ratio of leaf pool (unitless)
712                                                                      !! based on CN from White et al. (2000)
713!$OMP THREADPRIVATE(LC_leaf)
714
715 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_sapabove          !! Lignin/C ratio of sapabove pool (unitless)
716                                                                      !! based on CN from White et al. (2000)
717!$OMP THREADPRIVATE(LC_sapabove)
718
719 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_sapbelow          !! Lignin/C ratio of sapbelow pool (unitless)
720                                                                      !! based on CN from White et al. (2000)
721!$OMP THREADPRIVATE(LC_sapbelow)
722
723 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_heartabove        !! Lignin/C ratio of heartabove pool (unitless)
724                                                                      !! based on CN from White et al. (2000)
725!$OMP THREADPRIVATE(LC_heartabove)
726
727 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_heartbelow        !! Lignin/C ratio of heartbelow pool (unitless)
728                                                                      !! based on CN from White et al. (2000)
729!$OMP THREADPRIVATE(LC_heartbelow)
730
731 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_fruit             !! Lignin/C ratio of fruit pool (unitless)
732                                                                      !! based on CN from White et al. (2000)
733!$OMP THREADPRIVATE(LC_fruit)
734
735 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_root              !! Lignin/C ratio of root pool (unitless)
736                                                                      !! based on CN from White et al. (2000)
737!$OMP THREADPRIVATE(LC_root)
738
739 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_carbres           !! Lignin/C ratio of carbres pool (unitless)
740                                                                      !! based on CN from White et al. (2000)
741!$OMP THREADPRIVATE(LC_carbres)
742
743 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: LC_labile            !! Lignin/C ratio of labile pool (unitless)
744                                                                      !! based on CN from White et al. (2000)
745!$OMP THREADPRIVATE(LC_labile)
746
747 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: decomp_factor        !! Multpliactive factor modifying
748                                                                      !! the standard decomposition factor for each SOM pool
749!$OMP THREADPRIVATE(decomp_factor)
750
751
752
753  !
754  ! STAND STRUCTURE (stomate)
755  !
756  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_density        !! Wood density in @tex $(gC.m^{-3})$ @endtex
757!$OMP THREADPRIVATE(pipe_density)
758
759  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune1          !! crown area = pipe_tune1*stem diameter**pipe_tune_exp_coeff
760!$OMP THREADPRIVATE(pipe_tune1)
761 
762  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune2          !! height=pipe_tune2 * diameter**pipe_tune3
763!$OMP THREADPRIVATE(pipe_tune2)     
764 
765  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune3          !! height=pipe_tune2 * diameter**pipe_tune3
766!$OMP THREADPRIVATE(pipe_tune3)     
767 
768  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune4          !! ???needed for stem diameter
769!$OMP THREADPRIVATE(pipe_tune4)     
770 
771  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_k1             !! ???
772!$OMP THREADPRIVATE(pipe_k1)       
773 
774  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pipe_tune_exp_coeff !! crown area = pipe_tune1*stem diameter**pipe_tune_exp_coeff
775!$OMP THREADPRIVATE(pipe_tune_exp_coeff)     
776 
777
778  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tree_ff             !! Volume reduction factor from cylinder to real tree shape (inc.branches)
779!$OMP THREADPRIVATE(tree_ff)
780  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: mass_ratio_heart_sap!! mass ratio (heartwood+sapwood)/heartwood
781!$OMP THREADPRIVATE(mass_ratio_heart_sap)
782
783  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: canopy_cover        !! Canopy cover - current values are guesses for testing
784                                                                      !! could tune this variable to match MODIS albedo
785!$OMP THREADPRIVATE(canopy_cover)
786   
787  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nmaxtrees      !! Intial number of seedlings per hectare. Used
788                                                                    !! in prescribe to initialize the model and after
789                                                                    !! every clearcut
790!$OMP THREADPRIVATE(nmaxtrees)
791  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_init_min   !! The minimum height of a tree sapling when a forest
792                                                                    !! stand is established. Owing to the allometric
793                                                                    !! relationship this setting determines all
794                                                                    !! biomass components of a newly establised stand
795                                                                    !! @tex $(m)$ @endtex
796!$OMP THREADPRIVATE(height_init_min)
797  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_init_max   !! The maximum height of a tree sapling when a forest
798                                                                    !! stand is established.
799                                                                    !! @tex $(m)$ @endtex
800!$OMP THREADPRIVATE(height_init_max)
801
802  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_root              !! Fine root specific conductivity
803                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
804!$OMP THREADPRIVATE(k_root)
805 
806  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: k_sap               !! Sapwood specific conductivity
807                                                                      !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex
808!$OMP THREADPRIVATE(k_sap)
809
810  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_to_height       !! Covert lai into vegetation height for grasses and crops
811!$OMP THREADPRIVATE(lai_to_height)   
812
813  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_a      !! intercept of the intra-tree competition within a stand
814                                                                    !! based on the competion rule of Deleuze and Dhote 2004
815                                                                    !! Used when n_circ > 6
816!$OMP THREADPRIVATE(deleuze_a)
817
818  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_b      !! slope of the intra-tree competition within a stand
819                                                                    !! based on the competion rule of Deleuze and Dhote 2004
820                                                                    !! Used when n_circ > 6
821!$OMP THREADPRIVATE(deleuze_b)
822
823  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)    :: deleuze_p_all  !! Percentile of the circumferences that receives photosynthates
824                                                                    !! based on the competion rule of Deleuze and Dhote 2004
825                                                                    !! Used when n_circ > 6 for FM1, FM2 and FM4
826!$OMP THREADPRIVATE(deleuze_p_all)
827
828  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: m_dv                !! Parameter in the Deleuze & Dhote allocation rule that
829                                                                      !! relaxes the cut-off imposed by ::sigma. Owing to m_relax
830                                                                      !! trees still grow a little when their ::circ is below
831                                                                      !! ::sigma
832!$OMP THREADPRIVATE(m_dv)
833
834  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fruit_alloc         !! Fraction of biomass allocated to fruit production (0-1)
835
836!$OMP THREADPRIVATE(fruit_alloc)
837
838 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: labile_reserve       !! The size of the labile pool as a fraction of the
839                                                                      !! weekly gpp (-). For example, 3 indicates that the
840                                                                      !! is 3 times the weekly gpp.
841!$OMP THREADPRIVATE(labile_reserve)
842
843 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: deciduous_reserve    !! Fraction of sapwood mass stored in the reserve pool of deciduous
844                                                                      !! trees during the growing season (unitless, 0-1)
845
846!$OMP THREADPRIVATE(deciduous_reserve)
847
848 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: evergreen_reserve    !! Fraction of sapwood mass stored in the reserve pool of evergreen
849                                                                      !! trees (unitless, 0-1)
850
851!$OMP THREADPRIVATE(evergreen_reserve)
852
853 REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescense_reserve   !! Fraction of sapwood mass stored in the reserve pool of deciduous
854                                                                      !! trees during senescense(unitless, 0-1)
855
856!$OMP THREADPRIVATE(senescense_reserve)
857
858  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_wood            !! CN ratio of wood for allocation, relative to leaf CN according
859                                                                      !! to Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
860!$OMP THREADPRIVATE(fcn_wood)
861
862  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fcn_root            !! CN of roots for allocation, relative to leaf CN according
863                                                                      !! to Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
864!$OMP THREADPRIVATE(fcn_root)
865
866  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: branch_ratio      !! branches/total aboveground biomass ratio
867                                                                    !! (cf carbofor for CITEPA inventory, these
868                                                                    !! Guerric, Lim 2004, Peischl 2007,
869                                                                    !! Schulp 2008: 15-30% slash after harvest,
870                                                                    !! Zaehle 2007: 30% slash after harvest)
871!$OMP THREADPRIVATE(branch_ratio)
872
873  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_leaf_init      !! CN of foliage for allocation, according to Sitch et al 2003
874                                                                    !! (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
875!$OMP THREADPRIVATE(cn_leaf_init)
876
877
878  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient
879                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
880!$OMP THREADPRIVATE(maint_resp_slope)
881
882  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
883                                                                      !! constant c of aT^2+bT+c , tabulated
884!$OMP THREADPRIVATE(maint_resp_slope_c)
885
886  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K),
887                                                                      !! constant b of aT^2+bT+c , tabulated
888!$OMP THREADPRIVATE(maint_resp_slope_b)
889
890  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K),
891                                                                      !! constant a of aT^2+bT+c , tabulated
892!$OMP THREADPRIVATE(maint_resp_slope_a)
893
894
895
896END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.