source: branches/publications/ORCHIDEE-MICT-OP-r6850/src_parameters/constantes_var.f90 @ 7746

Last change on this file since 7746 was 6849, checked in by yidi.xu, 4 years ago

ORCHIDEE-MICT-OP for oil palm growth modelling

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