source: branches/publications/ORCHIDEE-LEAK-r5919/src_parameters/pft_parameters_var.f90 @ 5925

Last change on this file since 5925 was 3221, checked in by josefine.ghattas, 8 years ago

Ticket #230 : modifications related to BVOC
J Lathiere, P Messina, A Cozic

  • Property svn:keywords set to Date Revision
File size: 37.8 KB
Line 
1! =================================================================================================================================
2! MODULE       : pft_parameters_var
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module contains the variables in function of plant funtional type (pft).
10!!
11!!\n DESCRIPTION: This module contains the declarations for the externalized variables in function of the
12!!                plant foncional type(pft). \n
13!!                The module is already USE in module pft_parameters. Therefor no need to USE it seperatly except
14!!                if the subroutines in module pft_parameters are not needed.\n
15!!
16!! RECENT CHANGE(S): None
17!!
18!! REFERENCE(S) : None
19!!
20!! SVN          :
21!! $HeadURL: $
22!! $Date$
23!! $Revision$
24!! \n
25!_ ================================================================================================================================
26
27MODULE pft_parameters_var
28
29  USE defprec
30 
31  IMPLICIT NONE
32
33
34  !
35  ! PFT GLOBAL
36  !
37  INTEGER(i_std), SAVE :: nvm = 13                               !! Number of vegetation types (2-N, unitless)
38!$OMP THREADPRIVATE(nvm)
39
40  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pft_to_mtc  !! Table of conversion : we associate one pft to one metaclass
41                                                                 !! (1-13, unitless)
42!$OMP THREADPRIVATE(pft_to_mtc)
43
44  CHARACTER(LEN=34), ALLOCATABLE, SAVE, DIMENSION(:) :: PFT_name !! Description of the PFT (unitless)
45!$OMP THREADPRIVATE(PFT_name)
46
47  LOGICAL, SAVE   :: l_first_pft_parameters = .TRUE.             !! To keep first call trace of the module (true/false)
48!$OMP THREADPRIVATE(l_first_pft_parameters)
49
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(:) ::  rveg_pft              !! Potentiometer to set vegetation resistance (unitless)
104                                                                         !! Nathalie on March 28th, 2006 - from Fred Hourdin,
105!$OMP THREADPRIVATE(rveg_pft)
106
107  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sla                    !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
108!$OMP THREADPRIVATE(sla)
109
110  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: availability_fact      !! calculate dynamic mortality in lpj_gap
111!$OMP THREADPRIVATE(availability_fact)
112
113  !
114  ! EVAPOTRANSPIRATION (sechiba)
115  !
116  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const          !! Structural resistance.
117                                                                         !! Value for rstruct_const : one for each vegetation type
118                                                                         !! @tex $(s.m^{-1})$ @endtex
119!$OMP THREADPRIVATE(rstruct_const)
120
121  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero                  !! A vegetation dependent constant used in the calculation
122                                                                         !! of the surface resistance.
123                                                                         !! Value for kzero one for each vegetation type
124                                                                         !! @tex $(kg.m^2.s^{-1})$ @endtex
125!$OMP THREADPRIVATE(kzero)
126
127  !
128  ! WATER (sechiba)
129  !
130  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wmax_veg  !! Volumetric available soil water capacity in each PFT
131                                                            !! @tex $(kg.m^{-3} of soil)$ @endtex
132!$OMP THREADPRIVATE(wmax_veg)
133
134  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: humcste   !! Root profile description for the different vegetation types.
135                                                            !! These are the factor in the exponential which gets
136                                                            !! the root density as a function of depth
137                                                            !! @tex $(m^{-1})$ @endtex
138!$OMP THREADPRIVATE(humcste)
139
140  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft !! Fraction of rain intercepted by the canopy (0-100, unitless)
141!$OMP THREADPRIVATE(throughfall_by_pft)
142
143  !
144  ! ALBEDO (sechiba)
145  !
146  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged    !! Minimum snow albedo value for each vegetation type
147                                                                !! after aging (dirty old snow) (unitless)
148                                                                !! Source : Values are from the Thesis of S. Chalita (1992)
149!$OMP THREADPRIVATE(snowa_aged)
150
151  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec     !! Decay rate of snow albedo value for each vegetation type
152                                                                !! as it will be used in condveg_snow (unitless)
153                                                                !! Source : Values are from the Thesis of S. Chalita (1992)
154!$OMP THREADPRIVATE(snowa_dec)
155
156  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis  !! leaf albedo of vegetation type, visible albedo (unitless)
157!$OMP THREADPRIVATE(alb_leaf_vis)
158
159  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir  !! leaf albedo of vegetation type, near infrared albedo (unitless)
160!$OMP THREADPRIVATE(alb_leaf_nir)
161
162  !
163  ! SOIL - VEGETATION
164  !
165  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg      !! Table which contains the correlation between the soil
166                                                                        !! types and vegetation type. Two modes exist :
167                                                                        !! 1) pref_soil_veg = 0 then we have an equidistribution
168                                                                        !!    of vegetation on soil types
169                                                                        !! 2) Else for each pft the prefered soil type is given :
170                                                                        !!    1=sand, 2=loan, 3=clay
171                                                                        !! This variable is initialized in slowproc.(1-3, unitless)
172!$OMP THREADPRIVATE(pref_soil_veg)
173
174  !
175  ! PHOTOSYNTHESIS
176  !
177  !-
178  ! 1. CO2
179  !-
180  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4             !! flag for C4 vegetation types (true/false)
181!$OMP THREADPRIVATE(is_c4)
182
183  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix     !! values used for vcmax when STOMATE is not activated
184                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
185!$OMP THREADPRIVATE(vcmax_fix)
186
187  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation (unitless)
188!$OMP THREADPRIVATE(downregulation_co2_coeff)
189
190  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC         !! Energy of activation for KmC (J mol-1)
191!$OMP THREADPRIVATE(E_KmC)                                                               
192  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO         !! Energy of activation for KmO (J mol-1)
193!$OMP THREADPRIVATE(E_KmO)         
194  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star  !! Energy of activation for gamma_star (J mol-1)
195!$OMP THREADPRIVATE(E_gamma_star)   
196  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax       !! Energy of activation for Vcmax (J mol-1)
197!$OMP THREADPRIVATE(E_Vcmax)                                                             
198  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax        !! Energy of activation for Jmax (J mol-1)
199!$OMP THREADPRIVATE(E_Jmax)
200  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)
201!$OMP THREADPRIVATE(aSV)   
202  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)
203!$OMP THREADPRIVATE(bSV)
204  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min   !! minimum photosynthesis temperature (deg C)
205!$OMP THREADPRIVATE(tphoto_min)
206  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max   !! maximum photosynthesis temperature (deg C)
207!$OMP THREADPRIVATE(tphoto_max)
208  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)
209!$OMP THREADPRIVATE(aSJ)   
210  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)
211!$OMP THREADPRIVATE(bSJ)   
212  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax       !! Energy of deactivation for Vcmax (J mol-1)
213!$OMP THREADPRIVATE(D_Vcmax)                     
214  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax        !! Energy of deactivation for Jmax (J mol-1)
215!$OMP THREADPRIVATE(D_Jmax)                                   
216  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd          !! Energy of activation for Rd (J mol-1)
217!$OMP THREADPRIVATE(E_Rd)                                     
218  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25       !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
219                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
220!$OMP THREADPRIVATE(Vcmax25)
221  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)
222!$OMP THREADPRIVATE(arJV)
223  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)
224!$OMP THREADPRIVATE(brJV)
225  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25         !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
226!$OMP THREADPRIVATE(KmC25)                                     
227  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25         !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
228!$OMP THREADPRIVATE(KmO25)               
229  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25  !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
230!$OMP THREADPRIVATE(gamma_star25)       
231  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a1            !! Empirical factor involved in the calculation of fvpd (-)
232!$OMP THREADPRIVATE(a1)                                       
233  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b1            !! Empirical factor involved in the calculation of fvpd (-)
234!$OMP THREADPRIVATE(b1)                                       
235  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: g0            !! Residual stomatal conductance when irradiance approaches zero (mol m−2 s−1 bar−1)
236!$OMP THREADPRIVATE(g0)                                       
237  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_protons     !! Number of protons required to produce one ATP (mol mol-1)
238!$OMP THREADPRIVATE(h_protons)                                 
239  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpsir         !! Fraction of PSII e− transport rate partitioned to the C4 cycle (-)
240!$OMP THREADPRIVATE(fpsir)                                         
241  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
242!$OMP THREADPRIVATE(fQ)                                       
243  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpseudo       !! Fraction of electrons at PSI that follow  pseudocyclic transport (-) - Values for C3 platns are not used
244!$OMP THREADPRIVATE(fpseudo)                                   
245  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kp            !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
246!$OMP THREADPRIVATE(kp)                                       
247  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha         !! Fraction of PSII activity in the bundle sheath (-)
248!$OMP THREADPRIVATE(alpha)                                     
249  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gbs           !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
250!$OMP THREADPRIVATE(gbs)                                       
251  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: theta         !! Convexity factor for response of J to irradiance (-)
252!$OMP THREADPRIVATE(theta)                                     
253  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_LL      !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
254!$OMP THREADPRIVATE(alpha_LL)
255
256
257  !-
258  ! 2. Stomate
259  !-
260  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff     !! extinction coefficient of the Monsi&Saeki relationship (1953)
261                                                                !! (unitless)
262!$OMP THREADPRIVATE(ext_coeff)
263
264
265  !
266  ! ALLOCATION (stomate)
267  !
268  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: R0            !! Default root allocation (0-1, unitless)
269!$OMP THREADPRIVATE(R0)
270  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0            !! Default sapwood allocation (0-1, unitless)
271!$OMP THREADPRIVATE(S0)
272  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0            !! Default leaf allocation (0-1, unitless)
273!$OMP THREADPRIVATE(L0)
274
275
276  !
277  ! RESPIRATION (stomate)
278  !
279  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp  !! fraction of GPP which is lost as growth respiration
280
281!$OMP THREADPRIVATE(frac_growthresp)
282
283  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient
284                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
285!$OMP THREADPRIVATE(maint_resp_slope)
286
287  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
288                                                                      !! constant c of aT^2+bT+c , tabulated
289!$OMP THREADPRIVATE(maint_resp_slope_c)
290
291  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K),
292                                                                      !! constant b of aT^2+bT+c , tabulated
293!$OMP THREADPRIVATE(maint_resp_slope_b)
294
295  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K),
296                                                                      !! constant a of aT^2+bT+c , tabulated
297!$OMP THREADPRIVATE(maint_resp_slope_a)
298
299  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: coeff_maint_zero  !! maintenance respiration coefficient at 0 deg C,
300                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
301!$OMP THREADPRIVATE(coeff_maint_zero)
302
303  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_leaf        !! maintenance respiration coefficient at 0 deg C,
304                                                                      !! for leaves, tabulated
305                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
306!$OMP THREADPRIVATE(cm_zero_leaf)
307
308  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapabove    !! maintenance respiration coefficient at 0 deg C,
309                                                                      !! for sapwood above, tabulated
310                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
311!$OMP THREADPRIVATE(cm_zero_sapabove)
312
313  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapbelow    !! maintenance respiration coefficient at 0 deg C,
314                                                                      !! for sapwood below, tabulated
315                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
316!$OMP THREADPRIVATE(cm_zero_sapbelow)
317
318  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartabove  !! maintenance respiration coefficient at 0 deg C
319                                                                      !! for heartwood above, tabulated
320                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
321!$OMP THREADPRIVATE(cm_zero_heartabove)
322
323  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartbelow  !! maintenance respiration coefficient at 0 deg C,
324                                                                      !! for heartwood below, tabulated
325                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
326!$OMP THREADPRIVATE(cm_zero_heartbelow)
327
328  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_root        !! maintenance respiration coefficient at 0 deg C,
329                                                                      !! for roots, tabulated
330                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
331!$OMP THREADPRIVATE(cm_zero_root)
332
333  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_fruit       !! maintenance respiration coefficient  at 0 deg C,
334                                                                      !! for fruits, tabulated
335                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
336!$OMP THREADPRIVATE(cm_zero_fruit)
337
338  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_carbres     !! maintenance respiration coefficient at 0 deg C,
339                                                                      !! for carbohydrate reserve, tabulated
340                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
341!$OMP THREADPRIVATE(cm_zero_carbres)
342
343 
344  !
345  ! FIRE (stomate)
346  !
347  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
348                                                                    !! capacity (0-1, unitless)
349!$OMP THREADPRIVATE(flam)
350
351  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
352!$OMP THREADPRIVATE(resist)
353
354
355  !
356  ! FLUX - LUC (Land Use Change)
357  !
358  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1   !! Coeff of biomass export for the year (unitless)
359!$OMP THREADPRIVATE(coeff_lcchange_1)
360
361  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10  !! Coeff of biomass export for the decade (unitless)
362!$OMP THREADPRIVATE(coeff_lcchange_10)
363
364  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless)
365!$OMP THREADPRIVATE(coeff_lcchange_100)
366 
367 
368  !
369  ! PHENOLOGY
370  !
371  !-
372  ! 1. Stomate
373  !-
374  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy  !! threshold of LAI below which plant uses carbohydrate reserves
375!$OMP THREADPRIVATE(lai_max_to_happy)
376
377  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
378!$OMP THREADPRIVATE(lai_max)
379
380  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
381                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
382                                                                    !! 3=raingreen,  4=perennial
383                                                                    !! For the moment, the bare ground phenotype is not managed,
384                                                                    !! so it is considered as "evergreen"
385!$OMP THREADPRIVATE(pheno_type)
386
387  !-
388  ! 2. Leaf Onset
389  !-
390  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
391!$OMP THREADPRIVATE(pheno_gdd_crit)
392
393  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
394                                                                     !! constant c of aT^2+bT+c (unitless)
395!$OMP THREADPRIVATE(pheno_gdd_crit_c)
396
397  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
398                                                                     !! constant b of aT^2+bT+c (unitless)
399!$OMP THREADPRIVATE(pheno_gdd_crit_b)
400
401  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
402                                                                     !! constant a of aT^2+bT+c (unitless)
403!$OMP THREADPRIVATE(pheno_gdd_crit_a)
404
405  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C)
406!$OMP THREADPRIVATE(pheno_moigdd_t_crit)
407
408  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
409!$OMP THREADPRIVATE(ngd_crit)
410
411  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
412                                                                     !! in phenology (C)
413!$OMP THREADPRIVATE(ncdgdd_temp)
414
415  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
416                                                                     !! (0-1, unitless)
417!$OMP THREADPRIVATE(hum_frac)
418
419  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
420!$OMP THREADPRIVATE(hum_min_time)
421
422  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! sapwood -> heartwood conversion time (days)
423!$OMP THREADPRIVATE(tau_sap)
424
425  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit lifetime (days)
426!$OMP THREADPRIVATE(tau_fruit)
427
428  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit  !! time to attain the initial foliage using the carbohydrate reserve
429!$OMP THREADPRIVATE(tau_leafinit)
430
431  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
432                                                                     !! into reserve (0-1, unitless)
433!$OMP THREADPRIVATE(ecureuil)
434
435  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
436!$OMP THREADPRIVATE(alloc_min)
437
438  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
439!$OMP THREADPRIVATE(alloc_max)
440
441  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
442!$OMP THREADPRIVATE(demi_alloc)
443
444  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaflife_tab       !! leaf longevity, tabulated (??units??)
445!$OMP THREADPRIVATE(leaflife_tab)
446
447  !-
448  ! 3. Senescence
449  !-
450  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
451!$OMP THREADPRIVATE(leaffall)
452
453  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leafagecrit           !! critical leaf age,tabulated (days)
454!$OMP THREADPRIVATE(leafagecrit)
455
456  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
457                                                                        !! List of avaible types of senescence :
458                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
459!$OMP THREADPRIVATE(senescence_type)
460
461  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
462                                                                        !! (0-1, unitless)
463!$OMP THREADPRIVATE(senescence_hum)
464
465  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
466                                                                        !! no humidity-related senescence (0-1, unitless)
467!$OMP THREADPRIVATE(nosenescence_hum)
468
469  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
470!$OMP THREADPRIVATE(max_turnover_time)
471
472  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
473!$OMP THREADPRIVATE(min_turnover_time)
474
475  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
476!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
477
478  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
479                                                                        !! used in the code
480!$OMP THREADPRIVATE(senescence_temp)
481
482  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
483                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
484!$OMP THREADPRIVATE(senescence_temp_c)
485
486  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
487                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
488!$OMP THREADPRIVATE(senescence_temp_b)
489
490  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
491                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
492!$OMP THREADPRIVATE(senescence_temp_a)
493
494  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
495!$OMP THREADPRIVATE(gdd_senescence)
496
497  !
498  ! DGVM
499  !
500
501  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time        !! residence time of trees (y)
502!$OMP THREADPRIVATE(residence_time)
503
504  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit             !! critical tmin, tabulated (C)
505!$OMP THREADPRIVATE(tmin_crit)
506
507  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit              !! critical tcm, tabulated (C)
508!$OMP THREADPRIVATE(tcm_crit)
509
510  !
511  ! Biogenic Volatile Organic Compounds
512  !
513
514  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
515                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
516!$OMP THREADPRIVATE(em_factor_isoprene)
517
518  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
519                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
520!$OMP THREADPRIVATE(em_factor_monoterpene)
521
522  REAL(r_std), SAVE :: LDF_mono                                            !! monoterpenes fraction dependancy to light
523!$OMP THREADPRIVATE(LDF_mono)
524  REAL(r_std), SAVE :: LDF_sesq                                            !! sesquiterpenes fraction dependancy to light
525!$OMP THREADPRIVATE(LDF_sesq)
526  REAL(r_std), SAVE :: LDF_meth                                            !! methanol fraction dependancy to light
527!$OMP THREADPRIVATE(LDF_meth)
528  REAL(r_std), SAVE :: LDF_acet                                            !! acetone fraction dependancy to light
529!$OMP THREADPRIVATE(LDF_acet)
530  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene        !! Alfa pinene emission factor
531                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
532!$OMP THREADPRIVATE(em_factor_apinene)
533
534  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene        !! Beta pinene emission factor
535                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
536!$OMP THREADPRIVATE(em_factor_bpinene)
537
538  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene       !! Limonene emission factor
539                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
540!$OMP THREADPRIVATE(em_factor_limonene)
541
542  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene        !! Myrcene emission factor
543                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
544!$OMP THREADPRIVATE(em_factor_myrcene)
545
546  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene       !! Sabinene emission factor
547                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
548!$OMP THREADPRIVATE(em_factor_sabinene)
549
550  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene       !! Camphene emission factor
551                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
552!$OMP THREADPRIVATE(em_factor_camphene)
553
554  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene        !! 3-carene emission factor
555                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
556!$OMP THREADPRIVATE(em_factor_3carene)
557
558  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene      !! T-beta-ocimene emission factor
559                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
560!$OMP THREADPRIVATE(em_factor_tbocimene)
561
562  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot     !! Other monoterpenes emission factor
563                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
564!$OMP THREADPRIVATE(em_factor_othermonot)
565
566  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp     !! Sesquiterpene emission factor
567                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
568!$OMP THREADPRIVATE(em_factor_sesquiterp)
569
570  REAL(r_std), SAVE :: beta_mono                                           !! Monoterpenes temperature dependency coefficient
571!$OMP THREADPRIVATE(beta_mono)
572  REAL(r_std), SAVE :: beta_sesq                                           !! Sesquiterpenes temperature dependency coefficient
573!$OMP THREADPRIVATE(beta_sesq)
574  REAL(r_std), SAVE :: beta_meth                                           !! Methanol temperature dependency coefficient
575!$OMP THREADPRIVATE(beta_meth)
576  REAL(r_std), SAVE :: beta_acet                                           !! Acetone temperature dependency coefficient
577!$OMP THREADPRIVATE(beta_acet)
578  REAL(r_std), SAVE :: beta_oxyVOC                                         !! Other oxygenated BVOC temperature dependency coefficient
579!$OMP THREADPRIVATE(beta_oxyVOC)
580
581  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
582                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
583!$OMP THREADPRIVATE(em_factor_ORVOC)
584
585  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
586                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
587!$OMP THREADPRIVATE(em_factor_OVOC)
588
589  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
590                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
591!$OMP THREADPRIVATE(em_factor_MBO)
592
593  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
594                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
595!$OMP THREADPRIVATE(em_factor_methanol)
596
597  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
598                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
599!$OMP THREADPRIVATE(em_factor_acetone)
600
601  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
602                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
603!$OMP THREADPRIVATE(em_factor_acetal)
604
605  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
606                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
607!$OMP THREADPRIVATE(em_factor_formal)
608
609  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
610                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
611!$OMP THREADPRIVATE(em_factor_acetic)
612
613  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
614                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
615!$OMP THREADPRIVATE(em_factor_formic)
616
617  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
618                                                                           !! exponential dependancy factor for wet soils
619                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
620!$OMP THREADPRIVATE(em_factor_no_wet)
621
622  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
623                                                                           !! exponential dependancy factor for dry soils
624                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
625!$OMP THREADPRIVATE(em_factor_no_dry)
626
627  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
628!$OMP THREADPRIVATE(Larch)
629
630  !
631  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
632  !
633
634  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
635                                                                !! @tex $(m^2.m^{-2})$ @endtex
636!$OMP THREADPRIVATE(lai_initmin)
637
638  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl   !! sapling biomass @tex $(gC.ind^{-1})$ @endtex
639!$OMP THREADPRIVATE(bm_sapl)
640
641  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
642!$OMP THREADPRIVATE(migrate)
643
644  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
645                                                                !! increases (m)
646!$OMP THREADPRIVATE(maxdia)
647
648  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
649!$OMP THREADPRIVATE(cn_sapl)
650
651  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
652!$OMP THREADPRIVATE(leaf_timecst)
653
654
655END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.