source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_var.f90 @ 6393

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

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

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

See ticket #641

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