source: tags/ORCHIDEE_2_0/ORCHIDEE/src_parameters/pft_parameters_var.f90 @ 6392

Last change on this file since 6392 was 6392, checked in by josefine.ghattas, 5 years ago

Added new option for downregulation parametrization. Set DOWNREGULATION_CO2_NEW=y in run.def to activate. This option will be availble for configurations IPSLCM66.1.11 and later.

IF both DOWNREGULATION_CO2 and DOWNREGULATION_CO2_NEW are true, then DOWNREGULATION_CO2 will be set to false.

See ticket #641

  • Property svn:keywords set to Date Revision
File size: 41.0 KB
RevLine 
[720]1! =================================================================================================================================
[1475]2! MODULE       : pft_parameters_var
[720]3!
[4470]4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
[720]5!
[733]6! LICENCE      : IPSL (2011)
[720]7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
[1475]9!>\BRIEF        This module contains the variables in function of plant funtional type (pft).
[628]10!!
[1475]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
[628]15!!
[720]16!! RECENT CHANGE(S): None
[628]17!!
[720]18!! REFERENCE(S) : None
[628]19!!
[720]20!! SVN          :
21!! $HeadURL: $
22!! $Date$
23!! $Revision$
24!! \n
25!_ ================================================================================================================================
26
[1475]27MODULE pft_parameters_var
[511]28
[1078]29  USE defprec
[534]30 
31  IMPLICIT NONE
[511]32
33
[531]34  !
35  ! PFT GLOBAL
36  !
[720]37  INTEGER(i_std), SAVE :: nvm = 13                               !! Number of vegetation types (2-N, unitless)
[1078]38!$OMP THREADPRIVATE(nvm)
[511]39
[720]40  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pft_to_mtc  !! Table of conversion : we associate one pft to one metaclass
41                                                                 !! (1-13, unitless)
[1078]42!$OMP THREADPRIVATE(pft_to_mtc)
[531]43
[720]44  CHARACTER(LEN=34), ALLOCATABLE, SAVE, DIMENSION(:) :: PFT_name !! Description of the PFT (unitless)
[1078]45!$OMP THREADPRIVATE(PFT_name)
[720]46
[890]47  LOGICAL, SAVE   :: l_first_pft_parameters = .TRUE.             !! To keep first call trace of the module (true/false)
[1078]48!$OMP THREADPRIVATE(l_first_pft_parameters)
[720]49
[531]50  !
51  ! VEGETATION STRUCTURE
52  !
[1091]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
[720]61  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tree               !! Is the vegetation type a tree ? (true/false)
[1078]62!$OMP THREADPRIVATE(is_tree)
[720]63
64  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_deciduous          !! Is PFT deciduous ? (true/false)
[1078]65!$OMP THREADPRIVATE(is_deciduous)
[720]66
67  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_evergreen          !! Is PFT evegreen ? (true/false)
[1078]68!$OMP THREADPRIVATE(is_evergreen)
[720]69
[890]70  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_needleleaf         !! Is PFT needleleaf ? (true/false)
[1078]71!$OMP THREADPRIVATE(is_needleleaf)
[890]72 
73  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tropical           !! Is PFT tropical ? (true/false)
[1078]74!$OMP THREADPRIVATE(is_tropical)
[890]75
[1091]76  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: natural               !! natural? (true/false)
77!$OMP THREADPRIVATE(natural)
[890]78
[720]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
[1078]83!$OMP THREADPRIVATE(type_of_lai)
[1091]84
[720]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)
[1078]87!$OMP THREADPRIVATE(veget_ori_fixed_test_1)
[720]88
89  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimax                !! laimax for maximum lai see also type of lai
[1082]90                                                                         !! interpolation
91                                                                         !! @tex $(m^2.m^{-2})$ @endtex
[1078]92!$OMP THREADPRIVATE(llaimax)
[720]93
94  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimin                !! laimin for minimum lai see also type of lai
[1082]95                                                                         !! interpolation
96                                                                         !! @tex $(m^2.m^{-2})$ @endtex
[1078]97!$OMP THREADPRIVATE(llaimin)
[720]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
[1078]101!$OMP THREADPRIVATE(height_presc)
[720]102
[3524]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
[720]110  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) ::  rveg_pft              !! Potentiometer to set vegetation resistance (unitless)
111                                                                         !! Nathalie on March 28th, 2006 - from Fred Hourdin,
[1078]112!$OMP THREADPRIVATE(rveg_pft)
[720]113
[1082]114  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sla                    !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
[1078]115!$OMP THREADPRIVATE(sla)
[511]116
[2668]117  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: availability_fact      !! calculate dynamic mortality in lpj_gap
118!$OMP THREADPRIVATE(availability_fact)
119
[511]120  !
[531]121  ! EVAPOTRANSPIRATION (sechiba)
122  !
[1082]123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const          !! Structural resistance.
[720]124                                                                         !! Value for rstruct_const : one for each vegetation type
[1082]125                                                                         !! @tex $(s.m^{-1})$ @endtex
[1078]126!$OMP THREADPRIVATE(rstruct_const)
[511]127
[720]128  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero                  !! A vegetation dependent constant used in the calculation
[1082]129                                                                         !! of the surface resistance.
[720]130                                                                         !! Value for kzero one for each vegetation type
[1082]131                                                                         !! @tex $(kg.m^2.s^{-1})$ @endtex
[1078]132!$OMP THREADPRIVATE(kzero)
[511]133
[531]134  !
135  ! WATER (sechiba)
136  !
[1082]137  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wmax_veg  !! Volumetric available soil water capacity in each PFT
138                                                            !! @tex $(kg.m^{-3} of soil)$ @endtex
[1078]139!$OMP THREADPRIVATE(wmax_veg)
[511]140
[720]141  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: humcste   !! Root profile description for the different vegetation types.
142                                                            !! These are the factor in the exponential which gets
[1082]143                                                            !! the root density as a function of depth
144                                                            !! @tex $(m^{-1})$ @endtex
[1078]145!$OMP THREADPRIVATE(humcste)
[511]146
[4752]147  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft !! Percent by PFT of precip that is not intercepted by the canopy
[1078]148!$OMP THREADPRIVATE(throughfall_by_pft)
[720]149
[511]150  !
[531]151  ! ALBEDO (sechiba)
[511]152  !
[3599]153  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_vis !! Minimum snow albedo value for each vegetation type
154                                                                 !! after aging (dirty old snow), visible albedo (unitless)
155                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
156!$OMP THREADPRIVATE(snowa_aged_vis)
[511]157
[3599]158  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_nir !! Minimum snow albedo value for each vegetation type
159                                                                 !! after aging (dirty old snow), near infrared albedo (unitless)
160                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
161!$OMP THREADPRIVATE(snowa_aged_nir)
[511]162
[3599]163  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_vis  !! Decay rate of snow albedo value for each vegetation type
164                                                                 !! as it will be used in condveg_snow, visible albedo (unitless)
165                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
166!$OMP THREADPRIVATE(snowa_dec_vis)
167
168  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_nir  !! Decay rate of snow albedo value for each vegetation type
169                                                                 !! as it will be used in condveg_snow, near infrared albedo (unitless)
170                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
171!$OMP THREADPRIVATE(snowa_dec_nir)
172
[720]173  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis  !! leaf albedo of vegetation type, visible albedo (unitless)
[1078]174!$OMP THREADPRIVATE(alb_leaf_vis)
[720]175
176  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir  !! leaf albedo of vegetation type, near infrared albedo (unitless)
[1078]177!$OMP THREADPRIVATE(alb_leaf_nir)
[720]178
[511]179  !
[531]180  ! SOIL - VEGETATION
181  !
[947]182  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg      !! Table which contains the correlation between the soil
[720]183                                                                        !! types and vegetation type. Two modes exist :
184                                                                        !! 1) pref_soil_veg = 0 then we have an equidistribution
185                                                                        !!    of vegetation on soil types
186                                                                        !! 2) Else for each pft the prefered soil type is given :
187                                                                        !!    1=sand, 2=loan, 3=clay
188                                                                        !! This variable is initialized in slowproc.(1-3, unitless)
[1078]189!$OMP THREADPRIVATE(pref_soil_veg)
[511]190
[531]191  !
192  ! PHOTOSYNTHESIS
193  !
[511]194  !-
[531]195  ! 1. CO2
[511]196  !-
[720]197  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4             !! flag for C4 vegetation types (true/false)
[1078]198!$OMP THREADPRIVATE(is_c4)
[720]199
200  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix     !! values used for vcmax when STOMATE is not activated
[1082]201                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
[1078]202!$OMP THREADPRIVATE(vcmax_fix)
[720]203
[6392]204  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation if downregulation_co2 (used for CMIP6 6.1.0-6.1.10) (unitless)
[1882]205!$OMP THREADPRIVATE(downregulation_co2_coeff)
206
[6392]207  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff_new !! Coefficient for CO2 downregulation if downregulation_co2_new (used for CMIP6 6.1.11) (unitless)
208!$OMP THREADPRIVATE(downregulation_co2_coeff_new)
209
[2031]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)         
[3972]214REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Sco           !! Energy of activation for Sco (J mol-1)
215!$OMP THREADPRIVATE(E_Sco)           
[2031]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)
[3972]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         
[2031]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)               
[3972]259REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Sco25           !! Relative CO2 /O2 specificity factor for Rubisco at 25°C (bar bar-1)
260!$OMP THREADPRIVATE(Sco25)     
[2031]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)       
[3972]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)     
[2031]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 (-)
[2058]274!$OMP THREADPRIVATE(fpsir)                                         
[2031]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)
[3972]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)
[1882]295
[511]296  !-
[531]297  ! 2. Stomate
[511]298  !-
[720]299  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff     !! extinction coefficient of the Monsi&Saeki relationship (1953)
300                                                                !! (unitless)
[1078]301!$OMP THREADPRIVATE(ext_coeff)
[3524]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)
[511]305
306
307  !
[1882]308  ! ALLOCATION (stomate)
309  !
[2282]310  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: R0            !! Default root allocation (0-1, unitless)
311!$OMP THREADPRIVATE(R0)
[1882]312  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0            !! Default sapwood allocation (0-1, unitless)
313!$OMP THREADPRIVATE(S0)
314  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0            !! Default leaf allocation (0-1, unitless)
315!$OMP THREADPRIVATE(L0)
316
317
318  !
[531]319  ! RESPIRATION (stomate)
320  !
[2282]321  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp  !! fraction of GPP which is lost as growth respiration
322
323!$OMP THREADPRIVATE(frac_growthresp)
324
[720]325  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient
326                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
[1078]327!$OMP THREADPRIVATE(maint_resp_slope)
[511]328
[720]329  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
330                                                                      !! constant c of aT^2+bT+c , tabulated
[1078]331!$OMP THREADPRIVATE(maint_resp_slope_c)
[720]332
333  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K),
334                                                                      !! constant b of aT^2+bT+c , tabulated
[1078]335!$OMP THREADPRIVATE(maint_resp_slope_b)
[720]336
337  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K),
338                                                                      !! constant a of aT^2+bT+c , tabulated
[1078]339!$OMP THREADPRIVATE(maint_resp_slope_a)
[720]340
341  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: coeff_maint_zero  !! maintenance respiration coefficient at 0 deg C,
[1082]342                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]343!$OMP THREADPRIVATE(coeff_maint_zero)
[720]344
345  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_leaf        !! maintenance respiration coefficient at 0 deg C,
[1082]346                                                                      !! for leaves, tabulated
347                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]348!$OMP THREADPRIVATE(cm_zero_leaf)
[720]349
350  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapabove    !! maintenance respiration coefficient at 0 deg C,
[1082]351                                                                      !! for sapwood above, tabulated
352                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]353!$OMP THREADPRIVATE(cm_zero_sapabove)
[720]354
355  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapbelow    !! maintenance respiration coefficient at 0 deg C,
[1082]356                                                                      !! for sapwood below, tabulated
357                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]358!$OMP THREADPRIVATE(cm_zero_sapbelow)
[720]359
360  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartabove  !! maintenance respiration coefficient at 0 deg C
[1082]361                                                                      !! for heartwood above, tabulated
362                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]363!$OMP THREADPRIVATE(cm_zero_heartabove)
[720]364
365  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartbelow  !! maintenance respiration coefficient at 0 deg C,
[1082]366                                                                      !! for heartwood below, tabulated
367                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]368!$OMP THREADPRIVATE(cm_zero_heartbelow)
[720]369
370  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_root        !! maintenance respiration coefficient at 0 deg C,
[1082]371                                                                      !! for roots, tabulated
372                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]373!$OMP THREADPRIVATE(cm_zero_root)
[720]374
375  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_fruit       !! maintenance respiration coefficient  at 0 deg C,
[1082]376                                                                      !! for fruits, tabulated
377                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]378!$OMP THREADPRIVATE(cm_zero_fruit)
[720]379
380  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_carbres     !! maintenance respiration coefficient at 0 deg C,
[1082]381                                                                      !! for carbohydrate reserve, tabulated
382                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[1078]383!$OMP THREADPRIVATE(cm_zero_carbres)
[720]384
[511]385 
386  !
[531]387  ! FIRE (stomate)
388  !
[720]389  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
390                                                                    !! capacity (0-1, unitless)
[1078]391!$OMP THREADPRIVATE(flam)
[511]392
[720]393  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
[1078]394!$OMP THREADPRIVATE(resist)
[511]395
[720]396
[511]397  !
[720]398  ! FLUX - LUC (Land Use Change)
[531]399  !
[720]400  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1   !! Coeff of biomass export for the year (unitless)
[1078]401!$OMP THREADPRIVATE(coeff_lcchange_1)
[720]402
403  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10  !! Coeff of biomass export for the decade (unitless)
[1078]404!$OMP THREADPRIVATE(coeff_lcchange_10)
[720]405
406  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless)
[1078]407!$OMP THREADPRIVATE(coeff_lcchange_100)
[511]408 
[531]409 
410  !
411  ! PHENOLOGY
412  !
[511]413  !-
[531]414  ! 1. Stomate
[511]415  !-
[2282]416  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy  !! threshold of LAI below which plant uses carbohydrate reserves
417!$OMP THREADPRIVATE(lai_max_to_happy)
418
[1082]419  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
[1078]420!$OMP THREADPRIVATE(lai_max)
[720]421
422  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
423                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
424                                                                    !! 3=raingreen,  4=perennial
425                                                                    !! For the moment, the bare ground phenotype is not managed,
426                                                                    !! so it is considered as "evergreen"
[1078]427!$OMP THREADPRIVATE(pheno_type)
[1091]428
[511]429  !-
430  ! 2. Leaf Onset
431  !-
[720]432  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
[1078]433!$OMP THREADPRIVATE(pheno_gdd_crit)
[720]434
435  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
436                                                                     !! constant c of aT^2+bT+c (unitless)
[1078]437!$OMP THREADPRIVATE(pheno_gdd_crit_c)
[720]438
439  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
440                                                                     !! constant b of aT^2+bT+c (unitless)
[1078]441!$OMP THREADPRIVATE(pheno_gdd_crit_b)
[720]442
443  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
444                                                                     !! constant a of aT^2+bT+c (unitless)
[1078]445!$OMP THREADPRIVATE(pheno_gdd_crit_a)
[720]446
[2665]447  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C)
448!$OMP THREADPRIVATE(pheno_moigdd_t_crit)
449
[720]450  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
[1078]451!$OMP THREADPRIVATE(ngd_crit)
[720]452
453  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
454                                                                     !! in phenology (C)
[1078]455!$OMP THREADPRIVATE(ncdgdd_temp)
[720]456
457  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
458                                                                     !! (0-1, unitless)
[1078]459!$OMP THREADPRIVATE(hum_frac)
[720]460
461  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
[1078]462!$OMP THREADPRIVATE(hum_min_time)
[720]463
464  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! sapwood -> heartwood conversion time (days)
[1078]465!$OMP THREADPRIVATE(tau_sap)
[720]466
467  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit lifetime (days)
[1078]468!$OMP THREADPRIVATE(tau_fruit)
[720]469
[2282]470  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit  !! time to attain the initial foliage using the carbohydrate reserve
471!$OMP THREADPRIVATE(tau_leafinit)
472
[720]473  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
474                                                                     !! into reserve (0-1, unitless)
[1078]475!$OMP THREADPRIVATE(ecureuil)
[720]476
477  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
[1078]478!$OMP THREADPRIVATE(alloc_min)
[720]479
480  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
[1078]481!$OMP THREADPRIVATE(alloc_max)
[720]482
483  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
[1078]484!$OMP THREADPRIVATE(demi_alloc)
[720]485
486  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaflife_tab       !! leaf longevity, tabulated (??units??)
[1078]487!$OMP THREADPRIVATE(leaflife_tab)
[1091]488
[511]489  !-
490  ! 3. Senescence
491  !-
[720]492  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
[1078]493!$OMP THREADPRIVATE(leaffall)
[511]494
[720]495  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leafagecrit           !! critical leaf age,tabulated (days)
[1078]496!$OMP THREADPRIVATE(leafagecrit)
[511]497
[720]498  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
499                                                                        !! List of avaible types of senescence :
500                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
[1078]501!$OMP THREADPRIVATE(senescence_type)
[720]502
503  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
504                                                                        !! (0-1, unitless)
[1078]505!$OMP THREADPRIVATE(senescence_hum)
[720]506
507  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
508                                                                        !! no humidity-related senescence (0-1, unitless)
[1078]509!$OMP THREADPRIVATE(nosenescence_hum)
[720]510
511  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
[1078]512!$OMP THREADPRIVATE(max_turnover_time)
[720]513
514  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
[1078]515!$OMP THREADPRIVATE(min_turnover_time)
[720]516
517  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
[1078]518!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
[720]519
[733]520  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
[720]521                                                                        !! used in the code
[1078]522!$OMP THREADPRIVATE(senescence_temp)
[720]523
524  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
525                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
[1078]526!$OMP THREADPRIVATE(senescence_temp_c)
[720]527
528  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
529                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
[1078]530!$OMP THREADPRIVATE(senescence_temp_b)
[720]531
532  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
533                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
[1078]534!$OMP THREADPRIVATE(senescence_temp_a)
[720]535
[1102]536  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
537!$OMP THREADPRIVATE(gdd_senescence)
[720]538
[4902]539  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: always_init               !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
540!$OMP THREADPRIVATE(always_init)
541
[531]542  !
[511]543  ! DGVM
[531]544  !
[890]545
[720]546  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time        !! residence time of trees (y)
[1078]547!$OMP THREADPRIVATE(residence_time)
[511]548
[720]549  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit             !! critical tmin, tabulated (C)
[1078]550!$OMP THREADPRIVATE(tmin_crit)
[720]551
552  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit              !! critical tcm, tabulated (C)
[1078]553!$OMP THREADPRIVATE(tcm_crit)
[720]554
[511]555  !
[890]556  ! Biogenic Volatile Organic Compounds
557  !
558
559  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
[1082]560                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]561!$OMP THREADPRIVATE(em_factor_isoprene)
[890]562
563  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
[1082]564                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]565!$OMP THREADPRIVATE(em_factor_monoterpene)
[890]566
[3221]567  REAL(r_std), SAVE :: LDF_mono                                            !! monoterpenes fraction dependancy to light
568!$OMP THREADPRIVATE(LDF_mono)
569  REAL(r_std), SAVE :: LDF_sesq                                            !! sesquiterpenes fraction dependancy to light
570!$OMP THREADPRIVATE(LDF_sesq)
571  REAL(r_std), SAVE :: LDF_meth                                            !! methanol fraction dependancy to light
572!$OMP THREADPRIVATE(LDF_meth)
573  REAL(r_std), SAVE :: LDF_acet                                            !! acetone fraction dependancy to light
574!$OMP THREADPRIVATE(LDF_acet)
575  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene        !! Alfa pinene emission factor
576                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
577!$OMP THREADPRIVATE(em_factor_apinene)
578
579  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene        !! Beta pinene emission factor
580                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
581!$OMP THREADPRIVATE(em_factor_bpinene)
582
583  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene       !! Limonene emission factor
584                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
585!$OMP THREADPRIVATE(em_factor_limonene)
586
587  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene        !! Myrcene emission factor
588                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
589!$OMP THREADPRIVATE(em_factor_myrcene)
590
591  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene       !! Sabinene emission factor
592                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
593!$OMP THREADPRIVATE(em_factor_sabinene)
594
595  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene       !! Camphene emission factor
596                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
597!$OMP THREADPRIVATE(em_factor_camphene)
598
599  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene        !! 3-carene emission factor
600                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
601!$OMP THREADPRIVATE(em_factor_3carene)
602
603  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene      !! T-beta-ocimene emission factor
604                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
605!$OMP THREADPRIVATE(em_factor_tbocimene)
606
607  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot     !! Other monoterpenes emission factor
608                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
609!$OMP THREADPRIVATE(em_factor_othermonot)
610
611  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp     !! Sesquiterpene emission factor
612                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
613!$OMP THREADPRIVATE(em_factor_sesquiterp)
614
615  REAL(r_std), SAVE :: beta_mono                                           !! Monoterpenes temperature dependency coefficient
616!$OMP THREADPRIVATE(beta_mono)
617  REAL(r_std), SAVE :: beta_sesq                                           !! Sesquiterpenes temperature dependency coefficient
618!$OMP THREADPRIVATE(beta_sesq)
619  REAL(r_std), SAVE :: beta_meth                                           !! Methanol temperature dependency coefficient
620!$OMP THREADPRIVATE(beta_meth)
621  REAL(r_std), SAVE :: beta_acet                                           !! Acetone temperature dependency coefficient
622!$OMP THREADPRIVATE(beta_acet)
623  REAL(r_std), SAVE :: beta_oxyVOC                                         !! Other oxygenated BVOC temperature dependency coefficient
624!$OMP THREADPRIVATE(beta_oxyVOC)
625
[890]626  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
[1082]627                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]628!$OMP THREADPRIVATE(em_factor_ORVOC)
[890]629
630  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
[1082]631                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]632!$OMP THREADPRIVATE(em_factor_OVOC)
[890]633
634  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
[1082]635                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]636!$OMP THREADPRIVATE(em_factor_MBO)
[890]637
638  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
[1082]639                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]640!$OMP THREADPRIVATE(em_factor_methanol)
[890]641
642  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
[1082]643                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]644!$OMP THREADPRIVATE(em_factor_acetone)
[890]645
646  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
[1082]647                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]648!$OMP THREADPRIVATE(em_factor_acetal)
[890]649
650  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
[1082]651                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]652!$OMP THREADPRIVATE(em_factor_formal)
[890]653
654  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
[1082]655                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]656!$OMP THREADPRIVATE(em_factor_acetic)
[890]657
658  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
[1082]659                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[1078]660!$OMP THREADPRIVATE(em_factor_formic)
[890]661
662  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
663                                                                           !! exponential dependancy factor for wet soils
[1082]664                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
[1078]665!$OMP THREADPRIVATE(em_factor_no_wet)
[890]666
667  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
668                                                                           !! exponential dependancy factor for dry soils
[1082]669                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
[1078]670!$OMP THREADPRIVATE(em_factor_no_dry)
[890]671
672  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
[1078]673!$OMP THREADPRIVATE(Larch)
[890]674
675  !
[531]676  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
677  !
[890]678
[1082]679  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
680                                                                !! @tex $(m^2.m^{-2})$ @endtex
[1078]681!$OMP THREADPRIVATE(lai_initmin)
[511]682
[1170]683  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl   !! sapling biomass @tex $(gC.ind^{-1})$ @endtex
[1078]684!$OMP THREADPRIVATE(bm_sapl)
[720]685
[1082]686  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
[1078]687!$OMP THREADPRIVATE(migrate)
[720]688
689  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
[1078]690                                                                !! increases (m)
691!$OMP THREADPRIVATE(maxdia)
[720]692
[1082]693  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
[1078]694!$OMP THREADPRIVATE(cn_sapl)
[720]695
696  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
[1078]697!$OMP THREADPRIVATE(leaf_timecst)
[720]698
699
[1475]700END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.