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

Last change on this file was 8462, checked in by josefine.ghattas, 4 months ago

The Moyano function describing the soil moisture effect on OM decomposition is added. It has been developed by Elodie Salmon in another branch and integrated in ORCHIDEE_2_2 by Bertrad Guenet. This commit corresponds to a corrected version of [8418].

  • Property svn:keywords set to Date Revision
File size: 64.4 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  !-
[8377]229#ifndef OASIS
230  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! Radius of the Earth : Earth radius ~= Equatorial radius (m)
231#else
232  REAL(r_std), PARAMETER :: R_Earth = 6370000.              !! When coupled through OASIS it is with WRF. We have to use another Earth radius 
233#endif
[836]234  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
[720]235  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
[2222]236  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! 0 degre Celsius in degre Kelvin (K)
[720]237  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
[737]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})
[720]244  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
245                                                            !! of dry air (unitless)
[737]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})
[720]249       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
[737]250  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
[720]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)
[737]255  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
[3524]256  REAL(r_std), PARAMETER :: ct_karman = 0.41_r_std          !! Van Karmann Constant (unitless)
[737]257  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
[720]258  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
[2031]259  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gas constant (J.mol^{-1}.K^{-1})
[890]260  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
[531]261
[890]262
[3972]263  INTEGER(i_std), SAVE :: testpft = 6
[5539]264!$OMP THREADPRIVATE(testpft)
[511]265  !-
[531]266  ! 3. Climatic constants
[511]267  !-
[620]268  !! Constantes of the Louis scheme
[2222]269  REAL(r_std), SAVE :: cb = 5._r_std              !! Constant of the Louis scheme (unitless);
[720]270                                                  !! reference to Louis (1979)
[2903]271!$OMP THREADPRIVATE(cb)
[2222]272  REAL(r_std), SAVE :: cc = 5._r_std              !! Constant of the Louis scheme (unitless);
[720]273                                                  !! reference to Louis (1979)
[2903]274!$OMP THREADPRIVATE(cc)
[2222]275  REAL(r_std), SAVE :: cd = 5._r_std              !! Constant of the Louis scheme (unitless);
[720]276                                                  !! reference to Louis (1979)
[2903]277!$OMP THREADPRIVATE(cd)
[2222]278  REAL(r_std), SAVE :: rayt_cste = 125.           !! Constant in the computation of surface resistance (W.m^{-2})
[2903]279!$OMP THREADPRIVATE(rayt_cste)
[2222]280  REAL(r_std), SAVE :: defc_plus = 23.E-3         !! Constant in the computation of surface resistance (K.W^{-1})
[2903]281!$OMP THREADPRIVATE(defc_plus)
[2222]282  REAL(r_std), SAVE :: defc_mult = 1.5            !! Constant in the computation of surface resistance (K.W^{-1})
[2903]283!$OMP THREADPRIVATE(defc_mult)
[531]284
[511]285  !-
[531]286  ! 4. Soil thermodynamics constants
[511]287  !-
[1082]288  ! Look at constantes_soil.f90
[511]289
[1082]290
[531]291  !
292  ! OPTIONAL PARTS OF THE MODEL
293  !
[720]294  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
295                                                  !! we provide here a way to catch that in the calling procedure.
296                                                  !! (from Jan Polcher)(true/false)
[2720]297  LOGICAL, SAVE     :: almaoutput =.FALSE.        !! Selects the type of output for the model.(true/false)
[720]298                                                  !! Value is read from run.def in intersurf_history
[1078]299!$OMP THREADPRIVATE(almaoutput)
[1082]300
[531]301  !
302  ! DIVERSE
303  !
[1078]304  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
305                                                           ! Compatibility with Nicolas Viovy driver.
306!$OMP THREADPRIVATE(stomate_forcing_name)
307  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
308                                                           ! Compatibility with Nicolas Viovy driver.
309!$OMP THREADPRIVATE(stomate_Cforcing_name)
[720]310  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
[1078]311!$OMP THREADPRIVATE(forcing_id)
[2305]312  LOGICAL, SAVE :: allow_forcing_write=.TRUE.        !! Allow writing of stomate_forcing file.
313                                                     !! This variable will be set to false for teststomate.
[5543]314!$OMP THREADPRIVATE(allow_forcing_write)
[511]315
316
317
[531]318                         !------------------------!
319                         !  SECHIBA PARAMETERS    !
320                         !------------------------!
321 
[511]322
[531]323  !
324  ! GLOBAL PARAMETERS   
325  !
[737]326  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
[1078]327!$OMP THREADPRIVATE(min_wind)
[6019]328  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]329  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occures (kg.m^{-2})
[1078]330!$OMP THREADPRIVATE(snowcri)
[511]331
[1082]332
[511]333  !
334  ! FLAGS ACTIVATING SUB-MODELS
335  !
[620]336  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
[1078]337!$OMP THREADPRIVATE(treat_expansion)
[947]338  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
[1078]339!$OMP THREADPRIVATE(ok_herbivores)
[947]340  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
[1078]341!$OMP THREADPRIVATE(harvest_agri)
[2668]342  LOGICAL, SAVE :: lpj_gap_const_mort          !! constant moratlity (true/false). Default value depend on OK_DGVM.
[1078]343!$OMP THREADPRIVATE(lpj_gap_const_mort)
[4962]344  LOGICAL, SAVE :: disable_fire = .TRUE.       !! flag that disable fire (true/false)
[1078]345!$OMP THREADPRIVATE(disable_fire)
[1100]346  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
347!$OMP THREADPRIVATE(spinup_analytic)
[1102]348
[511]349  !
[531]350  ! CONFIGURATION VEGETATION
[511]351  !
[620]352  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
[1078]353!$OMP THREADPRIVATE(agriculture)
[620]354  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
[1078]355!$OMP THREADPRIVATE(impveg)
[620]356  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
[1078]357!$OMP THREADPRIVATE(impsoilt)
[7547]358  LOGICAL, SAVE :: impslope = .FALSE.      !! Impose reinf_slope ? (true/false)
359!$OMP THREADPRIVATE(impslope)
[2718]360  LOGICAL, SAVE :: do_now_stomate_lcchange = .FALSE.  !! Time to call lcchange in stomate_lpj
361!$OMP THREADPRIVATE(do_now_stomate_lcchange)
[4657]362  LOGICAL, SAVE :: do_now_stomate_woodharvest = .FALSE.  !! Time to call woodharvest in stomate_lpj
363!$OMP THREADPRIVATE(do_now_stomate_woodharvest)
[3094]364  LOGICAL, SAVE :: done_stomate_lcchange = .FALSE.    !! If true, call lcchange in stomate_lpj has just been done.
365!$OMP THREADPRIVATE(done_stomate_lcchange)
[947]366  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
[1078]367!$OMP THREADPRIVATE(read_lai)
[628]368  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
[1078]369!$OMP THREADPRIVATE(veget_reinit)
[5605]370  LOGICAL, SAVE :: vegetmap_reset = .FALSE.!! Reset the vegetation map and reset carbon related variables
371!$OMP THREADPRIVATE(vegetmap_reset)
[5389]372  INTEGER(i_std) , SAVE :: veget_update    !! Update frequency in years for landuse (nb of years)
373!$OMP THREADPRIVATE(veget_update)
[511]374  !
[531]375  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
[511]376  !
[628]377  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
[1078]378!$OMP THREADPRIVATE(max_snow_age)
[3605]379  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]380!$OMP THREADPRIVATE(snow_trans)
[737]381  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
[1078]382!$OMP THREADPRIVATE(sneige)
[2053]383  REAL(r_std), SAVE :: maxmass_snow = 3000.     !! The maximum mass of snow (kg.m^{-2})
384!$OMP THREADPRIVATE(maxmass_snow)
[1082]385
[2222]386  !! Heat capacity
387  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3)
388  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3)
[4820]389  REAL(r_std), PARAMETER :: rho_soil = 2700.            !! Density of soil particles (kg/m3), value from Peters-Lidard et al. 1998
[2222]390
391  !! Thermal conductivities
392  REAL(r_std), PARAMETER :: cond_water = 0.6            !! Thermal conductivity of liquid water (W/m/K)
393  REAL(r_std), PARAMETER :: cond_ice = 2.2              !! Thermal conductivity of ice (W/m/K)
394  REAL(r_std), PARAMETER :: cond_solid = 2.32           !! Thermal conductivity of mineral soil particles (W/m/K)
395
396  !! Time constant of long-term soil humidity (s)
397  REAL(r_std), PARAMETER :: lhf = 0.3336*1.E6           !! Latent heat of fusion (J/kg)
398
399  INTEGER(i_std), PARAMETER :: nsnow=3                  !! Number of levels in the snow for explicit snow scheme   
400  REAL(r_std), PARAMETER    :: XMD    = 28.9644E-3 
401  REAL(r_std), PARAMETER    :: XBOLTZ      = 1.380658E-23 
402  REAL(r_std), PARAMETER    :: XAVOGADRO   = 6.0221367E+23 
403  REAL(r_std), PARAMETER    :: XRD    = XAVOGADRO * XBOLTZ / XMD 
404  REAL(r_std), PARAMETER    :: XCPD   = 7.* XRD /2. 
405  REAL(r_std), PARAMETER    :: phigeoth = 0.057 ! 0. DKtest
406  REAL(r_std), PARAMETER    :: thick_min_snow = .01 
407
408  !! The maximum snow density and water holding characterisicts
409  REAL(r_std), SAVE         :: xrhosmax = 750.  ! (kg m-3)
[5541]410!$OMP THREADPRIVATE(xrhosmax)
[2222]411  REAL(r_std), SAVE         :: xwsnowholdmax1   = 0.03  ! (-)
[5539]412!$OMP THREADPRIVATE(xwsnowholdmax1)
[2222]413  REAL(r_std), SAVE         :: xwsnowholdmax2   = 0.10  ! (-)
[5539]414!$OMP THREADPRIVATE(xwsnowholdmax2)
[2222]415  REAL(r_std), SAVE         :: xsnowrhohold     = 200.0 ! (kg/m3)
[5539]416!$OMP THREADPRIVATE(xsnowrhohold)
[2222]417  REAL(r_std), SAVE         :: xrhosmin = 50. 
[5539]418!$OMP THREADPRIVATE(xrhosmin)
[2222]419  REAL(r_std), PARAMETER    :: xci = 2.106e+3 
420  REAL(r_std), PARAMETER    :: xrv = 6.0221367e+23 * 1.380658e-23 /18.0153e-3 
421
422  !! ISBA-ES Critical snow depth at which snow grid thicknesses constant
423  REAL(r_std), PARAMETER    :: xsnowcritd = 0.03  ! (m)
[2650]424
425  !! The threshold of snow depth used for preventing numerical problem in thermal calculations
426  REAL(r_std), PARAMETER    :: snowcritd_thermal = 0.01  ! (m) 
[2222]427 
428  !! ISBA-ES CROCUS (Pahaut 1976): snowfall density coefficients:
429  REAL(r_std), PARAMETER       :: snowfall_a_sn = 109.0  !! (kg/m3)
430  REAL(r_std), PARAMETER       :: snowfall_b_sn =   6.0  !! (kg/m3/K)
431  REAL(r_std), PARAMETER       :: snowfall_c_sn =  26.0  !! [kg/(m7/2 s1/2)]
432
433  REAL(r_std), PARAMETER       :: dgrain_new_max=  2.0e-4!! (m) : Maximum grain size of new snowfall
434 
[2650]435  !! Used in explicitsnow to prevent numerical problems as snow becomes vanishingly thin.
[2222]436  REAL(r_std), PARAMETER                :: psnowdzmin = .0001   ! m
437  REAL(r_std), PARAMETER                :: xsnowdmin = .000001  ! m
438
439  REAL(r_std), PARAMETER                :: ph2o = 1000.         !! Water density [kg/m3]
440 
441  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
442  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
443  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND1 = 0.02    ! [W/m/K]
[5539]444!$OMP THREADPRIVATE(ZSNOWTHRMCOND1)
[2222]445  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND2 = 2.5E-6  ! [W m5/(kg2 K)]
[5539]446!$OMP THREADPRIVATE(ZSNOWTHRMCOND2)
[2222]447 
448  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
449  ! (sig only for new snow OR high altitudes)
450  ! from Sun et al. (1999): based on data from Jordan (1991)
451  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
452  !
453  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_AVAP  = -0.06023 ! (W/m/K)
[5541]454!$OMP THREADPRIVATE(ZSNOWTHRMCOND_AVAP)
[2222]455  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_BVAP  = -2.5425  ! (W/m)
[5541]456!$OMP THREADPRIVATE(ZSNOWTHRMCOND_BVAP)
[2222]457  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_CVAP  = -289.99  ! (K)
[5541]458!$OMP THREADPRIVATE(ZSNOWTHRMCOND_CVAP)
[2222]459 
460  REAL(r_std),SAVE :: xansmax = 0.85      !! Maxmimum snow albedo
[5539]461!$OMP THREADPRIVATE(xansmax)
[2222]462  REAL(r_std),SAVE :: xansmin = 0.50      !! Miniumum snow albedo
[5539]463!$OMP THREADPRIVATE(xansmin)
[2222]464  REAL(r_std),SAVE :: xans_todry = 0.008  !! Albedo decay rate for dry snow
[5539]465!$OMP THREADPRIVATE(xans_todry)
[2222]466  REAL(r_std),SAVE :: xans_t = 0.240      !! Albedo decay rate for wet snow
[5539]467!$OMP THREADPRIVATE(xans_t)
[2222]468
469  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
470  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
471  REAL(r_std), PARAMETER                  :: XP00 = 1.E5
472
473  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
474  ! (sig only for new snow OR high altitudes)
475  ! from Sun et al. (1999): based on data from Jordan (1991)
476  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
[890]477  !
[2222]478  REAL(r_std), SAVE          :: ZSNOWCMPCT_RHOD  = 150.0        !! (kg/m3)
[5539]479!$OMP THREADPRIVATE(ZSNOWCMPCT_RHOD)
480  REAL(r_std), SAVE          :: ZSNOWCMPCT_ACM   = 2.8e-6       !! (1/s
481!$OMP THREADPRIVATE(ZSNOWCMPCT_ACM)
[2222]482  REAL(r_std), SAVE          :: ZSNOWCMPCT_BCM   = 0.04         !! (1/K)
[5539]483!$OMP THREADPRIVATE(ZSNOWCMPCT_BCM)
[2222]484  REAL(r_std), SAVE          :: ZSNOWCMPCT_CCM   = 460.         !! (m3/kg)
[5539]485!$OMP THREADPRIVATE(ZSNOWCMPCT_CCM)
[2222]486  REAL(r_std), SAVE          :: ZSNOWCMPCT_V0    = 3.7e7        !! (Pa/s)
[5539]487!$OMP THREADPRIVATE(ZSNOWCMPCT_V0)
[2222]488  REAL(r_std), SAVE          :: ZSNOWCMPCT_VT    = 0.081        !! (1/K)
[5539]489!$OMP THREADPRIVATE(ZSNOWCMPCT_VT)
[2222]490  REAL(r_std), SAVE          :: ZSNOWCMPCT_VR    = 0.018        !! (m3/kg)
[5539]491!$OMP THREADPRIVATE(ZSNOWCMPCT_VR)
[2222]492
493  !
[890]494  ! BVOC : Biogenic activity  for each age class
495  !
496  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
497                                                                                       !! age class : isoprene (unitless)
[1078]498!$OMP THREADPRIVATE(iso_activity)
[890]499  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
500                                                                                       !! age class : methanol (unnitless)
[1078]501!$OMP THREADPRIVATE(methanol_activity)
[511]502
[7709]503
504 !
505 ! Parameters for irrigation scheme
506 !
[8320]507  REAL(r_std), SAVE :: irrig_dosmax = 3.              !! The maximum irrigation water injected per hour (kg.m^{-2}/hour)
[7709]508!$OMP THREADPRIVATE(irrig_dosmax)
[8320]509  REAL(r_std), SAVE :: cum_dh_thr = 0.64                !! Cumulated nroot threshoold to define root zone, and calculate water deficit for irrigation (-)
510!$OMP THREADPRIVATE(cum_dh_thr)
[7709]511  LOGICAL, SAVE :: irrigated_soiltile = .FALSE.       !! Do we introduce a new soil tile for irrigated croplands? (true/false)
512!$OMP THREADPRIVATE(irrigated_soiltile)
513  LOGICAL, SAVE :: old_irrig_scheme = .FALSE.         !! Do we run with the old irrigation scheme? (true/false)  , add to compatiblity
514!$OMP THREADPRIVATE(old_irrig_scheme)
515  INTEGER, SAVE :: irrig_st = 3                       !! Which is the soil tile with irrigation flux
516!$OMP THREADPRIVATE(irrig_st)
[8320]517  REAL(r_std), SAVE, DIMENSION(3) :: avail_reserve = (/0.9,0.9,0.9/)     !! Available water from routing reservoirs, to withdraw for irrigation
[7709]518                                                      !! IMPORTANT: As the routing model uses 3 reservoirs, dimension is set to 3
519                                                      !! IMPORTANT: Order of available water must be in this order: streamflow, fast, and slow reservoir
520!$OMP THREADPRIVATE(avail_reserve)
[8320]521  REAL(r_std), SAVE :: beta_irrig = 0.9               !! Threshold multiplier of Target SM to calculate root deficit(unitless)
[7709]522!$OMP THREADPRIVATE(beta_irrig)
523  REAL(r_std), SAVE :: lai_irrig_min = 0.1            !! Minimum LAI to trigger irrigation (kg.m^{-2}/hour)
524!$OMP THREADPRIVATE(lai_irrig_min)
525  LOGICAL, SAVE :: irrig_map_dynamic_flag = .FALSE.   !! Do we use a dynamic irrig map?
526!$OMP THREADPRIVATE(irrig_map_dynamic_flag)
527  LOGICAL, SAVE :: select_source_irrig = .FALSE.      !! Do we use the new priorization scheme, based on maps of equipped area with surface water?
528!$OMP THREADPRIVATE(select_source_irrig)
529  LOGICAL, SAVE :: Reinfiltr_IrrigField = .FALSE.     !! Do we reinfiltrate all runoff from crop soil tile?O
530!$OMP THREADPRIVATE(Reinfiltr_IrrigField)
531  REAL, SAVE :: reinf_slope_cropParam = 0.8           !! Externalized for irrigated cropland, when Reinfiltr_IrrigField=.TRUE.
532                                                      !! Max value of reinf_slope in irrig_st 
533!$OMP THREADPRIVATE(reinf_slope_cropParam)
[8320]534  REAL, SAVE :: a_stream_adduction = 0.05             !! Externalized for available volume to adduction
[7709]535!$OMP THREADPRIVATE(a_stream_adduction)
536
537
538
[531]539  !
540  ! condveg.f90
541  !
[511]542
543  ! 1. Scalar
544
[531]545  ! 1.1 Flags used inside the module
[511]546
[947]547  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
548                                            !! albedo (see header of subroutine)
549                                            !! (true/false)
[1078]550!$OMP THREADPRIVATE(alb_bare_model)
[4962]551  LOGICAL, SAVE :: alb_bg_modis = .TRUE.    !! Switch for choosing values of bare soil
[3171]552                                            !! albedo read from file
553                                            !! (true/false)
554!$OMP THREADPRIVATE(alb_bg_modis)
[947]555  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
556                                            !! (see header of subroutine). 
557                                            !! (true/false)
[1078]558!$OMP THREADPRIVATE(impaze)
[4962]559  LOGICAL, SAVE :: rough_dyn = .TRUE.       !! Chooses between two methods to calculate the
[3524]560                                            !! the roughness height : static or dynamic (varying with LAI)
[947]561                                            !! (true/false)
[3524]562!$OMP THREADPRIVATE(rough_dyn)
[8273]563  LOGICAL, SAVE :: use_ratio_z0m_z0h = .FALSE. !! To impose a constant ratio as done in ROUGH_DYN=F
564!$OMP THREADPRIVATE(use_ratio_z0m_z0h)
[3524]565
[3972]566  LOGICAL, SAVE :: new_watstress = .FALSE.
567!$OMP THREADPRIVATE(new_watstress)
568
569  REAL(r_std), SAVE :: alpha_watstress = 1.
570!$OMP THREADPRIVATE(alpha_watstress)
571
[531]572  ! 1.2 Others
573
[3524]574
575  REAL(r_std), SAVE :: height_displacement = 0.66        !! Factor to calculate the zero-plane displacement
[947]576                                                         !! height from vegetation height (m)
[1078]577!$OMP THREADPRIVATE(height_displacement)
[620]578  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
[1078]579!$OMP THREADPRIVATE(z0_bare)
[620]580  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
[1078]581!$OMP THREADPRIVATE(z0_ice)
[3605]582  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]583!$OMP THREADPRIVATE(tcst_snowa)
[1957]584  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
[1078]585!$OMP THREADPRIVATE(snowcri_alb)
[947]586  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
[1078]587!$OMP THREADPRIVATE(fixed_snow_albedo)
[947]588  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
[1078]589!$OMP THREADPRIVATE(z0_scal)
[947]590  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
591                                                         !! displacement height (m) (imposed)
[1078]592!$OMP THREADPRIVATE(roughheight_scal)
[947]593  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
[1078]594!$OMP THREADPRIVATE(emis_scal)
[3524]595
596  REAL(r_std), SAVE :: c1 = 0.32                         !! Constant used in the formulation of the ratio of
597!$OMP THREADPRIVATE(c1)                                  !! friction velocity to the wind speed at the canopy top
598                                                         !! see Ershadi et al. (2015) for more info
599  REAL(r_std), SAVE :: c2 = 0.264                        !! Constant used in the formulation of the ratio of
600!$OMP THREADPRIVATE(c2)                                  !! friction velocity to the wind speed at the canopy top
601                                                         !! see Ershadi et al. (2015) for more info
602  REAL(r_std), SAVE :: c3 = 15.1                         !! Constant used in the formulation of the ratio of
603!$OMP THREADPRIVATE(c3)                                  !! friction velocity to the wind speed at the canopy top
604                                                         !! see Ershadi et al. (2015) for more info
605  REAL(r_std), SAVE :: Cdrag_foliage = 0.2               !! Drag coefficient of the foliage
606!$OMP THREADPRIVATE(Cdrag_foliage)                       !! See Ershadi et al. (2015) and Su et. al (2001) for more info
607  REAL(r_std), SAVE :: Ct = 0.01                         !! Heat transfer coefficient of the leaf
608!$OMP THREADPRIVATE(Ct)                                  !! See Ershadi et al. (2015) and Su et. al (2001) for more info
609  REAL(r_std), SAVE :: Prandtl = 0.71                    !! Prandtl number used in the calculation of Ct_star
610!$OMP THREADPRIVATE(Prandtl)                             !! See Su et. al (2001) for more info
611
612
613
[511]614  ! 2. Arrays
615
[720]616  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
[1078]617!$OMP THREADPRIVATE(alb_deadleaf)
[720]618  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
[1078]619!$OMP THREADPRIVATE(alb_ice)
[947]620  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! Albedo values for visible and near-infrared
621                                                                     !! used imposed (unitless)
[1078]622!$OMP THREADPRIVATE(albedo_scal)
623  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
[947]624       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
625                                                          !! dry soil albedo values in visible range
[1078]626!$OMP THREADPRIVATE(vis_dry)
627  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
[947]628       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
629                                                          !! dry soil albedo values in near-infrared range
[1078]630!$OMP THREADPRIVATE(nir_dry)
631  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
[947]632       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
633                                                          !! wet soil albedo values in visible range
[1078]634!$OMP THREADPRIVATE(vis_wet)
635  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
[947]636       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
637                                                          !! wet soil albedo values in near-infrared range
[1078]638!$OMP THREADPRIVATE(nir_wet)
639  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
[947]640       &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:
641                                                                   !! Averaged of wet and dry soil albedo values
642                                                                   !! in visible and near-infrared range
[1078]643!$OMP THREADPRIVATE(albsoil_vis)
644  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
[947]645       &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:
646                                                                !! Averaged of wet and dry soil albedo values
647                                                                !! in visible and near-infrared range
[1078]648!$OMP THREADPRIVATE(albsoil_nir)
[511]649
[531]650  !
651  ! diffuco.f90
652  !
653
654  ! 0. Constants
655
[720]656  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
657                                                     !! of dry air (unitless)
658  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
[2031]659  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
[3972]660  REAL(r_std), PARAMETER :: mol_to_m_1 = 0.0244      !!
[720]661  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
[3972]662  REAL(r_std), PARAMETER :: W_to_mol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
[531]663
[511]664  ! 1. Scalar
665
[720]666  INTEGER(i_std), SAVE :: nlai = 20             !! Number of LAI levels (unitless)
[1078]667!$OMP THREADPRIVATE(nlai)
[620]668  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
[1078]669!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
[890]670  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
[1078]671!$OMP THREADPRIVATE(laimax)
[6393]672  LOGICAL, SAVE :: downregulation_co2 = .TRUE.             !! Set to .TRUE. if you want CO2 downregulation version used for CMIP6 6.1.0-6.1.10
[1882]673!$OMP THREADPRIVATE(downregulation_co2)
[6393]674  LOGICAL, SAVE :: downregulation_co2_new = .FALSE.        !! Set to .TRUE. if you want CO2 downregulation version revised for CMIP6 6.1.11
675!$OMP THREADPRIVATE(downregulation_co2_new)
[4962]676  REAL(r_std), SAVE :: downregulation_co2_baselevel = 380. !! CO2 base level (ppm)
[1925]677!$OMP THREADPRIVATE(downregulation_co2_baselevel)
[6393]678  REAL(r_std), SAVE :: downregulation_co2_minimum = 280.   !! CO2 value above which downregulation is taken into account
679!$OMP THREADPRIVATE(downregulation_co2_minimum)
[511]680
[3972]681  REAL(r_std), SAVE :: gb_ref = 1./25.                     !! Leaf bulk boundary layer resistance (s m-1)
[5539]682!$OMP THREADPRIVATE(gb_ref)
[3972]683
[511]684  ! 3. Coefficients of equations
685
[720]686  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
[1078]687!$OMP THREADPRIVATE(lai_level_depth)
[2031]688!
[720]689  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
690  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
[1078]691!$OMP THREADPRIVATE(dew_veg_poly_coeff)
[2031]692!
693  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
694!$OMP THREADPRIVATE(Oi)
[531]695  !
696  ! slowproc.f90
697  !
[511]698
699  ! 1. Scalar
700
[947]701  INTEGER(i_std), SAVE :: veget_year_orig = 0        !!  first year for landuse (number)
[1078]702!$OMP THREADPRIVATE(veget_year_orig)
[7432]703 
[8462]704 REAL(r_std), SAVE :: bulk_default = 1000.0           !! Default value for bulk density of soil (kg/m3)
705!$OMP THREADPRIVATE(bulk_default)
[720]706  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
[1078]707!$OMP THREADPRIVATE(min_vegfrac)
[720]708  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]709!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
710 
[720]711  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
[1078]712!$OMP THREADPRIVATE(stempdiag_bid)
[511]713
714
715                           !-----------------------------!
716                           !  STOMATE AND LPJ PARAMETERS !
717                           !-----------------------------!
718
[531]719
[511]720  !
[531]721  ! lpj_constraints.f90
722  !
[511]723 
724  ! 1. Scalar
725
[947]726  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
727                                           !! regeneration (vernalization) (years)
[1078]728!$OMP THREADPRIVATE(too_long)
[511]729
730
[531]731  !
732  ! lpj_establish.f90
733  !
734
[511]735  ! 1. Scalar
[531]736
[4185]737  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (ind/m2/dt_stomate)
[1078]738!$OMP THREADPRIVATE(estab_max_tree)
[4185]739  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (ind/m2/dt_stomate)
[1078]740!$OMP THREADPRIVATE(estab_max_grass)
[511]741 
742  ! 3. Coefficients of equations
743
[720]744  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
[1078]745!$OMP THREADPRIVATE(establish_scal_fact)
[720]746  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
[1078]747!$OMP THREADPRIVATE(max_tree_coverage)
[720]748  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
[1078]749!$OMP THREADPRIVATE(ind_0_estab)
[511]750
751
[531]752  !
753  ! lpj_fire.f90
754  !
755
[511]756  ! 1. Scalar
757
[720]758  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
[1078]759!$OMP THREADPRIVATE(tau_fire)
[947]760  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
761                                                !! below which iginitions extinguish
762                                                !! @tex $(gC m^{-2})$ @endtex
[1078]763!$OMP THREADPRIVATE(litter_crit)
[720]764  REAL(r_std), SAVE :: fire_resist_struct = 0.5 !!
[1078]765!$OMP THREADPRIVATE(fire_resist_struct)
[511]766  ! 2. Arrays
767
[947]768  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
769       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /)       !! compartments emitted to the atmosphere
[1078]770!$OMP THREADPRIVATE(co2frac)                                                         !! when burned (unitless, 0-1) 
[511]771
772  ! 3. Coefficients of equations
773
[720]774  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
[1078]775!$OMP THREADPRIVATE(bcfrac_coeff)
[720]776  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
[1078]777!$OMP THREADPRIVATE(firefrac_coeff)
[511]778
[531]779  !
780  ! lpj_gap.f90
781  !
[511]782
[531]783  ! 1. Scalar
[511]784
[947]785  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
786                                                 !! @tex $(year^{-1})$ @endtex
[1078]787!$OMP THREADPRIVATE(ref_greff)
[511]788
[531]789  !               
790  ! lpj_light.f90
791  !             
[511]792
793  ! 1. Scalar
794 
[720]795  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
796                                            !! to fpc of last time step (F)? (true/false)
[1078]797!$OMP THREADPRIVATE(annual_increase)
[720]798  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
799                                            !! (due to its branches etc.) (0-1, unitless)
800                                            !! This means that only a small fraction of its crown area
801                                            !! can be invaded by other trees.
[1078]802!$OMP THREADPRIVATE(min_cover)
[531]803  !
804  ! lpj_pftinout.f90
805  !
806
[511]807  ! 1. Scalar
808
[720]809  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
[1078]810!$OMP THREADPRIVATE(min_avail)
[720]811  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
[1078]812!$OMP THREADPRIVATE(ind_0)
[511]813  ! 3. Coefficients of equations
814 
[947]815  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
[1078]816!$OMP THREADPRIVATE(RIP_time_min)
[737]817  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
[1078]818!$OMP THREADPRIVATE(npp_longterm_init)
[720]819  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
[1078]820!$OMP THREADPRIVATE(everywhere_init)
[511]821
822
[531]823  !
824  ! stomate_alloc.f90
825  !
[511]826
[531]827  ! 0. Constants
828
[737]829  REAL(r_std), PARAMETER :: max_possible_lai = 10. !! (m^2.m^{-2})
[720]830  REAL(r_std), PARAMETER :: Nlim_Q10 = 10.         !!
[531]831
[511]832  ! 1. Scalar
833
[720]834  LOGICAL, SAVE :: ok_minres = .TRUE.              !! [DISPENSABLE] Do we try to reach a minimum reservoir even if
835                                                   !! we are severely stressed? (true/false)
[1078]836!$OMP THREADPRIVATE(ok_minres)
[947]837  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
838                                                   !! carbohydrate reserve may be used for
839                                                   !! trees (days)
[1078]840!$OMP THREADPRIVATE(reserve_time_tree)
[947]841  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
842                                                   !! carbohydrate reserve may be used for
843                                                   !! grasses (days)
[1078]844!$OMP THREADPRIVATE(reserve_time_grass)
[947]845
[720]846  REAL(r_std), SAVE :: f_fruit = 0.1               !! Default fruit allocation (0-1, unitless)
[1078]847!$OMP THREADPRIVATE(f_fruit)
[947]848  REAL(r_std), SAVE :: alloc_sap_above_grass = 1.0 !! fraction of sapwood allocation above ground
849                                                   !! for grass (0-1, unitless)
[1078]850!$OMP THREADPRIVATE(alloc_sap_above_grass)
[947]851  REAL(r_std), SAVE :: min_LtoLSR = 0.2            !! Prescribed lower bounds for leaf
852                                                   !! allocation (0-1, unitless)
[1078]853!$OMP THREADPRIVATE(min_LtoLSR)
[947]854  REAL(r_std), SAVE :: max_LtoLSR = 0.5            !! Prescribed upper bounds for leaf
855                                                   !! allocation (0-1, unitless)
[1078]856!$OMP THREADPRIVATE(max_LtoLSR)
[947]857  REAL(r_std), SAVE :: z_nitrogen = 0.2            !! Curvature of the root profile (m)
[1078]858!$OMP THREADPRIVATE(z_nitrogen)
[511]859
860  ! 3. Coefficients of equations
861
[628]862  REAL(r_std), SAVE :: Nlim_tref = 25.             !! (C)
[1078]863!$OMP THREADPRIVATE(Nlim_tref)
[511]864
865
866  !
[531]867  ! stomate_data.f90
[511]868  !
869
[531]870  ! 1. Scalar
871
872  ! 1.1 Parameters for the pipe model
873
[628]874  REAL(r_std), SAVE :: pipe_tune1 = 100.0        !! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory) (unitless)
[1078]875!$OMP THREADPRIVATE(pipe_tune1)
[628]876  REAL(r_std), SAVE :: pipe_tune2 = 40.0         !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
[1078]877!$OMP THREADPRIVATE(pipe_tune2)
[628]878  REAL(r_std), SAVE :: pipe_tune3 = 0.5          !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
[1078]879!$OMP THREADPRIVATE(pipe_tune3)
[628]880  REAL(r_std), SAVE :: pipe_tune4 = 0.3          !! needed for stem diameter (unitless)
[1078]881!$OMP THREADPRIVATE(pipe_tune4)
[620]882  REAL(r_std), SAVE :: pipe_density = 2.e5       !! Density
[1078]883!$OMP THREADPRIVATE(pipe_density)
[620]884  REAL(r_std), SAVE :: pipe_k1 = 8.e3            !! one more SAVE
[1078]885!$OMP THREADPRIVATE(pipe_k1)
[628]886  REAL(r_std), SAVE :: pipe_tune_exp_coeff = 1.6 !! pipe tune exponential coeff (unitless)
[1078]887!$OMP THREADPRIVATE(pipe_tune_exp_coeff)
[531]888
[720]889  ! 1.2 climatic parameters
[511]890
[720]891  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
[1078]892!$OMP THREADPRIVATE(precip_crit)
[720]893  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
[1078]894!$OMP THREADPRIVATE(gdd_crit_estab)
[720]895  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
[1078]896!$OMP THREADPRIVATE(fpc_crit)
[531]897
[511]898  ! 1.3 sapling characteristics
899
[720]900  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
[1078]901!$OMP THREADPRIVATE(alpha_grass)
[720]902  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
[1078]903!$OMP THREADPRIVATE(alpha_tree)
[628]904  REAL(r_std), SAVE :: mass_ratio_heart_sap = 3. !! mass ratio (heartwood+sapwood)/sapwood (unitless)
[1078]905!$OMP THREADPRIVATE(mass_ratio_heart_sap)
[531]906
[511]907  ! 1.4  time scales for phenology and other processes (in days)
908
[628]909  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
[1078]910!$OMP THREADPRIVATE(tau_hum_month)
[628]911  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
[1078]912!$OMP THREADPRIVATE(tau_hum_week)
[628]913  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
[1078]914!$OMP THREADPRIVATE(tau_t2m_month)
[628]915  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
[1078]916!$OMP THREADPRIVATE(tau_t2m_week)
[628]917  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
[1078]918!$OMP THREADPRIVATE(tau_tsoil_month)
[628]919  REAL(r_std), SAVE :: tau_soilhum_month = 20.    !! (days)     
[1078]920!$OMP THREADPRIVATE(tau_soilhum_month)
[628]921  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
[1078]922!$OMP THREADPRIVATE(tau_gpp_week)
[628]923  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
[1078]924!$OMP THREADPRIVATE(tau_gdd)
[628]925  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
[1078]926!$OMP THREADPRIVATE(tau_ngd)
[628]927  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
[1078]928!$OMP THREADPRIVATE(coeff_tau_longterm)
[2441]929  REAL(r_std), SAVE :: tau_longterm_max           !! (days) 
930!$OMP THREADPRIVATE(tau_longterm_max)
[531]931
[511]932  ! 3. Coefficients of equations
933
[720]934  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
[1078]935!$OMP THREADPRIVATE(bm_sapl_carbres)
[720]936  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
[1078]937!$OMP THREADPRIVATE(bm_sapl_sapabove)
[720]938  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
[1078]939!$OMP THREADPRIVATE(bm_sapl_heartabove)
[720]940  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
[1078]941!$OMP THREADPRIVATE(bm_sapl_heartbelow)
[720]942  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
[1078]943!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
[720]944  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
[1078]945!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
[720]946  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
[1078]947!$OMP THREADPRIVATE(init_sapl_mass_carbres)
[720]948  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
[1078]949!$OMP THREADPRIVATE(init_sapl_mass_root)
[720]950  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
[1078]951!$OMP THREADPRIVATE(init_sapl_mass_fruit)
[720]952  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
[1078]953!$OMP THREADPRIVATE(cn_sapl_init)
[720]954  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
[1078]955!$OMP THREADPRIVATE(migrate_tree)
[720]956  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
[1078]957!$OMP THREADPRIVATE(migrate_grass)
[720]958  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
[1078]959!$OMP THREADPRIVATE(lai_initmin_tree)
[720]960  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
[1078]961!$OMP THREADPRIVATE(lai_initmin_grass)
[720]962  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
[1078]963!$OMP THREADPRIVATE(dia_coeff)
[720]964  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
[1078]965!$OMP THREADPRIVATE(maxdia_coeff)
[720]966  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
[1078]967!$OMP THREADPRIVATE(bm_sapl_leaf)
[511]968
969
970
[531]971  !
972  ! stomate_litter.f90
973  !
[511]974
[531]975  ! 0. Constants
[511]976
[720]977  REAL(r_std), PARAMETER :: Q10 = 10.               !!
[531]978
[511]979  ! 1. Scalar
980
[720]981  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
[1078]982!$OMP THREADPRIVATE(z_decomp)
[511]983
984  ! 2. Arrays
985
[720]986  REAL(r_std), SAVE :: frac_soil_struct_aa = 0.55   !! corresponding to frac_soil(istructural,iactive,iabove)
[1078]987!$OMP THREADPRIVATE(frac_soil_struct_aa)
[720]988  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
[1078]989!$OMP THREADPRIVATE(frac_soil_struct_ab)
[720]990  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
[1078]991!$OMP THREADPRIVATE(frac_soil_struct_sa)
[720]992  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
[1078]993!$OMP THREADPRIVATE(frac_soil_struct_sb)
[720]994  REAL(r_std), SAVE :: frac_soil_metab_aa = 0.45    !! corresponding to frac_soil(imetabolic,iactive,iabove)
[1078]995!$OMP THREADPRIVATE(frac_soil_metab_aa)
[720]996  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
[1078]997!$OMP THREADPRIVATE(frac_soil_metab_ab)
[947]998  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = &    !! C/N ratio of each plant pool (0-100, unitless)
[539]999       & (/ 40., 40., 40., 40., 40., 40., 40., 40. /) 
[1078]1000!$OMP THREADPRIVATE(CN)
[947]1001  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = &    !! Lignin/C ratio of different plant parts (0,22-0,35, unitless)
[531]1002       & (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /)
[1078]1003!$OMP THREADPRIVATE(LC)
[511]1004
1005  ! 3. Coefficients of equations
1006
[720]1007  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
[1078]1008!$OMP THREADPRIVATE(metabolic_ref_frac)
[720]1009  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
[1078]1010!$OMP THREADPRIVATE(metabolic_LN_ratio)
[720]1011  REAL(r_std), SAVE :: tau_metabolic = 0.066        !!
[1078]1012!$OMP THREADPRIVATE(tau_metabolic)
[720]1013  REAL(r_std), SAVE :: tau_struct = 0.245           !!
[1078]1014!$OMP THREADPRIVATE(tau_struct)
[720]1015  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
[1078]1016!$OMP THREADPRIVATE(soil_Q10)
[720]1017  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
[1078]1018!$OMP THREADPRIVATE(tsoil_ref)
[720]1019  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
[1078]1020!$OMP THREADPRIVATE(litter_struct_coef)
[720]1021  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
[1078]1022!$OMP THREADPRIVATE(moist_coeff)
[2282]1023  REAL(r_std), SAVE :: moistcont_min = 0.25  !! minimum soil wetness to limit the heterotrophic respiration
1024!$OMP THREADPRIVATE(moistcont_min)
[511]1025
[8462]1026  ! 4. Moyano et la. 2012 Biogeosciences
[511]1027
[8462]1028  LOGICAL, SAVE :: ok_moyano_soilhumsat = .FALSE.  !! Use soilhumSAT and Moyano formulation for control_moist
1029!$OMP THREADPRIVATE(ok_moyano_soilhumsat)
1030  LOGICAL, SAVE :: ok_orga = .TRUE.                !! Do we use also the equation designed for organic soils by Moyano et al.
1031                                                   !! for control_moist
1032!$OMP THREADPRIVATE(ok_orga)
1033  REAL(r_std), SAVE :: beta1 = -0.26               !! 1st(Beta1*M) term of Moyano' PRSR model 2
1034                                                   !! for fraction of saturation Beta1= [-0.28,-0.24]
1035!$OMP THREADPRIVATE(beta1)
1036  REAL(r_std), SAVE :: beta2 = 0.32                !! 2nd(Beta2*M^2) term of Moyano' PRSR model 2
1037                                                   !! for fraction of saturation Beta2= [0.28,0.36]
1038!$OMP THREADPRIVATE(beta2)
1039  REAL(r_std), SAVE :: beta3 = -0.15               !! 3rd(Beta3*M^3) term of Moyano' PRSR model 2
1040                                                   !! for fraction of saturation Beta3= [-0.18,-0.12]
1041!$OMP THREADPRIVATE(beta3)
1042  REAL(r_std), SAVE :: beta1_orga = -0.67          !! 1st(Beta1*M) term of Moyano' PRSR model 3
1043                                                   !! for fraction of saturation Beta1= [-0.65,-0.69]
1044!$OMP THREADPRIVATE(beta1_orga)
1045  REAL(r_std), SAVE :: beta2_orga = 1.08           !! 2nd(Beta2*M^2) term of Moyano' PRSR model 3
1046                                                   !! for fraction of saturation Beta2= [1.03,1.13]
1047!$OMP THREADPRIVATE(beta2_orga)
1048  REAL(r_std), SAVE :: beta3_orga = -0.57          !! 3rd(Beta3*M^3) term of Moyano' PRSR model 3
1049                                                   !! for fraction of saturation Beta3= [-0.54,-0.60]
1050!$OMP THREADPRIVATE(beta3_orga)
1051  REAL(r_std), SAVE :: beta4 = 0.08                !! 4th(Beta4*clay) term of Moyano' PRSR model 2
1052                                                   !! for fraction of saturation Beta4= [0.07,0.09]
1053!$OMP THREADPRIVATE(beta4)
1054  REAL(r_std), SAVE :: beta5 = -0.09               !! 5th(Beta5*M*clay) term of Moyano' PRSR model 2
1055                                                   !! for fraction of saturation Beta5= [-0.10,-0.08]
1056!$OMP THREADPRIVATE(beta5)
1057  REAL(r_std), SAVE :: beta6 = 0.57                !! 6th(Beta6*SOC) term of Moyano' PRSR model 2
1058                                                   !! for fraction of saturation Beta6= [0.53,0.61]
1059!$OMP THREADPRIVATE(beta6)
1060  REAL(r_std), SAVE :: intercept = 1.059           !! intercept term of Moyano' PRSR model 2
1061                                                   !! for fraction of saturation intercept= [1.056,1.062]
1062!$OMP THREADPRIVATE(intercept)
1063  REAL(r_std), SAVE :: intercept_orga = 1.134      !! intercept term of Moyano' PRSR model 3
1064                                                   !! for fraction of saturation intercept= [1.131,1.137]
1065!$OMP THREADPRIVATE(intercept_orga)
1066  REAL(r_std), SAVE :: SRo = 1.0                   !! Initial respiration value (SR0) arbitrary defined at 1.0
1067!$OMP THREADPRIVATE(SRo)
1068  REAL(r_std), SAVE :: moistcontSAT_min = 0.0      !! minimum soil wetness to limit the heterotrophic respiration
1069!$OMP THREADPRIVATE(moistcontSAT_min)
1070  REAL(r_std), SAVE :: soilheight = 0.10           !! soil height in meter to converte totalSOC
1071                                                   !! from gC/m2soil to gC/gsoil [0.10, 0.20, 0.30, 0.50, 1m]
1072!$OMP THREADPRIVATE(soilheight)
1073  REAL(r_std), SAVE :: Cini_Moyano = 1000_r_std !!Initial carbon content for Moyano equation  (kgC/m3)
1074!$OMP THREADPRIVATE(Cini_Moyano)
1075  REAL(r_std), SAVE :: Litterini_Moyano = 1000_r_std !!Initial litter carbon content for Moyano equation  (kgC/m3)
1076!$OMP THREADPRIVATE(Litterini_Moyano)
1077  REAL(r_std), SAVE :: min_carbon_moyano = 0.01   !! Minimum carbon concentration in the database
1078                                                  !! used by Moyano et al (gC/gSoil)
1079!$OMP THREADPRIVATE(min_carbon_moyano)
1080  REAL(r_std), SAVE :: max_carbon_moyano = 0.35   !! Maximum carbon concentration in the database
1081                                                  !! used by Moyano et al (gC/gSoil)
1082!$OMP THREADPRIVATE(max_carbon_moyano)
1083  REAL(r_std), SAVE :: limit_carbon_orga = 0.06   !! Minimum carbon concentration in the database
1084                                                  !! for organic soil used by Moyano et al (gC/gSoil)
1085!$OMP THREADPRIVATE(limit_carbon_orga)
1086  REAL(r_std), SAVE :: min_clay_moyano = 0.03     !! Minimum clay fraction in the database used by Moyano et al (unitless)
1087!$OMP THREADPRIVATE(min_clay_moyano)
1088  REAL(r_std), SAVE :: max_clay_moyano = 0.58     !! Maximum clay fraction in the database used by Moyano et al (unitless)
1089!$OMP THREADPRIVATE(max_clay_moyano)
[531]1090  !
1091  ! stomate_lpj.f90
1092  !
[511]1093
1094  ! 1. Scalar
1095
[720]1096  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
[1078]1097!$OMP THREADPRIVATE(frac_turnover_daily)
[511]1098
1099
[531]1100  !
1101  ! stomate_npp.f90
1102  !
1103
[511]1104  ! 1. Scalar
1105
[947]1106  REAL(r_std), SAVE :: tax_max = 0.8 !! Maximum fraction of allocatable biomass used
[720]1107                                     !! for maintenance respiration (0-1, unitless)
[1078]1108!$OMP THREADPRIVATE(tax_max)
[511]1109
1110
[531]1111  !
1112  ! stomate_phenology.f90
1113  !
[511]1114
1115  ! 1. Scalar
1116
[720]1117  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
[1078]1118!$OMP THREADPRIVATE(min_growthinit_time)
[947]1119  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
1120                                                   !!  - for trees (0-1, unitless)
[1078]1121!$OMP THREADPRIVATE(moiavail_always_tree)
[947]1122  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1123                                                   !! - for grass (0-1, unitless)
[1078]1124!$OMP THREADPRIVATE(moiavail_always_grass)
[620]1125  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
[1078]1126!$OMP THREADPRIVATE(t_always)
[720]1127  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
[1078]1128!$OMP THREADPRIVATE(t_always_add)
[511]1129
1130  ! 3. Coefficients of equations
1131 
[720]1132  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
[1078]1133!$OMP THREADPRIVATE(gddncd_ref)
[720]1134  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
[1078]1135!$OMP THREADPRIVATE(gddncd_curve)
[720]1136  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
[1078]1137!$OMP THREADPRIVATE(gddncd_offset)
[511]1138
1139
[531]1140  !
1141  ! stomate_prescribe.f90
1142  !
[511]1143
1144  ! 3. Coefficients of equations
1145
[720]1146  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
[1078]1147!$OMP THREADPRIVATE(bm_sapl_rescale)
[511]1148
1149
[531]1150  !
1151  ! stomate_resp.f90
1152  !
[511]1153
1154  ! 3. Coefficients of equations
1155
[720]1156  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
[1078]1157!$OMP THREADPRIVATE(maint_resp_min_vmax)
[720]1158  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
[1078]1159!$OMP THREADPRIVATE(maint_resp_coeff)
[511]1160
1161
[531]1162  !
1163  ! stomate_soilcarbon.f90
1164  !
[511]1165
1166  ! 2. Arrays
1167
[531]1168  ! 2.1 frac_carb_coefficients
[511]1169
[720]1170  REAL(r_std), SAVE :: frac_carb_ap = 0.004  !! from active pool: depends on clay content  (0-1, unitless)
1171                                             !! corresponding to frac_carb(:,iactive,ipassive)
[1078]1172!$OMP THREADPRIVATE(frac_carb_ap)
[720]1173  REAL(r_std), SAVE :: frac_carb_sa = 0.42   !! from slow pool (0-1, unitless)
1174                                             !! corresponding to frac_carb(:,islow,iactive)
[1078]1175!$OMP THREADPRIVATE(frac_carb_sa)
[720]1176  REAL(r_std), SAVE :: frac_carb_sp = 0.03   !! from slow pool (0-1, unitless)
1177                                             !! corresponding to frac_carb(:,islow,ipassive)
[1078]1178!$OMP THREADPRIVATE(frac_carb_sp)
[720]1179  REAL(r_std), SAVE :: frac_carb_pa = 0.45   !! from passive pool (0-1, unitless)
1180                                             !! corresponding to frac_carb(:,ipassive,iactive)
[1078]1181!$OMP THREADPRIVATE(frac_carb_pa)
[720]1182  REAL(r_std), SAVE :: frac_carb_ps = 0.0    !! from passive pool (0-1, unitless)
1183                                             !! corresponding to frac_carb(:,ipassive,islow)
[1078]1184!$OMP THREADPRIVATE(frac_carb_ps)
[511]1185
1186  ! 3. Coefficients of equations
1187
[720]1188  REAL(r_std), SAVE :: active_to_pass_clay_frac = 0.68  !! (0-1, unitless)
[1078]1189!$OMP THREADPRIVATE(active_to_pass_clay_frac)
[620]1190  !! residence times in carbon pools (days)
1191  REAL(r_std), SAVE :: carbon_tau_iactive = 0.149   !! residence times in active pool (days)
[1078]1192!$OMP THREADPRIVATE(carbon_tau_iactive)
[4962]1193  REAL(r_std), SAVE :: carbon_tau_islow = 7.0       !! residence times in slow pool (days)
[1078]1194!$OMP THREADPRIVATE(carbon_tau_islow)
[4962]1195  REAL(r_std), SAVE :: carbon_tau_ipassive = 300.   !! residence times in passive pool (days)
[1078]1196!$OMP THREADPRIVATE(carbon_tau_ipassive)
[511]1197  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
[1078]1198!$OMP THREADPRIVATE(flux_tot_coeff)
[511]1199
[531]1200  !
1201  ! stomate_turnover.f90
1202  !
[511]1203
[720]1204  ! 3. Coefficients of equations
[511]1205
[628]1206  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
[1078]1207!$OMP THREADPRIVATE(new_turnover_time_ref)
[720]1208  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
[1078]1209!$OMP THREADPRIVATE(leaf_age_crit_tref)
[720]1210  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
[1078]1211!$OMP THREADPRIVATE(leaf_age_crit_coeff)
[511]1212
1213
[531]1214  !
1215  ! stomate_vmax.f90
1216  !
1217 
[511]1218  ! 1. Scalar
1219
[947]1220  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
[1078]1221!$OMP THREADPRIVATE(vmax_offset)
[947]1222  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1223                                                !! reaches 1 (unitless)
[1078]1224!$OMP THREADPRIVATE(leafage_firstmax)
[947]1225  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1226                                                !! falls below 1 (unitless)
[1078]1227!$OMP THREADPRIVATE(leafage_lastmax)
[947]1228  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1229                                                !! reaches its minimum (vmax_offset)
1230                                                !! (unitless)
[1078]1231!$OMP THREADPRIVATE(leafage_old)
[531]1232  !
1233  ! stomate_season.f90
1234  !
[511]1235
1236  ! 1. Scalar
1237
[947]1238  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
[1078]1239!$OMP THREADPRIVATE(gppfrac_dormance)
[720]1240  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
[1078]1241!$OMP THREADPRIVATE(tau_climatology)
[720]1242  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
[1078]1243!$OMP THREADPRIVATE(hvc1)
[720]1244  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
[1078]1245!$OMP THREADPRIVATE(hvc2)
[947]1246  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
[1078]1247!$OMP THREADPRIVATE(leaf_frac_hvc)
[620]1248  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
[1078]1249!$OMP THREADPRIVATE(tlong_ref_max)
[620]1250  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
[1078]1251!$OMP THREADPRIVATE(tlong_ref_min)
[511]1252
1253  ! 3. Coefficients of equations
1254
[531]1255  REAL(r_std), SAVE :: ncd_max_year = 3.
[1078]1256!$OMP THREADPRIVATE(ncd_max_year)
[531]1257  REAL(r_std), SAVE :: gdd_threshold = 5.
[1078]1258!$OMP THREADPRIVATE(gdd_threshold)
[531]1259  REAL(r_std), SAVE :: green_age_ever = 2.
[1078]1260!$OMP THREADPRIVATE(green_age_ever)
[531]1261  REAL(r_std), SAVE :: green_age_dec = 0.5
[1078]1262!$OMP THREADPRIVATE(green_age_dec)
[511]1263
[1475]1264END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.