source: branches/publications/ORCHIDEE-Hillslope-r6515/src_parameters/constantes_var.f90 @ 7369

Last change on this file since 7369 was 4962, checked in by josefine.ghattas, 7 years ago

Updated default values as have been decided for version ORCHIDEE 2.0 and to be used for CMIP6. See ticket #414

  • Property svn:keywords set to Date Revision
File size: 56.5 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_var
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        constantes_var module contains most constantes like pi, Earth radius, etc...
10!!              and all externalized parameters except pft-dependent constants.
11!!
12!!\n DESCRIPTION: This module contains most constantes and the externalized parameters of ORCHIDEE which
13!!                are not pft-dependent.\n
14!!                In this module, you can set the flag diag_qsat in order to detect the pixel where the
15!!                temperature is out of range (look qsatcalc and dev_qsatcalc in qsat_moisture.f90).\n
16!!                The Earth radius is approximated by the Equatorial radius.The Earth's equatorial radius a,
17!!                or semi-major axis, is the distance from its center to the equator and equals 6,378.1370 km.
18!!                The equatorial radius is often used to compare Earth with other planets.\n
19!!                The meridional mean is well approximated by the semicubic mean of the two axe yielding
20!!                6367.4491 km or less accurately by the quadratic mean of the two axes about 6,367.454 km
21!!                or even just the mean of the two axes about 6,367.445 km.\n
22!!                This module is already USE in module constantes. Therefor no need to USE it seperatly except
23!!                if the subroutines in module constantes are not needed.\n
24!!               
25!! RECENT CHANGE(S):
26!!
27!! REFERENCE(S) :
28!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
29!! Boundary Layer Meteorology, 187-202.\n
30!!
31!! SVN          :
32!! $HeadURL: $
33!! $Date$
34!! $Revision$
35!! \n
36!_ ================================================================================================================================
37
38MODULE constantes_var
39
40  USE defprec
41
42  IMPLICIT NONE
43!-
44
45                         !-----------------------!
46                         !  ORCHIDEE CONSTANTS   !
47                         !-----------------------!
48
49  !
50  ! FLAGS
51  !
52  LOGICAL :: river_routing      !! activate river routing
53!$OMP THREADPRIVATE(river_routing)
54  LOGICAL :: hydrol_cwrr        !! activate 11 layers hydrolgy model
55!$OMP THREADPRIVATE(hydrol_cwrr)
56  LOGICAL, SAVE :: ok_nudge_mc  !! Activate nudging of soil moisture
57!$OMP THREADPRIVATE(ok_nudge_mc)
58  LOGICAL, SAVE :: ok_nudge_snow!! Activate nudging of snow variables
59!$OMP THREADPRIVATE(ok_nudge_snow)
60  LOGICAL, SAVE :: nudge_interpol_with_xios  !! Activate reading and interpolation with XIOS for nudging fields
61!$OMP THREADPRIVATE(nudge_interpol_with_xios)
62  LOGICAL :: do_floodplains     !! activate flood plains
63!$OMP THREADPRIVATE(do_floodplains)
64  LOGICAL :: do_irrigation      !! activate computation of irrigation flux
65!$OMP THREADPRIVATE(do_irrigation)
66  LOGICAL :: ok_sechiba         !! activate physic of the model
67!$OMP THREADPRIVATE(ok_sechiba)
68  LOGICAL :: ok_co2             !! activate photosynthesis
69!$OMP THREADPRIVATE(ok_co2)
70  LOGICAL :: ok_stomate         !! activate carbon cycle
71!$OMP THREADPRIVATE(ok_stomate)
72  LOGICAL :: ok_dgvm            !! activate dynamic vegetation
73!$OMP THREADPRIVATE(ok_dgvm)
74  LOGICAL :: do_wood_harvest    !! activate wood harvest
75!$OMP THREADPRIVATE(do_wood_harvest)
76  LOGICAL :: ok_pheno           !! activate the calculation of lai using stomate rather than a prescription
77!$OMP THREADPRIVATE(ok_pheno)
78  LOGICAL :: ok_bvoc            !! activate biogenic volatile organic coumpounds
79!$OMP THREADPRIVATE(ok_bvoc)
80  LOGICAL :: ok_leafage         !! activate leafage
81!$OMP THREADPRIVATE(ok_leafage)
82  LOGICAL :: ok_radcanopy       !! use canopy radiative transfer model
83!$OMP THREADPRIVATE(ok_radcanopy)
84  LOGICAL :: ok_multilayer      !! use canopy radiative transfer model with multi-layers
85!$OMP THREADPRIVATE(ok_multilayer)
86  LOGICAL :: ok_pulse_NOx       !! calculate NOx emissions with pulse
87!$OMP THREADPRIVATE(ok_pulse_NOx)
88  LOGICAL :: ok_bbgfertil_NOx   !! calculate NOx emissions with bbg fertilizing effect
89!$OMP THREADPRIVATE(ok_bbgfertil_NOx)
90  LOGICAL :: ok_cropsfertil_NOx !! calculate NOx emissions with fertilizers use
91!$OMP THREADPRIVATE(ok_cropsfertil_NOx)
92
93  LOGICAL :: ok_co2bvoc_poss    !! CO2 inhibition on isoprene activated following Possell et al. (2005) model
94!$OMP THREADPRIVATE(ok_co2bvoc_poss)
95  LOGICAL :: ok_co2bvoc_wilk    !! CO2 inhibition on isoprene activated following Wilkinson et al. (2006) model
96!$OMP THREADPRIVATE(ok_co2bvoc_wilk)
97 
98  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE.  !! ORCHIDEE detects if it is coupled with a GCM or
99                                            !! just use with one driver in OFF-LINE. (true/false)
100!$OMP THREADPRIVATE(OFF_LINE_MODE) 
101  LOGICAL, SAVE :: impose_param = .TRUE.    !! Flag impos_param : read all the parameters in the run.def file
102!$OMP THREADPRIVATE(impose_param)
103  CHARACTER(LEN=80), SAVE     :: restname_in       = 'NONE'                 !! Input Restart files name for Sechiba component 
104!$OMP THREADPRIVATE(restname_in)
105  CHARACTER(LEN=80), SAVE     :: restname_out      = 'sechiba_rest_out.nc'  !! Output Restart files name for Sechiba component
106!$OMP THREADPRIVATE(restname_out)
107  CHARACTER(LEN=80), SAVE     :: stom_restname_in  = 'NONE'                 !! Input Restart files name for Stomate component
108!$OMP THREADPRIVATE(stom_restname_in)
109  CHARACTER(LEN=80), SAVE     :: stom_restname_out = 'stomate_rest_out.nc'  !! Output Restart files name for Stomate component
110!$OMP THREADPRIVATE(stom_restname_out)
111  INTEGER, SAVE :: printlev=2       !! Standard level for text output [0, 1, 2, 3]
112!$OMP THREADPRIVATE(printlev)
113
114  !
115  ! TIME
116  !
117  INTEGER(i_std), PARAMETER  :: spring_days_max = 40  !! Maximum number of days during which we watch for possible spring frost damage
118  !
119  ! SPECIAL VALUES
120  !
121  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
122  !-
123  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
124!$OMP THREADPRIVATE(val_exp)
125  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
126 
127  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
128  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
129 
130  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
131  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
132
133  REAL(r_std), SAVE :: alpha_nudge_mc                    !! Nudging constant for soil moisture
134!$OMP THREADPRIVATE(alpha_nudge_mc)
135  REAL(r_std), SAVE :: alpha_nudge_snow                  !! Nudging constant for snow variables
136!$OMP THREADPRIVATE(alpha_nudge_snow)
137
138  !
139  !  DIMENSIONING AND INDICES PARAMETERS 
140  !
141  INTEGER(i_std), PARAMETER :: ibare_sechiba = 1 !! Index for bare soil in Sechiba (unitless)
142  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for albedo in visible range (unitless)
143  INTEGER(i_std), PARAMETER :: inir = 2          !! index for albeod i near-infrared range (unitless)
144  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
145  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
146  !-
147  !! Soil
148  INTEGER(i_std), PARAMETER :: classnb = 9       !! Levels of soil colour classification (unitless)
149  !-
150  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
151  !-
152  !! litter fractions: indices (unitless)
153  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
154  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
155  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
156  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
157  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
158  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
159  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
160  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
161  INTEGER(i_std), PARAMETER :: nparts = 8        !! Number of biomass compartments (unitless)
162  !-
163  !! indices for assimilation parameters
164  INTEGER(i_std), PARAMETER :: ivcmax = 1        !! Index for vcmax (assimilation parameters) (unitless)
165  INTEGER(i_std), PARAMETER :: npco2 = 1         !! Number of assimilation parameters (unitless)
166  !-
167  !! trees and litter: indices for the parts of heart-
168  !! and sapwood above and below the ground
169  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
170  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
171  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
172  !-
173  !! litter: indices for metabolic and structural part
174  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
175  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
176  INTEGER(i_std), PARAMETER :: nlitt = 2        !! Number of levels for litter compartments (unitless)
177  !-
178  !! carbon pools: indices
179  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
180  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
181  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
182  INTEGER(i_std), PARAMETER :: ncarb = 3        !! Number of soil carbon pools (unitless)
183  !-
184  !! For isotopes and nitrogen
185  INTEGER(i_std), PARAMETER :: nelements = 1    !! Number of isotopes considered
186  INTEGER(i_std), PARAMETER :: icarbon = 1      !! Index for carbon
187  !
188  !! Indices used for analytical spin-up
189  INTEGER(i_std), PARAMETER :: nbpools = 7              !! Total number of carbon pools (unitless)
190  INTEGER(i_std), PARAMETER :: istructural_above = 1    !! Index for structural litter above (unitless)
191  INTEGER(i_std), PARAMETER :: istructural_below = 2    !! Index for structural litter below (unitless)
192  INTEGER(i_std), PARAMETER :: imetabolic_above = 3     !! Index for metabolic litter above (unitless)
193  INTEGER(i_std), PARAMETER :: imetabolic_below = 4     !! Index for metabolic litter below (unitless)
194  INTEGER(i_std), PARAMETER :: iactive_pool = 5         !! Index for active carbon pool (unitless)
195  INTEGER(i_std), PARAMETER :: islow_pool   = 6         !! Index for slow carbon pool (unitless)
196  INTEGER(i_std), PARAMETER :: ipassive_pool = 7        !! Index for passive carbon pool (unitless)
197  !
198  !! Indicies used for output variables on Landuse tiles defined according to LUMIP project
199  !! Note that ORCHIDEE do not represent pasture and urban land. Therefor the variables will have
200  !! val_exp as missing value for these tiles.
201  INTEGER(i_std), PARAMETER :: nlut=4                   !! Total number of landuse tiles according to LUMIP
202  INTEGER(i_std), PARAMETER :: id_psl=1                 !! Index for primary and secondary land
203  INTEGER(i_std), PARAMETER :: id_crp=2                 !! Index for crop land
204  INTEGER(i_std), PARAMETER :: id_pst=3                 !! Index for pasture land
205  INTEGER(i_std), PARAMETER :: id_urb=4                 !! Index for urban land
206
207
208  !
209  ! NUMERICAL AND PHYSICS CONSTANTS
210  !
211  !
212
213  !-
214  ! 1. Mathematical and numerical constants
215  !-
216  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
217  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
218  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
219  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
220  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
221  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
222  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
223  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
224  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
225  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
226  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
227  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
228  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
229
230  !-
231  ! 2 . Physics
232  !-
233  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
234  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
235  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
236  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! 0 degre Celsius in degre Kelvin (K)
237  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
238  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
239  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
240  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
241  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
242  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
243  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
244  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
245                                                            !! of dry air (unitless)
246  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
247  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
248  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
249       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
250  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
251  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
252                                                            !! vapor minus 1(unitless) 
253  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
254                                                            !! minus 1 (unitless)
255  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
256  REAL(r_std), PARAMETER :: ct_karman = 0.41_r_std          !! Van Karmann Constant (unitless)
257  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
258  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
259  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gas constant (J.mol^{-1}.K^{-1})
260  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
261
262
263  INTEGER(i_std), SAVE :: testpft = 6
264  !-
265  ! 3. Climatic constants
266  !-
267  !! Constantes of the Louis scheme
268  REAL(r_std), SAVE :: cb = 5._r_std              !! Constant of the Louis scheme (unitless);
269                                                  !! reference to Louis (1979)
270!$OMP THREADPRIVATE(cb)
271  REAL(r_std), SAVE :: cc = 5._r_std              !! Constant of the Louis scheme (unitless);
272                                                  !! reference to Louis (1979)
273!$OMP THREADPRIVATE(cc)
274  REAL(r_std), SAVE :: cd = 5._r_std              !! Constant of the Louis scheme (unitless);
275                                                  !! reference to Louis (1979)
276!$OMP THREADPRIVATE(cd)
277  REAL(r_std), SAVE :: rayt_cste = 125.           !! Constant in the computation of surface resistance (W.m^{-2})
278!$OMP THREADPRIVATE(rayt_cste)
279  REAL(r_std), SAVE :: defc_plus = 23.E-3         !! Constant in the computation of surface resistance (K.W^{-1})
280!$OMP THREADPRIVATE(defc_plus)
281  REAL(r_std), SAVE :: defc_mult = 1.5            !! Constant in the computation of surface resistance (K.W^{-1})
282!$OMP THREADPRIVATE(defc_mult)
283
284  !-
285  ! 4. Soil thermodynamics constants
286  !-
287  ! Look at constantes_soil.f90
288
289
290  !
291  ! OPTIONAL PARTS OF THE MODEL
292  !
293  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
294                                                  !! we provide here a way to catch that in the calling procedure.
295                                                  !! (from Jan Polcher)(true/false)
296  LOGICAL, SAVE     :: almaoutput =.FALSE.        !! Selects the type of output for the model.(true/false)
297                                                  !! Value is read from run.def in intersurf_history
298!$OMP THREADPRIVATE(almaoutput)
299
300  !
301  ! DIVERSE
302  !
303  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
304                                                           ! Compatibility with Nicolas Viovy driver.
305!$OMP THREADPRIVATE(stomate_forcing_name)
306  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
307                                                           ! Compatibility with Nicolas Viovy driver.
308!$OMP THREADPRIVATE(stomate_Cforcing_name)
309  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
310!$OMP THREADPRIVATE(forcing_id)
311  LOGICAL, SAVE :: allow_forcing_write=.TRUE.        !! Allow writing of stomate_forcing file.
312                                                     !! This variable will be set to false for teststomate.
313
314
315
316                         !------------------------!
317                         !  SECHIBA PARAMETERS    !
318                         !------------------------!
319 
320
321  !
322  ! GLOBAL PARAMETERS   
323  !
324  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
325!$OMP THREADPRIVATE(min_wind)
326  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occures (kg.m^{-2})
327!$OMP THREADPRIVATE(snowcri)
328
329
330  !
331  ! FLAGS ACTIVATING SUB-MODELS
332  !
333  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
334!$OMP THREADPRIVATE(treat_expansion)
335  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
336!$OMP THREADPRIVATE(ok_herbivores)
337  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
338!$OMP THREADPRIVATE(harvest_agri)
339  LOGICAL, SAVE :: lpj_gap_const_mort          !! constant moratlity (true/false). Default value depend on OK_DGVM.
340!$OMP THREADPRIVATE(lpj_gap_const_mort)
341  LOGICAL, SAVE :: disable_fire = .TRUE.       !! flag that disable fire (true/false)
342!$OMP THREADPRIVATE(disable_fire)
343  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
344!$OMP THREADPRIVATE(spinup_analytic)
345  LOGICAL, SAVE :: ok_explicitsnow             !! Flag to activate explicit snow scheme instead of default snow scheme
346!$OMP THREADPRIVATE(ok_explicitsnow)
347
348  !
349  ! CONFIGURATION VEGETATION
350  !
351  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
352!$OMP THREADPRIVATE(agriculture)
353  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
354!$OMP THREADPRIVATE(impveg)
355  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
356!$OMP THREADPRIVATE(impsoilt)
357  LOGICAL, SAVE :: do_now_stomate_lcchange = .FALSE.  !! Time to call lcchange in stomate_lpj
358!$OMP THREADPRIVATE(do_now_stomate_lcchange)
359  LOGICAL, SAVE :: do_now_stomate_woodharvest = .FALSE.  !! Time to call woodharvest in stomate_lpj
360!$OMP THREADPRIVATE(do_now_stomate_woodharvest)
361  LOGICAL, SAVE :: done_stomate_lcchange = .FALSE.    !! If true, call lcchange in stomate_lpj has just been done.
362!$OMP THREADPRIVATE(done_stomate_lcchange)
363  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
364!$OMP THREADPRIVATE(read_lai)
365  LOGICAL, SAVE :: map_pft_format = .TRUE. !! Read a land use vegetation map on PFT format (true/false)
366!$OMP THREADPRIVATE(map_pft_format)
367  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
368!$OMP THREADPRIVATE(veget_reinit)
369
370  !
371  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
372  !
373  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
374!$OMP THREADPRIVATE(max_snow_age)
375  REAL(r_std), SAVE :: snow_trans = 0.2_r_std   !! Transformation time constant for snow (m), reduced from the value 0.3 (04/07/2016)
376!$OMP THREADPRIVATE(snow_trans)
377  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
378!$OMP THREADPRIVATE(sneige)
379  REAL(r_std), SAVE :: maxmass_snow = 3000.     !! The maximum mass of snow (kg.m^{-2})
380!$OMP THREADPRIVATE(maxmass_snow)
381
382  !! Heat capacity
383  REAL(r_std), PARAMETER :: capa_ice = 2.228*1.E3       !! Heat capacity of ice (J/kg/K)
384  REAL(r_std), SAVE      :: so_capa_ice                 !! Heat capacity of saturated frozen soil (J/K/m3)
385!$OMP THREADPRIVATE(so_capa_ice)
386  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3)
387  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3)
388  REAL(r_std), PARAMETER :: rho_soil = 2700.            !! Density of soil particles (kg/m3), value from Peters-Lidard et al. 1998
389
390  !! Thermal conductivities
391  REAL(r_std), PARAMETER :: cond_water = 0.6            !! Thermal conductivity of liquid water (W/m/K)
392  REAL(r_std), PARAMETER :: cond_ice = 2.2              !! Thermal conductivity of ice (W/m/K)
393  REAL(r_std), PARAMETER :: cond_solid = 2.32           !! Thermal conductivity of mineral soil particles (W/m/K)
394
395  !! Time constant of long-term soil humidity (s)
396  REAL(r_std), PARAMETER :: lhf = 0.3336*1.E6           !! Latent heat of fusion (J/kg)
397
398  INTEGER(i_std), PARAMETER :: nsnow=3                  !! Number of levels in the snow for explicit snow scheme   
399  REAL(r_std), PARAMETER    :: XMD    = 28.9644E-3 
400  REAL(r_std), PARAMETER    :: XBOLTZ      = 1.380658E-23 
401  REAL(r_std), PARAMETER    :: XAVOGADRO   = 6.0221367E+23 
402  REAL(r_std), PARAMETER    :: XRD    = XAVOGADRO * XBOLTZ / XMD 
403  REAL(r_std), PARAMETER    :: XCPD   = 7.* XRD /2. 
404  REAL(r_std), PARAMETER    :: phigeoth = 0.057 ! 0. DKtest
405  REAL(r_std), PARAMETER    :: thick_min_snow = .01 
406
407  !! The maximum snow density and water holding characterisicts
408  REAL(r_std), SAVE         :: xrhosmax = 750.  ! (kg m-3)
409  REAL(r_std), SAVE         :: xwsnowholdmax1   = 0.03  ! (-)
410  REAL(r_std), SAVE         :: xwsnowholdmax2   = 0.10  ! (-)
411  REAL(r_std), SAVE         :: xsnowrhohold     = 200.0 ! (kg/m3)
412  REAL(r_std), SAVE         :: xrhosmin = 50. 
413  REAL(r_std), PARAMETER    :: xci = 2.106e+3 
414  REAL(r_std), PARAMETER    :: xrv = 6.0221367e+23 * 1.380658e-23 /18.0153e-3 
415
416  !! ISBA-ES Critical snow depth at which snow grid thicknesses constant
417  REAL(r_std), PARAMETER    :: xsnowcritd = 0.03  ! (m)
418
419  !! The threshold of snow depth used for preventing numerical problem in thermal calculations
420  REAL(r_std), PARAMETER    :: snowcritd_thermal = 0.01  ! (m) 
421 
422  !! ISBA-ES CROCUS (Pahaut 1976): snowfall density coefficients:
423  REAL(r_std), PARAMETER       :: snowfall_a_sn = 109.0  !! (kg/m3)
424  REAL(r_std), PARAMETER       :: snowfall_b_sn =   6.0  !! (kg/m3/K)
425  REAL(r_std), PARAMETER       :: snowfall_c_sn =  26.0  !! [kg/(m7/2 s1/2)]
426
427  REAL(r_std), PARAMETER       :: dgrain_new_max=  2.0e-4!! (m) : Maximum grain size of new snowfall
428 
429  !! Used in explicitsnow to prevent numerical problems as snow becomes vanishingly thin.
430  REAL(r_std), PARAMETER                :: psnowdzmin = .0001   ! m
431  REAL(r_std), PARAMETER                :: xsnowdmin = .000001  ! m
432
433  REAL(r_std), PARAMETER                :: ph2o = 1000.         !! Water density [kg/m3]
434 
435  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
436  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
437  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND1 = 0.02    ! [W/m/K]
438  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND2 = 2.5E-6  ! [W m5/(kg2 K)]
439 
440  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
441  ! (sig only for new snow OR high altitudes)
442  ! from Sun et al. (1999): based on data from Jordan (1991)
443  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
444  !
445  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_AVAP  = -0.06023 ! (W/m/K)
446  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_BVAP  = -2.5425  ! (W/m)
447  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_CVAP  = -289.99  ! (K)
448 
449  REAL(r_std),SAVE :: xansmax = 0.85      !! Maxmimum snow albedo
450  REAL(r_std),SAVE :: xansmin = 0.50      !! Miniumum snow albedo
451  REAL(r_std),SAVE :: xans_todry = 0.008  !! Albedo decay rate for dry snow
452  REAL(r_std),SAVE :: xans_t = 0.240      !! Albedo decay rate for wet snow
453
454  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
455  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
456  REAL(r_std), PARAMETER                  :: XP00 = 1.E5
457
458  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
459  ! (sig only for new snow OR high altitudes)
460  ! from Sun et al. (1999): based on data from Jordan (1991)
461  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
462  !
463  REAL(r_std), SAVE          :: ZSNOWCMPCT_RHOD  = 150.0        !! (kg/m3)
464  REAL(r_std), SAVE          :: ZSNOWCMPCT_ACM   = 2.8e-6       !! (1/s)
465  REAL(r_std), SAVE          :: ZSNOWCMPCT_BCM   = 0.04         !! (1/K)
466  REAL(r_std), SAVE          :: ZSNOWCMPCT_CCM   = 460.         !! (m3/kg)
467  REAL(r_std), SAVE          :: ZSNOWCMPCT_V0    = 3.7e7        !! (Pa/s)
468  REAL(r_std), SAVE          :: ZSNOWCMPCT_VT    = 0.081        !! (1/K)
469  REAL(r_std), SAVE          :: ZSNOWCMPCT_VR    = 0.018        !! (m3/kg)
470
471  !
472  ! BVOC : Biogenic activity  for each age class
473  !
474  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
475                                                                                       !! age class : isoprene (unitless)
476!$OMP THREADPRIVATE(iso_activity)
477  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
478                                                                                       !! age class : methanol (unnitless)
479!$OMP THREADPRIVATE(methanol_activity)
480
481  !
482  ! condveg.f90
483  !
484
485  ! 1. Scalar
486
487  ! 1.1 Flags used inside the module
488
489  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
490                                            !! albedo (see header of subroutine)
491                                            !! (true/false)
492!$OMP THREADPRIVATE(alb_bare_model)
493  LOGICAL, SAVE :: alb_bg_modis = .TRUE.    !! Switch for choosing values of bare soil
494                                            !! albedo read from file
495                                            !! (true/false)
496!$OMP THREADPRIVATE(alb_bg_modis)
497  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
498                                            !! (see header of subroutine). 
499                                            !! (true/false)
500!$OMP THREADPRIVATE(impaze)
501  LOGICAL, SAVE :: rough_dyn = .TRUE.       !! Chooses between two methods to calculate the
502                                            !! the roughness height : static or dynamic (varying with LAI)
503                                            !! (true/false)
504!$OMP THREADPRIVATE(rough_dyn)
505
506  LOGICAL, SAVE :: new_watstress = .FALSE.
507!$OMP THREADPRIVATE(new_watstress)
508
509  REAL(r_std), SAVE :: alpha_watstress = 1.
510!$OMP THREADPRIVATE(alpha_watstress)
511
512  ! 1.2 Others
513
514
515  REAL(r_std), SAVE :: height_displacement = 0.66        !! Factor to calculate the zero-plane displacement
516                                                         !! height from vegetation height (m)
517!$OMP THREADPRIVATE(height_displacement)
518  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
519!$OMP THREADPRIVATE(z0_bare)
520  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
521!$OMP THREADPRIVATE(z0_ice)
522  REAL(r_std), SAVE :: tcst_snowa = 10.0                 !! Time constant of the albedo decay of snow (days), increased from the value 5.0 (04/07/2016)
523!$OMP THREADPRIVATE(tcst_snowa)
524  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
525!$OMP THREADPRIVATE(snowcri_alb)
526  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
527!$OMP THREADPRIVATE(fixed_snow_albedo)
528  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
529!$OMP THREADPRIVATE(z0_scal)
530  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
531                                                         !! displacement height (m) (imposed)
532!$OMP THREADPRIVATE(roughheight_scal)
533  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
534!$OMP THREADPRIVATE(emis_scal)
535
536  REAL(r_std), SAVE :: c1 = 0.32                         !! Constant used in the formulation of the ratio of
537!$OMP THREADPRIVATE(c1)                                  !! friction velocity to the wind speed at the canopy top
538                                                         !! see Ershadi et al. (2015) for more info
539  REAL(r_std), SAVE :: c2 = 0.264                        !! Constant used in the formulation of the ratio of
540!$OMP THREADPRIVATE(c2)                                  !! friction velocity to the wind speed at the canopy top
541                                                         !! see Ershadi et al. (2015) for more info
542  REAL(r_std), SAVE :: c3 = 15.1                         !! Constant used in the formulation of the ratio of
543!$OMP THREADPRIVATE(c3)                                  !! friction velocity to the wind speed at the canopy top
544                                                         !! see Ershadi et al. (2015) for more info
545  REAL(r_std), SAVE :: Cdrag_foliage = 0.2               !! Drag coefficient of the foliage
546!$OMP THREADPRIVATE(Cdrag_foliage)                       !! See Ershadi et al. (2015) and Su et. al (2001) for more info
547  REAL(r_std), SAVE :: Ct = 0.01                         !! Heat transfer coefficient of the leaf
548!$OMP THREADPRIVATE(Ct)                                  !! See Ershadi et al. (2015) and Su et. al (2001) for more info
549  REAL(r_std), SAVE :: Prandtl = 0.71                    !! Prandtl number used in the calculation of Ct_star
550!$OMP THREADPRIVATE(Prandtl)                             !! See Su et. al (2001) for more info
551
552
553
554  ! 2. Arrays
555
556  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
557!$OMP THREADPRIVATE(alb_deadleaf)
558  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
559!$OMP THREADPRIVATE(alb_ice)
560  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! Albedo values for visible and near-infrared
561                                                                     !! used imposed (unitless)
562!$OMP THREADPRIVATE(albedo_scal)
563  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
564       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
565                                                          !! dry soil albedo values in visible range
566!$OMP THREADPRIVATE(vis_dry)
567  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
568       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
569                                                          !! dry soil albedo values in near-infrared range
570!$OMP THREADPRIVATE(nir_dry)
571  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
572       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
573                                                          !! wet soil albedo values in visible range
574!$OMP THREADPRIVATE(vis_wet)
575  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
576       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
577                                                          !! wet soil albedo values in near-infrared range
578!$OMP THREADPRIVATE(nir_wet)
579  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
580       &0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25/)   !! Soil albedo values to soil colour classification:
581                                                                   !! Averaged of wet and dry soil albedo values
582                                                                   !! in visible and near-infrared range
583!$OMP THREADPRIVATE(albsoil_vis)
584  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
585       &0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45/)  !! Soil albedo values to soil colour classification:
586                                                                !! Averaged of wet and dry soil albedo values
587                                                                !! in visible and near-infrared range
588!$OMP THREADPRIVATE(albsoil_nir)
589
590  !
591  ! diffuco.f90
592  !
593
594  ! 0. Constants
595
596  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
597                                                     !! of dry air (unitless)
598  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
599  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
600  REAL(r_std), PARAMETER :: mol_to_m_1 = 0.0244      !!
601  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
602  REAL(r_std), PARAMETER :: W_to_mol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
603
604  ! 1. Scalar
605
606  INTEGER(i_std), SAVE :: nlai = 20             !! Number of LAI levels (unitless)
607!$OMP THREADPRIVATE(nlai)
608  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
609!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
610  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
611!$OMP THREADPRIVATE(laimax)
612  LOGICAL, SAVE :: downregulation_co2 = .TRUE.             !! Set to .TRUE. if you want CO2 downregulation.
613!$OMP THREADPRIVATE(downregulation_co2)
614  REAL(r_std), SAVE :: downregulation_co2_baselevel = 380. !! CO2 base level (ppm)
615!$OMP THREADPRIVATE(downregulation_co2_baselevel)
616
617  REAL(r_std), SAVE :: gb_ref = 1./25.                     !! Leaf bulk boundary layer resistance (s m-1)
618
619  ! 3. Coefficients of equations
620
621  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
622!$OMP THREADPRIVATE(lai_level_depth)
623!
624  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
625  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
626!$OMP THREADPRIVATE(dew_veg_poly_coeff)
627!
628  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
629!$OMP THREADPRIVATE(Oi)
630  !
631  ! slowproc.f90
632  !
633
634  ! 1. Scalar
635
636  INTEGER(i_std), SAVE :: veget_year_orig = 0        !!  first year for landuse (number)
637!$OMP THREADPRIVATE(veget_year_orig)
638! The default value for clay fraction is an heritage, with no documentation nor justification.   
639  REAL(r_std), SAVE :: clayfraction_default = 0.2    !! Default value for clay fraction (0-1, unitless)
640!$OMP THREADPRIVATE(clayfraction_default)
641! We need to output sand and silt fractiosn for SP-MIP, and the following default values, corresponding to a Loamy soil, are selected.
642  REAL(r_std), SAVE :: sandfraction_default = 0.4    !! Default value for sand fraction (0-1, unitless)
643!$OMP THREADPRIVATE(sandfraction_default)
644  REAL(r_std), SAVE :: siltfraction_default = 0.4    !! Default value for silt fraction (0-1, unitless)
645!$OMP THREADPRIVATE(siltfraction_default)
646  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
647!$OMP THREADPRIVATE(min_vegfrac)
648  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
649!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
650 
651  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
652!$OMP THREADPRIVATE(stempdiag_bid)
653
654
655                           !-----------------------------!
656                           !  STOMATE AND LPJ PARAMETERS !
657                           !-----------------------------!
658
659
660  !
661  ! lpj_constraints.f90
662  !
663 
664  ! 1. Scalar
665
666  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
667                                           !! regeneration (vernalization) (years)
668!$OMP THREADPRIVATE(too_long)
669
670
671  !
672  ! lpj_establish.f90
673  !
674
675  ! 1. Scalar
676
677  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (ind/m2/dt_stomate)
678!$OMP THREADPRIVATE(estab_max_tree)
679  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (ind/m2/dt_stomate)
680!$OMP THREADPRIVATE(estab_max_grass)
681 
682  ! 3. Coefficients of equations
683
684  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
685!$OMP THREADPRIVATE(establish_scal_fact)
686  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
687!$OMP THREADPRIVATE(max_tree_coverage)
688  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
689!$OMP THREADPRIVATE(ind_0_estab)
690
691
692  !
693  ! lpj_fire.f90
694  !
695
696  ! 1. Scalar
697
698  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
699!$OMP THREADPRIVATE(tau_fire)
700  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
701                                                !! below which iginitions extinguish
702                                                !! @tex $(gC m^{-2})$ @endtex
703!$OMP THREADPRIVATE(litter_crit)
704  REAL(r_std), SAVE :: fire_resist_struct = 0.5 !!
705!$OMP THREADPRIVATE(fire_resist_struct)
706  ! 2. Arrays
707
708  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
709       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /)       !! compartments emitted to the atmosphere
710!$OMP THREADPRIVATE(co2frac)                                                         !! when burned (unitless, 0-1) 
711
712  ! 3. Coefficients of equations
713
714  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
715!$OMP THREADPRIVATE(bcfrac_coeff)
716  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
717!$OMP THREADPRIVATE(firefrac_coeff)
718
719  !
720  ! lpj_gap.f90
721  !
722
723  ! 1. Scalar
724
725  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
726                                                 !! @tex $(year^{-1})$ @endtex
727!$OMP THREADPRIVATE(ref_greff)
728
729  !               
730  ! lpj_light.f90
731  !             
732
733  ! 1. Scalar
734 
735  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
736                                            !! to fpc of last time step (F)? (true/false)
737!$OMP THREADPRIVATE(annual_increase)
738  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
739                                            !! (due to its branches etc.) (0-1, unitless)
740                                            !! This means that only a small fraction of its crown area
741                                            !! can be invaded by other trees.
742!$OMP THREADPRIVATE(min_cover)
743  !
744  ! lpj_pftinout.f90
745  !
746
747  ! 1. Scalar
748
749  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
750!$OMP THREADPRIVATE(min_avail)
751  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
752!$OMP THREADPRIVATE(ind_0)
753  ! 3. Coefficients of equations
754 
755  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
756!$OMP THREADPRIVATE(RIP_time_min)
757  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
758!$OMP THREADPRIVATE(npp_longterm_init)
759  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
760!$OMP THREADPRIVATE(everywhere_init)
761
762
763  !
764  ! stomate_alloc.f90
765  !
766
767  ! 0. Constants
768
769  REAL(r_std), PARAMETER :: max_possible_lai = 10. !! (m^2.m^{-2})
770  REAL(r_std), PARAMETER :: Nlim_Q10 = 10.         !!
771
772  ! 1. Scalar
773
774  LOGICAL, SAVE :: ok_minres = .TRUE.              !! [DISPENSABLE] Do we try to reach a minimum reservoir even if
775                                                   !! we are severely stressed? (true/false)
776!$OMP THREADPRIVATE(ok_minres)
777  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
778                                                   !! carbohydrate reserve may be used for
779                                                   !! trees (days)
780!$OMP THREADPRIVATE(reserve_time_tree)
781  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
782                                                   !! carbohydrate reserve may be used for
783                                                   !! grasses (days)
784!$OMP THREADPRIVATE(reserve_time_grass)
785
786  REAL(r_std), SAVE :: f_fruit = 0.1               !! Default fruit allocation (0-1, unitless)
787!$OMP THREADPRIVATE(f_fruit)
788  REAL(r_std), SAVE :: alloc_sap_above_grass = 1.0 !! fraction of sapwood allocation above ground
789                                                   !! for grass (0-1, unitless)
790!$OMP THREADPRIVATE(alloc_sap_above_grass)
791  REAL(r_std), SAVE :: min_LtoLSR = 0.2            !! Prescribed lower bounds for leaf
792                                                   !! allocation (0-1, unitless)
793!$OMP THREADPRIVATE(min_LtoLSR)
794  REAL(r_std), SAVE :: max_LtoLSR = 0.5            !! Prescribed upper bounds for leaf
795                                                   !! allocation (0-1, unitless)
796!$OMP THREADPRIVATE(max_LtoLSR)
797  REAL(r_std), SAVE :: z_nitrogen = 0.2            !! Curvature of the root profile (m)
798!$OMP THREADPRIVATE(z_nitrogen)
799
800  ! 3. Coefficients of equations
801
802  REAL(r_std), SAVE :: Nlim_tref = 25.             !! (C)
803!$OMP THREADPRIVATE(Nlim_tref)
804
805
806  !
807  ! stomate_data.f90
808  !
809
810  ! 1. Scalar
811
812  ! 1.1 Parameters for the pipe model
813
814  REAL(r_std), SAVE :: pipe_tune1 = 100.0        !! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory) (unitless)
815!$OMP THREADPRIVATE(pipe_tune1)
816  REAL(r_std), SAVE :: pipe_tune2 = 40.0         !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
817!$OMP THREADPRIVATE(pipe_tune2)
818  REAL(r_std), SAVE :: pipe_tune3 = 0.5          !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
819!$OMP THREADPRIVATE(pipe_tune3)
820  REAL(r_std), SAVE :: pipe_tune4 = 0.3          !! needed for stem diameter (unitless)
821!$OMP THREADPRIVATE(pipe_tune4)
822  REAL(r_std), SAVE :: pipe_density = 2.e5       !! Density
823!$OMP THREADPRIVATE(pipe_density)
824  REAL(r_std), SAVE :: pipe_k1 = 8.e3            !! one more SAVE
825!$OMP THREADPRIVATE(pipe_k1)
826  REAL(r_std), SAVE :: pipe_tune_exp_coeff = 1.6 !! pipe tune exponential coeff (unitless)
827!$OMP THREADPRIVATE(pipe_tune_exp_coeff)
828
829  ! 1.2 climatic parameters
830
831  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
832!$OMP THREADPRIVATE(precip_crit)
833  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
834!$OMP THREADPRIVATE(gdd_crit_estab)
835  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
836!$OMP THREADPRIVATE(fpc_crit)
837
838  ! 1.3 sapling characteristics
839
840  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
841!$OMP THREADPRIVATE(alpha_grass)
842  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
843!$OMP THREADPRIVATE(alpha_tree)
844  REAL(r_std), SAVE :: mass_ratio_heart_sap = 3. !! mass ratio (heartwood+sapwood)/sapwood (unitless)
845!$OMP THREADPRIVATE(mass_ratio_heart_sap)
846
847  ! 1.4  time scales for phenology and other processes (in days)
848
849  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
850!$OMP THREADPRIVATE(tau_hum_month)
851  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
852!$OMP THREADPRIVATE(tau_hum_week)
853  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
854!$OMP THREADPRIVATE(tau_t2m_month)
855  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
856!$OMP THREADPRIVATE(tau_t2m_week)
857  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
858!$OMP THREADPRIVATE(tau_tsoil_month)
859  REAL(r_std), SAVE :: tau_soilhum_month = 20.    !! (days)     
860!$OMP THREADPRIVATE(tau_soilhum_month)
861  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
862!$OMP THREADPRIVATE(tau_gpp_week)
863  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
864!$OMP THREADPRIVATE(tau_gdd)
865  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
866!$OMP THREADPRIVATE(tau_ngd)
867  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
868!$OMP THREADPRIVATE(coeff_tau_longterm)
869  REAL(r_std), SAVE :: tau_longterm_max           !! (days) 
870!$OMP THREADPRIVATE(tau_longterm_max)
871
872  ! 3. Coefficients of equations
873
874  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
875!$OMP THREADPRIVATE(bm_sapl_carbres)
876  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
877!$OMP THREADPRIVATE(bm_sapl_sapabove)
878  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
879!$OMP THREADPRIVATE(bm_sapl_heartabove)
880  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
881!$OMP THREADPRIVATE(bm_sapl_heartbelow)
882  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
883!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
884  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
885!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
886  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
887!$OMP THREADPRIVATE(init_sapl_mass_carbres)
888  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
889!$OMP THREADPRIVATE(init_sapl_mass_root)
890  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
891!$OMP THREADPRIVATE(init_sapl_mass_fruit)
892  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
893!$OMP THREADPRIVATE(cn_sapl_init)
894  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
895!$OMP THREADPRIVATE(migrate_tree)
896  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
897!$OMP THREADPRIVATE(migrate_grass)
898  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
899!$OMP THREADPRIVATE(lai_initmin_tree)
900  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
901!$OMP THREADPRIVATE(lai_initmin_grass)
902  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
903!$OMP THREADPRIVATE(dia_coeff)
904  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
905!$OMP THREADPRIVATE(maxdia_coeff)
906  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
907!$OMP THREADPRIVATE(bm_sapl_leaf)
908
909
910
911  !
912  ! stomate_litter.f90
913  !
914
915  ! 0. Constants
916
917  REAL(r_std), PARAMETER :: Q10 = 10.               !!
918
919  ! 1. Scalar
920
921  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
922!$OMP THREADPRIVATE(z_decomp)
923
924  ! 2. Arrays
925
926  REAL(r_std), SAVE :: frac_soil_struct_aa = 0.55   !! corresponding to frac_soil(istructural,iactive,iabove)
927!$OMP THREADPRIVATE(frac_soil_struct_aa)
928  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
929!$OMP THREADPRIVATE(frac_soil_struct_ab)
930  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
931!$OMP THREADPRIVATE(frac_soil_struct_sa)
932  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
933!$OMP THREADPRIVATE(frac_soil_struct_sb)
934  REAL(r_std), SAVE :: frac_soil_metab_aa = 0.45    !! corresponding to frac_soil(imetabolic,iactive,iabove)
935!$OMP THREADPRIVATE(frac_soil_metab_aa)
936  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
937!$OMP THREADPRIVATE(frac_soil_metab_ab)
938  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = &    !! C/N ratio of each plant pool (0-100, unitless)
939       & (/ 40., 40., 40., 40., 40., 40., 40., 40. /) 
940!$OMP THREADPRIVATE(CN)
941  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = &    !! Lignin/C ratio of different plant parts (0,22-0,35, unitless)
942       & (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /)
943!$OMP THREADPRIVATE(LC)
944
945  ! 3. Coefficients of equations
946
947  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
948!$OMP THREADPRIVATE(metabolic_ref_frac)
949  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
950!$OMP THREADPRIVATE(metabolic_LN_ratio)
951  REAL(r_std), SAVE :: tau_metabolic = 0.066        !!
952!$OMP THREADPRIVATE(tau_metabolic)
953  REAL(r_std), SAVE :: tau_struct = 0.245           !!
954!$OMP THREADPRIVATE(tau_struct)
955  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
956!$OMP THREADPRIVATE(soil_Q10)
957  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
958!$OMP THREADPRIVATE(tsoil_ref)
959  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
960!$OMP THREADPRIVATE(litter_struct_coef)
961  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
962!$OMP THREADPRIVATE(moist_coeff)
963  REAL(r_std), SAVE :: moistcont_min = 0.25  !! minimum soil wetness to limit the heterotrophic respiration
964!$OMP THREADPRIVATE(moistcont_min)
965
966
967  !
968  ! stomate_lpj.f90
969  !
970
971  ! 1. Scalar
972
973  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
974!$OMP THREADPRIVATE(frac_turnover_daily)
975
976
977  !
978  ! stomate_npp.f90
979  !
980
981  ! 1. Scalar
982
983  REAL(r_std), SAVE :: tax_max = 0.8 !! Maximum fraction of allocatable biomass used
984                                     !! for maintenance respiration (0-1, unitless)
985!$OMP THREADPRIVATE(tax_max)
986
987
988  !
989  ! stomate_phenology.f90
990  !
991
992  ! 1. Scalar
993
994  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
995!$OMP THREADPRIVATE(min_growthinit_time)
996  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
997                                                   !!  - for trees (0-1, unitless)
998!$OMP THREADPRIVATE(moiavail_always_tree)
999  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1000                                                   !! - for grass (0-1, unitless)
1001!$OMP THREADPRIVATE(moiavail_always_grass)
1002  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
1003!$OMP THREADPRIVATE(t_always)
1004  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
1005!$OMP THREADPRIVATE(t_always_add)
1006
1007  ! 3. Coefficients of equations
1008 
1009  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
1010!$OMP THREADPRIVATE(gddncd_ref)
1011  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
1012!$OMP THREADPRIVATE(gddncd_curve)
1013  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
1014!$OMP THREADPRIVATE(gddncd_offset)
1015
1016
1017  !
1018  ! stomate_prescribe.f90
1019  !
1020
1021  ! 3. Coefficients of equations
1022
1023  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
1024!$OMP THREADPRIVATE(bm_sapl_rescale)
1025
1026
1027  !
1028  ! stomate_resp.f90
1029  !
1030
1031  ! 3. Coefficients of equations
1032
1033  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
1034!$OMP THREADPRIVATE(maint_resp_min_vmax)
1035  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
1036!$OMP THREADPRIVATE(maint_resp_coeff)
1037
1038
1039  !
1040  ! stomate_soilcarbon.f90
1041  !
1042
1043  ! 2. Arrays
1044
1045  ! 2.1 frac_carb_coefficients
1046
1047  REAL(r_std), SAVE :: frac_carb_ap = 0.004  !! from active pool: depends on clay content  (0-1, unitless)
1048                                             !! corresponding to frac_carb(:,iactive,ipassive)
1049!$OMP THREADPRIVATE(frac_carb_ap)
1050  REAL(r_std), SAVE :: frac_carb_sa = 0.42   !! from slow pool (0-1, unitless)
1051                                             !! corresponding to frac_carb(:,islow,iactive)
1052!$OMP THREADPRIVATE(frac_carb_sa)
1053  REAL(r_std), SAVE :: frac_carb_sp = 0.03   !! from slow pool (0-1, unitless)
1054                                             !! corresponding to frac_carb(:,islow,ipassive)
1055!$OMP THREADPRIVATE(frac_carb_sp)
1056  REAL(r_std), SAVE :: frac_carb_pa = 0.45   !! from passive pool (0-1, unitless)
1057                                             !! corresponding to frac_carb(:,ipassive,iactive)
1058!$OMP THREADPRIVATE(frac_carb_pa)
1059  REAL(r_std), SAVE :: frac_carb_ps = 0.0    !! from passive pool (0-1, unitless)
1060                                             !! corresponding to frac_carb(:,ipassive,islow)
1061!$OMP THREADPRIVATE(frac_carb_ps)
1062
1063  ! 3. Coefficients of equations
1064
1065  REAL(r_std), SAVE :: active_to_pass_clay_frac = 0.68  !! (0-1, unitless)
1066!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1067  !! residence times in carbon pools (days)
1068  REAL(r_std), SAVE :: carbon_tau_iactive = 0.149   !! residence times in active pool (days)
1069!$OMP THREADPRIVATE(carbon_tau_iactive)
1070  REAL(r_std), SAVE :: carbon_tau_islow = 7.0       !! residence times in slow pool (days)
1071!$OMP THREADPRIVATE(carbon_tau_islow)
1072  REAL(r_std), SAVE :: carbon_tau_ipassive = 300.   !! residence times in passive pool (days)
1073!$OMP THREADPRIVATE(carbon_tau_ipassive)
1074  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
1075!$OMP THREADPRIVATE(flux_tot_coeff)
1076
1077  !
1078  ! stomate_turnover.f90
1079  !
1080
1081  ! 3. Coefficients of equations
1082
1083  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
1084!$OMP THREADPRIVATE(new_turnover_time_ref)
1085  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
1086!$OMP THREADPRIVATE(leaf_age_crit_tref)
1087  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
1088!$OMP THREADPRIVATE(leaf_age_crit_coeff)
1089
1090
1091  !
1092  ! stomate_vmax.f90
1093  !
1094 
1095  ! 1. Scalar
1096
1097  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
1098!$OMP THREADPRIVATE(vmax_offset)
1099  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1100                                                !! reaches 1 (unitless)
1101!$OMP THREADPRIVATE(leafage_firstmax)
1102  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1103                                                !! falls below 1 (unitless)
1104!$OMP THREADPRIVATE(leafage_lastmax)
1105  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1106                                                !! reaches its minimum (vmax_offset)
1107                                                !! (unitless)
1108!$OMP THREADPRIVATE(leafage_old)
1109  !
1110  ! stomate_season.f90
1111  !
1112
1113  ! 1. Scalar
1114
1115  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
1116!$OMP THREADPRIVATE(gppfrac_dormance)
1117  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
1118!$OMP THREADPRIVATE(tau_climatology)
1119  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
1120!$OMP THREADPRIVATE(hvc1)
1121  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
1122!$OMP THREADPRIVATE(hvc2)
1123  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
1124!$OMP THREADPRIVATE(leaf_frac_hvc)
1125  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
1126!$OMP THREADPRIVATE(tlong_ref_max)
1127  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
1128!$OMP THREADPRIVATE(tlong_ref_min)
1129
1130  ! 3. Coefficients of equations
1131
1132  REAL(r_std), SAVE :: ncd_max_year = 3.
1133!$OMP THREADPRIVATE(ncd_max_year)
1134  REAL(r_std), SAVE :: gdd_threshold = 5.
1135!$OMP THREADPRIVATE(gdd_threshold)
1136  REAL(r_std), SAVE :: green_age_ever = 2.
1137!$OMP THREADPRIVATE(green_age_ever)
1138  REAL(r_std), SAVE :: green_age_dec = 0.5
1139!$OMP THREADPRIVATE(green_age_dec)
1140
1141END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.