source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_parameters/pft_parameters_var.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

  • Property svn:keywords set to Date Revision
File size: 40.5 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(:) :: 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(:) :: availability_fact      !! calculate dynamic mortality in lpj_gap
118!$OMP THREADPRIVATE(availability_fact)
119
120  !
121  ! EVAPOTRANSPIRATION (sechiba)
122  !
123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const          !! Structural resistance.
124                                                                         !! Value for rstruct_const : one for each vegetation type
125                                                                         !! @tex $(s.m^{-1})$ @endtex
126!$OMP THREADPRIVATE(rstruct_const)
127
128  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero                  !! A vegetation dependent constant used in the calculation
129                                                                         !! of the surface resistance.
130                                                                         !! Value for kzero one for each vegetation type
131                                                                         !! @tex $(kg.m^2.s^{-1})$ @endtex
132!$OMP THREADPRIVATE(kzero)
133
134  !
135  ! WATER (sechiba)
136  !
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
139!$OMP THREADPRIVATE(wmax_veg)
140
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
143                                                            !! the root density as a function of depth
144                                                            !! @tex $(m^{-1})$ @endtex
145!$OMP THREADPRIVATE(humcste)
146
147  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft !! Fraction of rain intercepted by the canopy (0-100, unitless)
148!$OMP THREADPRIVATE(throughfall_by_pft)
149
150  !
151  ! ALBEDO (sechiba)
152  !
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)
157
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)
162
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
173  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis  !! leaf albedo of vegetation type, visible albedo (unitless)
174!$OMP THREADPRIVATE(alb_leaf_vis)
175
176  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir  !! leaf albedo of vegetation type, near infrared albedo (unitless)
177!$OMP THREADPRIVATE(alb_leaf_nir)
178
179  !
180  ! SOIL - VEGETATION
181  !
182  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg      !! Table which contains the correlation between the soil
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)
189!$OMP THREADPRIVATE(pref_soil_veg)
190
191  !
192  ! PHOTOSYNTHESIS
193  !
194  !-
195  ! 1. CO2
196  !-
197  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4             !! flag for C4 vegetation types (true/false)
198!$OMP THREADPRIVATE(is_c4)
199
200  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix     !! values used for vcmax when STOMATE is not activated
201                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
202!$OMP THREADPRIVATE(vcmax_fix)
203
204  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation (unitless)
205!$OMP THREADPRIVATE(downregulation_co2_coeff)
206
207  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC         !! Energy of activation for KmC (J mol-1)
208!$OMP THREADPRIVATE(E_KmC)                                                               
209  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO         !! Energy of activation for KmO (J mol-1)
210!$OMP THREADPRIVATE(E_KmO)         
211  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star  !! Energy of activation for gamma_star (J mol-1)
212!$OMP THREADPRIVATE(E_gamma_star)   
213  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax       !! Energy of activation for Vcmax (J mol-1)
214!$OMP THREADPRIVATE(E_Vcmax)                                                             
215  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax        !! Energy of activation for Jmax (J mol-1)
216!$OMP THREADPRIVATE(E_Jmax)
217  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)
218!$OMP THREADPRIVATE(aSV)   
219  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)
220!$OMP THREADPRIVATE(bSV)
221  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min   !! minimum photosynthesis temperature (deg C)
222!$OMP THREADPRIVATE(tphoto_min)
223  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max   !! maximum photosynthesis temperature (deg C)
224!$OMP THREADPRIVATE(tphoto_max)
225  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)
226!$OMP THREADPRIVATE(aSJ)   
227  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)
228!$OMP THREADPRIVATE(bSJ)   
229  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax       !! Energy of deactivation for Vcmax (J mol-1)
230!$OMP THREADPRIVATE(D_Vcmax)                     
231  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax        !! Energy of deactivation for Jmax (J mol-1)
232!$OMP THREADPRIVATE(D_Jmax)                                   
233  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd          !! Energy of activation for Rd (J mol-1)
234!$OMP THREADPRIVATE(E_Rd)                                     
235  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25       !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
236                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
237!$OMP THREADPRIVATE(Vcmax25)
238  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)
239!$OMP THREADPRIVATE(arJV)
240  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)
241!$OMP THREADPRIVATE(brJV)
242  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25         !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
243!$OMP THREADPRIVATE(KmC25)                                     
244  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25         !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
245!$OMP THREADPRIVATE(KmO25)               
246  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25  !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
247!$OMP THREADPRIVATE(gamma_star25)       
248  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a1            !! Empirical factor involved in the calculation of fvpd (-)
249!$OMP THREADPRIVATE(a1)                                       
250  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b1            !! Empirical factor involved in the calculation of fvpd (-)
251!$OMP THREADPRIVATE(b1)                                       
252  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: g0            !! Residual stomatal conductance when irradiance approaches zero (mol m−2 s−1 bar−1)
253!$OMP THREADPRIVATE(g0)                                       
254  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_protons     !! Number of protons required to produce one ATP (mol mol-1)
255!$OMP THREADPRIVATE(h_protons)                                 
256  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpsir         !! Fraction of PSII e− transport rate partitioned to the C4 cycle (-)
257!$OMP THREADPRIVATE(fpsir)                                         
258  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
259!$OMP THREADPRIVATE(fQ)                                       
260  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpseudo       !! Fraction of electrons at PSI that follow  pseudocyclic transport (-) - Values for C3 platns are not used
261!$OMP THREADPRIVATE(fpseudo)                                   
262  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kp            !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
263!$OMP THREADPRIVATE(kp)                                       
264  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha         !! Fraction of PSII activity in the bundle sheath (-)
265!$OMP THREADPRIVATE(alpha)                                     
266  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gbs           !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
267!$OMP THREADPRIVATE(gbs)                                       
268  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: theta         !! Convexity factor for response of J to irradiance (-)
269!$OMP THREADPRIVATE(theta)                                     
270  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_LL      !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
271!$OMP THREADPRIVATE(alpha_LL)
272
273
274  !-
275  ! 2. Stomate
276  !-
277  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff     !! extinction coefficient of the Monsi&Saeki relationship (1953)
278                                                                !! (unitless)
279!$OMP THREADPRIVATE(ext_coeff)
280  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff_vegetfrac     !! extinction coefficient used for the calculation of the
281                                                                !! bare soil fraction (unitless)
282!$OMP THREADPRIVATE(ext_coeff_vegetfrac)
283
284
285  !
286  ! ALLOCATION (stomate)
287  !
288  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: R0            !! Default root allocation (0-1, unitless)
289!$OMP THREADPRIVATE(R0)
290  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0            !! Default sapwood allocation (0-1, unitless)
291!$OMP THREADPRIVATE(S0)
292  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0            !! Default leaf allocation (0-1, unitless)
293!$OMP THREADPRIVATE(L0)
294
295
296  !
297  ! RESPIRATION (stomate)
298  !
299  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp  !! fraction of GPP which is lost as growth respiration
300
301!$OMP THREADPRIVATE(frac_growthresp)
302
303  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient
304                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
305!$OMP THREADPRIVATE(maint_resp_slope)
306
307  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
308                                                                      !! constant c of aT^2+bT+c , tabulated
309!$OMP THREADPRIVATE(maint_resp_slope_c)
310
311  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K),
312                                                                      !! constant b of aT^2+bT+c , tabulated
313!$OMP THREADPRIVATE(maint_resp_slope_b)
314
315  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K),
316                                                                      !! constant a of aT^2+bT+c , tabulated
317!$OMP THREADPRIVATE(maint_resp_slope_a)
318
319  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: coeff_maint_zero  !! maintenance respiration coefficient at 0 deg C,
320                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
321!$OMP THREADPRIVATE(coeff_maint_zero)
322
323  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_leaf        !! maintenance respiration coefficient at 0 deg C,
324                                                                      !! for leaves, tabulated
325                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
326!$OMP THREADPRIVATE(cm_zero_leaf)
327
328  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapabove    !! maintenance respiration coefficient at 0 deg C,
329                                                                      !! for sapwood above, tabulated
330                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
331!$OMP THREADPRIVATE(cm_zero_sapabove)
332
333  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapbelow    !! maintenance respiration coefficient at 0 deg C,
334                                                                      !! for sapwood below, tabulated
335                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
336!$OMP THREADPRIVATE(cm_zero_sapbelow)
337
338  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartabove  !! maintenance respiration coefficient at 0 deg C
339                                                                      !! for heartwood above, tabulated
340                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
341!$OMP THREADPRIVATE(cm_zero_heartabove)
342
343  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartbelow  !! maintenance respiration coefficient at 0 deg C,
344                                                                      !! for heartwood below, tabulated
345                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
346!$OMP THREADPRIVATE(cm_zero_heartbelow)
347
348  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_root        !! maintenance respiration coefficient at 0 deg C,
349                                                                      !! for roots, tabulated
350                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
351!$OMP THREADPRIVATE(cm_zero_root)
352
353  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_fruit       !! maintenance respiration coefficient  at 0 deg C,
354                                                                      !! for fruits, tabulated
355                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
356!$OMP THREADPRIVATE(cm_zero_fruit)
357
358  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_carbres     !! maintenance respiration coefficient at 0 deg C,
359                                                                      !! for carbohydrate reserve, tabulated
360                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
361!$OMP THREADPRIVATE(cm_zero_carbres)
362
363 
364  !
365  ! FIRE (stomate)
366  !
367  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
368                                                                    !! capacity (0-1, unitless)
369!$OMP THREADPRIVATE(flam)
370
371  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
372!$OMP THREADPRIVATE(resist)
373
374
375  !
376  ! FLUX - LUC (Land Use Change)
377  !
378  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1   !! Coeff of biomass export for the year (unitless)
379!$OMP THREADPRIVATE(coeff_lcchange_1)
380
381  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10  !! Coeff of biomass export for the decade (unitless)
382!$OMP THREADPRIVATE(coeff_lcchange_10)
383
384  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless)
385!$OMP THREADPRIVATE(coeff_lcchange_100)
386 
387 
388  !
389  ! PHENOLOGY
390  !
391  !-
392  ! 1. Stomate
393  !-
394  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy  !! threshold of LAI below which plant uses carbohydrate reserves
395!$OMP THREADPRIVATE(lai_max_to_happy)
396
397  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
398!$OMP THREADPRIVATE(lai_max)
399
400  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
401                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
402                                                                    !! 3=raingreen,  4=perennial
403                                                                    !! For the moment, the bare ground phenotype is not managed,
404                                                                    !! so it is considered as "evergreen"
405!$OMP THREADPRIVATE(pheno_type)
406
407  !-
408  ! 2. Leaf Onset
409  !-
410  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
411!$OMP THREADPRIVATE(pheno_gdd_crit)
412
413  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
414                                                                     !! constant c of aT^2+bT+c (unitless)
415!$OMP THREADPRIVATE(pheno_gdd_crit_c)
416
417  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
418                                                                     !! constant b of aT^2+bT+c (unitless)
419!$OMP THREADPRIVATE(pheno_gdd_crit_b)
420
421  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
422                                                                     !! constant a of aT^2+bT+c (unitless)
423!$OMP THREADPRIVATE(pheno_gdd_crit_a)
424
425  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C)
426!$OMP THREADPRIVATE(pheno_moigdd_t_crit)
427
428  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
429!$OMP THREADPRIVATE(ngd_crit)
430
431  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
432                                                                     !! in phenology (C)
433!$OMP THREADPRIVATE(ncdgdd_temp)
434
435  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
436                                                                     !! (0-1, unitless)
437!$OMP THREADPRIVATE(hum_frac)
438
439  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
440!$OMP THREADPRIVATE(hum_min_time)
441
442  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! sapwood -> heartwood conversion time (days)
443!$OMP THREADPRIVATE(tau_sap)
444
445  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit lifetime (days)
446!$OMP THREADPRIVATE(tau_fruit)
447
448  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit  !! time to attain the initial foliage using the carbohydrate reserve
449!$OMP THREADPRIVATE(tau_leafinit)
450
451  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
452                                                                     !! into reserve (0-1, unitless)
453!$OMP THREADPRIVATE(ecureuil)
454
455  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
456!$OMP THREADPRIVATE(alloc_min)
457
458  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
459!$OMP THREADPRIVATE(alloc_max)
460
461  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
462!$OMP THREADPRIVATE(demi_alloc)
463
464  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaflife_tab       !! leaf longevity, tabulated (??units??)
465!$OMP THREADPRIVATE(leaflife_tab)
466
467  !-
468  ! 3. Senescence
469  !-
470  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
471!$OMP THREADPRIVATE(leaffall)
472
473  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leafagecrit           !! critical leaf age,tabulated (days)
474!$OMP THREADPRIVATE(leafagecrit)
475
476  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
477                                                                        !! List of avaible types of senescence :
478                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
479!$OMP THREADPRIVATE(senescence_type)
480
481  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
482                                                                        !! (0-1, unitless)
483!$OMP THREADPRIVATE(senescence_hum)
484
485  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
486                                                                        !! no humidity-related senescence (0-1, unitless)
487!$OMP THREADPRIVATE(nosenescence_hum)
488
489  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
490!$OMP THREADPRIVATE(max_turnover_time)
491
492  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
493!$OMP THREADPRIVATE(min_turnover_time)
494
495  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
496!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
497
498  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
499                                                                        !! used in the code
500!$OMP THREADPRIVATE(senescence_temp)
501
502  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
503                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
504!$OMP THREADPRIVATE(senescence_temp_c)
505
506  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
507                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
508!$OMP THREADPRIVATE(senescence_temp_b)
509
510  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
511                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
512!$OMP THREADPRIVATE(senescence_temp_a)
513
514  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
515!$OMP THREADPRIVATE(gdd_senescence)
516
517  !
518  ! DGVM
519  !
520
521  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time        !! residence time of trees (y)
522!$OMP THREADPRIVATE(residence_time)
523
524  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit             !! critical tmin, tabulated (C)
525!$OMP THREADPRIVATE(tmin_crit)
526
527  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit              !! critical tcm, tabulated (C)
528!$OMP THREADPRIVATE(tcm_crit)
529
530  !
531  ! Biogenic Volatile Organic Compounds
532  !
533
534  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
535                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
536!$OMP THREADPRIVATE(em_factor_isoprene)
537
538  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
539                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
540!$OMP THREADPRIVATE(em_factor_monoterpene)
541
542  REAL(r_std), SAVE :: LDF_mono                                            !! monoterpenes fraction dependancy to light
543!$OMP THREADPRIVATE(LDF_mono)
544  REAL(r_std), SAVE :: LDF_sesq                                            !! sesquiterpenes fraction dependancy to light
545!$OMP THREADPRIVATE(LDF_sesq)
546  REAL(r_std), SAVE :: LDF_meth                                            !! methanol fraction dependancy to light
547!$OMP THREADPRIVATE(LDF_meth)
548  REAL(r_std), SAVE :: LDF_acet                                            !! acetone fraction dependancy to light
549!$OMP THREADPRIVATE(LDF_acet)
550  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene        !! Alfa pinene emission factor
551                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
552!$OMP THREADPRIVATE(em_factor_apinene)
553
554  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene        !! Beta pinene emission factor
555                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
556!$OMP THREADPRIVATE(em_factor_bpinene)
557
558  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene       !! Limonene emission factor
559                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
560!$OMP THREADPRIVATE(em_factor_limonene)
561
562  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene        !! Myrcene emission factor
563                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
564!$OMP THREADPRIVATE(em_factor_myrcene)
565
566  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene       !! Sabinene emission factor
567                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
568!$OMP THREADPRIVATE(em_factor_sabinene)
569
570  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene       !! Camphene emission factor
571                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
572!$OMP THREADPRIVATE(em_factor_camphene)
573
574  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene        !! 3-carene emission factor
575                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
576!$OMP THREADPRIVATE(em_factor_3carene)
577
578  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene      !! T-beta-ocimene emission factor
579                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
580!$OMP THREADPRIVATE(em_factor_tbocimene)
581
582  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot     !! Other monoterpenes emission factor
583                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
584!$OMP THREADPRIVATE(em_factor_othermonot)
585
586  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp     !! Sesquiterpene emission factor
587                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
588!$OMP THREADPRIVATE(em_factor_sesquiterp)
589
590  REAL(r_std), SAVE :: beta_mono                                           !! Monoterpenes temperature dependency coefficient
591!$OMP THREADPRIVATE(beta_mono)
592  REAL(r_std), SAVE :: beta_sesq                                           !! Sesquiterpenes temperature dependency coefficient
593!$OMP THREADPRIVATE(beta_sesq)
594  REAL(r_std), SAVE :: beta_meth                                           !! Methanol temperature dependency coefficient
595!$OMP THREADPRIVATE(beta_meth)
596  REAL(r_std), SAVE :: beta_acet                                           !! Acetone temperature dependency coefficient
597!$OMP THREADPRIVATE(beta_acet)
598  REAL(r_std), SAVE :: beta_oxyVOC                                         !! Other oxygenated BVOC temperature dependency coefficient
599!$OMP THREADPRIVATE(beta_oxyVOC)
600
601  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
602                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
603!$OMP THREADPRIVATE(em_factor_ORVOC)
604
605  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
606                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
607!$OMP THREADPRIVATE(em_factor_OVOC)
608
609  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
610                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
611!$OMP THREADPRIVATE(em_factor_MBO)
612
613  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
614                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
615!$OMP THREADPRIVATE(em_factor_methanol)
616
617  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
618                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
619!$OMP THREADPRIVATE(em_factor_acetone)
620
621  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
622                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
623!$OMP THREADPRIVATE(em_factor_acetal)
624
625  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
626                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
627!$OMP THREADPRIVATE(em_factor_formal)
628
629  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
630                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
631!$OMP THREADPRIVATE(em_factor_acetic)
632
633  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
634                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
635!$OMP THREADPRIVATE(em_factor_formic)
636
637  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
638                                                                           !! exponential dependancy factor for wet soils
639                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
640!$OMP THREADPRIVATE(em_factor_no_wet)
641
642  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
643                                                                           !! exponential dependancy factor for dry soils
644                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
645!$OMP THREADPRIVATE(em_factor_no_dry)
646
647  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
648!$OMP THREADPRIVATE(Larch)
649
650  !
651  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
652  !
653
654  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
655                                                                !! @tex $(m^2.m^{-2})$ @endtex
656!$OMP THREADPRIVATE(lai_initmin)
657
658  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl   !! sapling biomass @tex $(gC.ind^{-1})$ @endtex
659!$OMP THREADPRIVATE(bm_sapl)
660
661  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
662!$OMP THREADPRIVATE(migrate)
663
664  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
665                                                                !! increases (m)
666!$OMP THREADPRIVATE(maxdia)
667
668  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
669!$OMP THREADPRIVATE(cn_sapl)
670
671  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
672!$OMP THREADPRIVATE(leaf_timecst)
673
674  !
675  ! grassland management
676  !
677  !gmjc
678  ! Is the vegetation type a managed grassland ?
679  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_manag
680  ! Is the vegetation type a cut grassland for management adaptation ?
681  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_cut
682  ! Is the vegetation type a grazed grassland for management adaptation ?
683  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_grazed
684  ! Is the vegetation type a wild grassland that can be grazed by wild grazer ?
685  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_wild
686  ! Management Intensity reading in MANAGEMENT_MAP
687  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: management_intensity
688  ! Start year of management reading in MANAGEMENT_MAP & GRAZING_MAP
689  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: management_start
690  ! Start year of N deposition reading in DEPOSITION_MAP
691  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: deposition_start
692  ! Number of year that management should be read
693  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nb_year_management
694  ! maximum specific leaf area (m**2/gC)
695  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION(:) :: sla_max
696  ! minimum specific leaf area (m**2/gC)
697  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)  :: sla_min
698  !end gmjc
699
700END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.