source: branches/publications/ORCHIDEE_CN_CAN_r5698/src_parameters/constantes_var.f90 @ 7346

Last change on this file since 7346 was 5696, checked in by sebastiaan.luyssaert, 5 years ago

DEV: tested for 16 years on a single pixel with LCC maps. The changes fix the mass balance problem in spaiens_lcchange reported in ticket #482. Added additional code to speed-up debugging of future mass balance problems in sapiens_lcchange.

  • Property svn:keywords set to Date Revision
File size: 111.7 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_var
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        constantes_var module contains most constantes like pi, Earth radius, etc...
10!!              and all externalized parameters except pft-dependent constants.
11!!
12!!\n DESCRIPTION: This module contains most constantes and the externalized parameters of ORCHIDEE which
13!!                are not pft-dependent.\n
14!!                In this module, you can set the flag diag_qsat in order to detect the pixel where the
15!!                temperature is out of range (look qsatcalc and dev_qsatcalc in qsat_moisture.f90).\n
16!!                The Earth radius is approximated by the Equatorial radius.The Earth's equatorial radius a,
17!!                or semi-major axis, is the distance from its center to the equator and equals 6,378.1370 km.
18!!                The equatorial radius is often used to compare Earth with other planets.\n
19!!                The meridional mean is well approximated by the semicubic mean of the two axe yielding
20!!                6367.4491 km or less accurately by the quadratic mean of the two axes about 6,367.454 km
21!!                or even just the mean of the two axes about 6,367.445 km.\n
22!!                This module is already USE in module constantes. Therefor no need to USE it seperatly except
23!!                if the subroutines in module constantes are not needed.\n
24!!               
25!! RECENT CHANGE(S):
26!!
27!! REFERENCE(S) :
28!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
29!! Boundary Layer Meteorology, 187-202.\n
30!!
31!! SVN          :
32!! $HeadURL: $
33!! $Date$
34!! $Revision$
35!! \n
36!_ ================================================================================================================================
37
38MODULE constantes_var
39
40  USE defprec
41
42  IMPLICIT NONE
43!-
44
45                         !-----------------------!
46                         !  ORCHIDEE CONSTANTS   !
47                         !-----------------------!
48
49  !
50  ! FLAGS
51  !
52  LOGICAL :: river_routing      !! activate river routing
53!$OMP THREADPRIVATE(river_routing)
54  LOGICAL :: do_floodplains     !! activate flood plains
55!$OMP THREADPRIVATE(do_floodplains)
56  LOGICAL :: do_irrigation      !! activate computation of irrigation flux
57!$OMP THREADPRIVATE(do_irrigation)
58  LOGICAL :: ok_sechiba         !! activate physic of the model
59!$OMP THREADPRIVATE(ok_sechiba)
60  LOGICAL :: ok_stomate         !! activate carbon cycle
61!$OMP THREADPRIVATE(ok_stomate)
62  LOGICAL :: ok_ncycle          !! activate nitrogen cycle
63!$OMP THREADPRIVATE(ok_ncycle)
64  LOGICAL :: impose_cn          !! impose the CN ratio of leaves
65!$OMP THREADPRIVATE(impose_cn)
66  LOGICAL :: ok_dgvm            !! activate dynamic vegetation
67!$OMP THREADPRIVATE(ok_dgvm)
68  LOGICAL :: ok_pheno           !! activate the calculation of lai using stomate rather than a prescription
69!$OMP THREADPRIVATE(ok_pheno)
70  LOGICAL :: ok_bvoc            !! activate biogenic volatile organic coumpounds
71!$OMP THREADPRIVATE(ok_bvoc)
72  LOGICAL :: ok_leafage         !! activate leafage
73!$OMP THREADPRIVATE(ok_leafage)
74  LOGICAL :: ok_radcanopy       !! use canopy radiative transfer model
75!$OMP THREADPRIVATE(ok_radcanopy)
76  LOGICAL :: ok_multilayer      !! use canopy radiative transfer model with multi-layers (BVOCs)
77!$OMP THREADPRIVATE(ok_multilayer)
78  LOGICAL :: ok_pulse_NOx       !! calculate NOx emissions with pulse
79!$OMP THREADPRIVATE(ok_pulse_NOx)
80  LOGICAL :: ok_bbgfertil_NOx   !! calculate NOx emissions with bbg fertilizing effect
81!$OMP THREADPRIVATE(ok_bbgfertil_NOx)
82  LOGICAL :: ok_cropsfertil_NOx !! calculate NOx emissions with fertilizers use
83!$OMP THREADPRIVATE(ok_cropsfertil_NOx)
84
85  LOGICAL :: ok_co2bvoc_poss    !! CO2 inhibition on isoprene activated following Possell et al. (2005) model
86!$OMP THREADPRIVATE(ok_co2bvoc_poss)
87  LOGICAL :: ok_co2bvoc_wilk    !! CO2 inhibition on isoprene activated following Wilkinson et al. (2006) model
88!$OMP THREADPRIVATE(ok_co2bvoc_wilk)
89  INTEGER       :: multi_layer_control                        !! Flag that automatically controls several other flags related to
90                                                              !! multi-layering (1/2/3).
91                                                              !! 1 - single layer: ok_hydrol_arch, ok_gs_feedback, ok_impose_canopy_structure
92                                                              !! and ok_mleb all true, but the energy budget is only calculated for a single layer
93                                                              !! (jnlvls=1,jnlvls_under=0,jnlvls_canopy=1,jnlvls_over=0).
94                                                              !! 2 - multi-layer: ok_hydrol_arch, ok_gs_feedback,  ok_impose_canopy_structure,
95                                                              !! ok_mleb all true, and the energy budget is calculated for multiple layers
96                                                              !! (jnlvls=29,jnlvls_under=10,jnlvls_canopy=10,jnlvls_over=9).   
97                                                              !! 3 - user specific: user specific settings for these controls
98                                                              !! and layers as defined in the run.def by the user.
99!$OMP THREADPRIVATE(multi_layer_control)
100  LOGICAL       :: ok_hydrol_arch                             !! Flag that activates the hydraulic architecture routine (true/false)
101                                                              !! The trunk version of ORCHIDEE (false) uses soil water as a
102                                                              !! proxy for water stress and applies the stress to Vcmax.
103                                                              !! When set to true the hydraulic architecture of the vegetation
104                                                              !! is accounted for to calculate the amount of water that
105                                                              !! can be transported through the plant given the soil and leaf
106                                                              !! potential and the conductivities of the roots, wood and
107                                                              !! leaves. Water supply through the plant is compared against
108                                                              !! the atmospheric demand for water. If the supply is smaller
109                                                              !! then the demand, the plant experiences water stress and the
110                                                              !! stomata will be closed (water stress is now on gs rather
111                                                              !! than Vcmax). Note that whether stomatal regulation is used or
112                                                              !! not is controled by a separate flag: ok_gs_feedback.
113!$OMP THREADPRIVATE(ok_hydrol_arch)
114
115  LOGICAL       :: ok_gs_feedback                             !! Flag that activates water stress on stomata (true/false)
116                                                              !! This flag is for debugging only! It allows developers
117                                                              !! to calculate GPP without any water stress. If the model is
118                                                              !! used in production mode and ok_hydrol_arch is true this
119                                                              !! flag should be true as well.
120!$OMP THREADPRIVATE(ok_gs_feedback)   
121  LOGICAL       :: ok_mleb                                    !! Flag that activates the multilayer energy budget (true/false)
122                                                              !! The model uses 10 (default) canopy layers to calculate
123                                                              !! the albedo, transmittance, absorbance and GPP. These canopy
124                                                              !! layers can be combined with 10 (default) layers below and
125                                                              !! 10 layers above the canopy to calculate the energy budget
126                                                              !! (ok_mleb=y). If set to no, this flag will make the model
127                                                              !! use 10 layers for the canopy albedo, transmittance,
128                                                              !! absorbance and GPP and just a single layer for the energy
129                                                              !! budget. Be aware that if you wish to run with hydraulic
130                                                              !! architechture ok_mleb needs to be se to true as well. Furthermore
131                                                              !! if you  wish to run with the original energy scheme (enerbil),
132                                                              !! set the layers for mleb to 1.
133!$OMP THREADPRIVATE(ok_mleb)
134  LOGICAL       :: ok_impose_can_structure                    !! This flag is for debugging only! It allows developers
135                                                              !! to use a prescribed canopy structure rather then the
136                                                              !! structure calculate by ORCHIDEE. The flag activates the
137                                                              !! sections of code which directly link the energy budget
138                                                              !! scheme to the the size and LAI profile of the canopy for the
139                                                              !! respective PFT and age class that is calculated in stomate,
140                                                              !! for the albedo. If set to TRUE and the multi-layer budget
141                                                              !! is activated the model takes LAI profile information and
142                                                              !! canopy level heights from the run.def. If set to FALSE, and
143                                                              !! the multi-layer energy budget is used the profile
144                                                              !! information and canopy levels heights comes from the
145                                                              !! PGap-based processes for calculation of stand profile
146                                                              !! information in stomate.
147!$OMP THREADPRIVATE(ok_impose_can_structure)
148  LOGICAL       :: ok_mleb_history_file                       !! Flag that controls the writing of an output file with the
149                                                              !! multi-layer energy simulations (true/false). Note that this
150                                                              !! is a large file and writing it slows down the code.
151!$OMP THREADPRIVATE(ok_mleb_history_file)
152  LOGICAL, SAVE :: ok_read_fm_map = .FALSE.                   !! A logical flag determining if we read
153                                                              !! in the forest management strategy from a map.
154                                                              !! This should be .TRUE. for all applications
155                                                              !! except for debugging and pixel-level simulations.
156!$OMP THREADPRIVATE(ok_read_fm_map)
157  LOGICAL, SAVE :: ok_change_species = .FALSE.                !! A logical flag determining if we change
158                                                              !! species after a clearcut
159!$OMP THREADPRIVATE(ok_change_species)
160  LOGICAL, SAVE :: ok_read_species_change_map = .FALSE.       !! A logical flag determining if we read
161                                                              !! in a map which changes species after a clearcut
162                                                              !! To be used with ok_change_species = .TRUE. or
163                                                              !! set species_change_force (see below)
164!$OMP THREADPRIVATE(ok_read_species_change_map)
165  LOGICAL, SAVE :: ok_read_desired_fm_map = .FALSE.           !! A logical flag determining if we read
166                                                              !! in the desired forest management strategy from a map.
167                                                              !! To be used with ok_change_species = .TRUE. or set
168                                                              !! fm_change_force (see below)
169!$OMP THREADPRIVATE(ok_read_desired_fm_map)
170  LOGICAL, SAVE :: ok_litter_raking = .FALSE.                 !! If TRUE, this flag will simulate litter raking in
171                                                              !! in grid squares.  This has the effect of moving litter
172                                                              !! once a year from forest PFTs to agricultural PFTs, if they
173                                                              !! are present on this pixel.  If TRUE, you must also provide
174                                                              !! a map with the litter demand so we know how much litter
175                                                              !! to remove for each pixel. Litter raking is a historical
176                                                              !! land use so you reconstrauctions to use this option.
177!$OMP THREADPRIVATE(ok_litter_raking)
178 
179  LOGICAL       :: ok_dimensional_product_use = .TRUE.        !! Once the wood is harvested it ends up in wood product pools
180                                                              !! Two options were coded: (1) the product use and thus
181                                                              !! its on longevity depends on the dimensions of the harvest
182                                                              !! (2) the dimensions are ignored and the wood is used according
183                                                              !! to fixed ratios.
184 
185!$OMP THREADPRIVATE(ok_dimensional_product_use)
186
187  LOGICAL       :: ok_constant_mortality                      !! Use constant mortality or calculate mortality
188                                                              !! as a function of last yearsÂŽs NPP
189!$OMP THREADPRIVATE(ok_constant_mortality)
190
191  LOGICAL, SAVE :: ok_c13                                     !! Activate carbon isotope concetration of biomass
192!$OMP THREADPRIVATE(ok_c13)
193
194  LOGICAL :: ok_recruitment                                   !! Activate the recruitment module. Note that recruitment has
195                                                              !! a double control. When this flag is .TRUE. recruitment will
196                                                              !! only be simulated for those PFTs for which ::recruitment_pft
197                                                              !! is set to .TRUE. The ::ok_recruitment flag is convenient for
198                                                              !! debugging and testing but it is redundant and can be removed
199!$OMP THREADPRIVATE(ok_recruitment)
200
201  LOGICAL, SAVE :: ok_windthrow = .FALSE.                     !! Activate the wind throw module. Trees will be killed
202                                                              !! if the wind speed exceeds the critical wind speed of
203                                                              !! of the forest (PFT).                             
204!$OMP THREADPRIVATE(ok_windthrow)
205 
206  LOGICAL, SAVE :: ok_bare_soil_new = .FALSE.                 !! Choose between the two options to calculate the bare soil.
207                                                              !! False = classic view: gaps within a canopy should be treated
208                                                              !! bare soil. True = ecological view: gaps within a canopy are
209                                                              !! part of the ecosystem and should be treated as such.
210!$OMP THREADPRIVATE(ok_bare_soil_new)
211
212
213
214  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE.                    !! ORCHIDEE detects if it is coupled with a GCM or
215                                                              !! just use with one driver in OFF-LINE. (true/false)
216!$OMP THREADPRIVATE(OFF_LINE_MODE) 
217  LOGICAL, SAVE :: impose_param = .TRUE.                      !! Flag impos_param : read all the parameters in the run.def file
218!$OMP THREADPRIVATE(impose_param)
219  CHARACTER(LEN=80), SAVE :: restname_in = 'NONE'             !! Input Restart files name for Sechiba component 
220!$OMP THREADPRIVATE(restname_in)
221  CHARACTER(LEN=80), SAVE :: restname_out = 'sechiba_rest_out.nc'  !! Output Restart files name for Sechiba component
222!$OMP THREADPRIVATE(restname_out)
223  CHARACTER(LEN=80), SAVE :: stom_restname_in = 'NONE'        !! Input Restart files name for Stomate component
224!$OMP THREADPRIVATE(stom_restname_in)
225  CHARACTER(LEN=80), SAVE :: stom_restname_out = 'stomate_rest_out.nc'  !! Output Restart files name for Stomate component
226!$OMP THREADPRIVATE(stom_restname_out)
227  INTEGER, SAVE :: printlev=2                                 !! Standard level for text output [0, 1, 2, 3]
228!$OMP THREADPRIVATE(printlev)
229  INTEGER, SAVE :: printlev_loc=1                             !! local level for text output [0, 1, 2, 3]
230!$OMP THREADPRIVATE(printlev_loc)
231  !
232  ! HACKS
233  !
234  LOGICAL, SAVE :: hack_enerbil_hydrol = .TRUE.!! For debugging only! Flag to skip a particular block of code in enerbil.f90 which results in
235                                               !! incorrect results for large scale simulations.
236!$OMP THREADPRIVATE(hack_enerbil_hydrol)
237  LOGICAL, SAVE :: hack_lcc = .TRUE.           !! Set to .TRUE. if you want the code to keep running past
238                                               !! a few places in land cover change where it would ordinarily
239                                               !! stop.  Only use in very specific cases!
240!$OMP THREADPRIVATE(hack_lcc)
241  LOGICAL, SAVE :: hack_circ_class = .TRUE.    !! Set to true for a temporary patch of a known bug, though the underlying
242!$OMP THREADPRIVATE(hack_circ_class)
243  REAL(r_std), SAVE :: min_n = 0.00001         !! Minimum allowable n_mineralisation when truncating som_input_total(:,initrogen) in stomate_litter.
244!$OMP THREADPRIVATE(min_n)
245  REAL(r_std), SAVE :: max_cn = 250            !! Maximum allowable ratio of som_input_total(:,icarbon) to som_input_total(:,initrogen).
246!$OMP THREADPRIVATE(max_cn)
247
248  !
249  ! TIME
250  !
251  REAL(r_std), SAVE :: one_day  !! One day in seconds (s)
252!$OMP THREADPRIVATE(one_day)
253  REAL(r_std), SAVE :: one_year !! One year in days
254!$OMP THREADPRIVATE(one_year)
255  REAL(r_std), PARAMETER :: one_hour = 3600.0  !! One hour in seconds (s)
256  INTEGER(i_std), PARAMETER  :: spring_days_max = 40  !! Maximum number of days during which we watch for possible spring frost damage
257
258  ! TIME STEP
259  REAL(r_std)            :: dt_sechiba         !! Time step in sechiba
260!$OMP THREADPRIVATE(dt_sechiba)
261  REAL(r_std)            :: dt_stomate         !! Time step in stomate
262!$OMP THREADPRIVATE(dt_stomate)
263
264  !
265  ! SPECIAL VALUES
266  !
267  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
268  !-
269  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
270!$OMP THREADPRIVATE(val_exp)
271  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
272 
273  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
274  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
275 
276  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
277  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
278
279  !
280  ! DIFFERENCE TESTS
281  !
282  INTEGER(i_std), PARAMETER :: istart = 1        !! Index to store values at the start
283  INTEGER(i_std), PARAMETER :: iend = 2          !! Index to store values at the end
284
285  !
286  !  DIMENSIONING AND INDICES PARAMETERS 
287  !
288  INTEGER(i_std), PARAMETER :: ibare_sechiba = 1 !! Index for bare soil in Sechiba (unitless)
289  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for albedo in visible range (unitless)
290  INTEGER(i_std), PARAMETER :: inir = 2          !! index for albeod i near-infrared range (unitless)
291  INTEGER(i_std), PARAMETER :: n_spectralbands=2 !! number of spectral bands
292  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
293  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
294  !-
295  !! Soil
296  INTEGER(i_std), PARAMETER :: classnb = 9       !! Levels of soil colour classification (unitless)
297  !-
298  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
299  !-
300  !! litter fractions: indices (unitless)
301  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
302  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
303  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
304  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
305  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
306  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
307  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
308  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
309  INTEGER(i_std), PARAMETER :: ilabile = 9       !! Index for reserve compartment (unitless)
310  INTEGER(i_std), PARAMETER :: nparts = 9        !! Number of biomass compartments (unitless)
311  !-
312  !! indices for assimilation parameters
313  INTEGER(i_std), PARAMETER :: ivcmax = 1        !! Index for vcmax (assimilation parameters) (unitless)
314  INTEGER(i_std), PARAMETER :: inue = 2          !! Index for nue (assimilationbn parameters) (unitless)
315  INTEGER(i_std), PARAMETER :: ileafN = 3        !! Index for leaf N (assimilationbn parameters) (unitless)
316  INTEGER(i_std), PARAMETER :: npco2 = 3         !! Number of assimilation parameters (unitless)
317  !-
318  !! trees and litter: indices for the parts of heart-
319  !! and sapwood above and below the ground
320  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
321  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
322  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
323  !-
324  !! litter: indices for metabolic and structural part
325  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
326  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
327  INTEGER(i_std), PARAMETER :: iwoody = 3       !! Index for woody litter (unitless)
328  INTEGER(i_std), PARAMETER :: nlitt = 3        !! Number of levels for litter compartments (unitless)
329  !-
330  !! carbon pools: indices
331  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
332  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
333  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
334  INTEGER(i_std), PARAMETER :: isurface = 4     !! Index for passive carbon pool (unitless)
335  INTEGER(i_std), PARAMETER :: ncarb = 4        !! Number of soil carbon pools (unitless)
336  !-
337  !! For isotopes and nitrogen
338  INTEGER(i_std), PARAMETER :: nelements = 2    !! Number of isotopes considered
339  INTEGER(i_std), PARAMETER :: icarbon = 1      !! Index for carbon
340  INTEGER(i_std), PARAMETER :: initrogen = 2    !! Index for nitrogen
341  !! N-cycle : indices
342  INTEGER(i_std), PARAMETER :: iammonium = 1    !! Index for Ammonium
343  INTEGER(i_std), PARAMETER :: initrate  = 2    !! Index for Nitrate
344  INTEGER(i_std), PARAMETER :: inox      = 3    !! Index for NOX
345  INTEGER(i_std), PARAMETER :: initrous  = 4    !! Index for N2O
346  INTEGER(i_std), PARAMETER :: idinitro  = 5    !! Index for N2
347  INTEGER(i_std), PARAMETER :: nionspec  = 2    !! Number of ionics form considered (ammonium, nitrate)
348  INTEGER(i_std), PARAMETER :: nnspec    = 5    !! Number of N-species considered
349
350  INTEGER(i_std), PARAMETER :: iatm_ammo = 1    !! Index for N input from Ammonium N atmospheric deposition
351  INTEGER(i_std), PARAMETER :: iatm_nitr = 2    !! Index for N input from Nitrate N atmospheric deposition
352  INTEGER(i_std), PARAMETER :: ibnf      = 3    !! Index for N input from BNF
353  INTEGER(i_std), PARAMETER :: ifert     = 4    !! Index for N input from Fertilisation
354  INTEGER(i_std), PARAMETER :: imanure   = 5    !! Index for N input from Manure
355  INTEGER(i_std), PARAMETER :: ninput    = 5    !! Number of N-input considered 
356
357  INTEGER(i_std), PARAMETER :: i_nh4_to_no3 = 1 !! Index for NO3 production
358  INTEGER(i_std), PARAMETER :: i_nh4_to_no  = 2 !! Index for NO production
359  INTEGER(i_std), PARAMETER :: i_nh4_to_n2o = 3 !! Index for N2O production
360  INTEGER(i_std), PARAMETER :: n_nh4_to_x = 3   !! Number of NH4 pathways
361
362  INTEGER(i_std), PARAMETER :: i_no3_to_nox = 1  !! Index for NO3 consumption
363  INTEGER(i_std), PARAMETER :: i_nox_to_n2o  = 2 !! Index for NO/Nox consumption
364  INTEGER(i_std), PARAMETER :: i_n2o_to_n2 = 3   !! Index for N2O consumption
365  INTEGER(i_std), PARAMETER :: n_n_to_x = 3      !! Number of N pathways
366
367  INTEGER(i_std), PARAMETER :: nmonth = 12       !! Months in a year; used for input .nc files with monthly arrays
368 
369  !! Updates for the mass balance closure in stomate_lpj
370  INTEGER(i_std), PARAMETER :: ibeg      = 1    !! At the begining of the routine
371  INTEGER(i_std), PARAMETER :: ipre      = 2    !! After precribe
372  INTEGER(i_std), PARAMETER :: iphe      = 3    !! After phenology
373  INTEGER(i_std), PARAMETER :: igro      = 4    !! After growth functional allocation
374  INTEGER(i_std), PARAMETER :: iage      = 5    !! After Age class distribution
375  INTEGER(i_std), PARAMETER :: ilcc      = 6    !! After land cover change
376  INTEGER(i_std), PARAMETER :: imor      = 7    !! After mortality_clean
377  INTEGER(i_std), PARAMETER :: ispc      = 8    !! After Species Change
378  INTEGER(i_std), PARAMETER :: irec      = 9    !! After recruitment
379  INTEGER(i_std), PARAMETER :: nupdates  = 9    !! Number of step in stomate_lpj where veget_max and atm_to_bm is update
380
381
382  ! These next sets of parameters are now used for both circ_class_kill and
383  ! for the harvest_pool.  One source of confusion is what to do with trees that
384  ! die from self-thinning or forest dieoffs.  These happen in all forests, regardless
385  ! of management strategy.  I decided to put death of this kind into ifm_none, since
386  ! it is the only type of mortality found in an unmanaged forest.  If the mortality
387  ! does not kill the whole forest (e.g. self thinning), it goes into icut_thin.  If it
388  ! does (forest dieoff), it goes into icut_clear.  The biomass is killed in lpj_gap.
389
390  !! Indices used for forest management strategies
391  INTEGER(i_std), PARAMETER :: nfm_types = 6             !! The total number of forest management
392                                                         !! strategies we can use
393  INTEGER(i_std), PARAMETER :: ifm_none = 1              !! No human intervention in the forests.
394  INTEGER(i_std), PARAMETER :: ifm_thin = 2              !! Regular thinning and harvesting of
395                                                         !! wood based on RDI.
396  INTEGER(i_std), PARAMETER :: ifm_cop = 3               !! Coppicing for fuelwood.
397  INTEGER(i_std), PARAMETER :: ifm_src = 4               !! Short rotation coppices for biomass
398                                                         !! production.
399  INTEGER(i_std), PARAMETER :: ifm_crop = 5              !! Crop harvest
400  INTEGER(i_std), PARAMETER :: ifm_grass = 6             !! Grazing or cutting
401 
402  !! Indices used for harvest pools
403  INTEGER(i_std), PARAMETER :: ncut_times = 11           !! The total number of times when trees
404                                                         !! are cut and wood harvested.
405  INTEGER(i_std), PARAMETER :: icut_clear = 1            !! A clearcut where all biomass is removed.
406  INTEGER(i_std), PARAMETER :: icut_thin = 2             !! Thinning of biomass to reduce the
407                                                         !! number of trees.
408  INTEGER(i_std), PARAMETER :: icut_lcc_wood = 3         !! Wood harvest following land cover
409                                                         !! change (LCC)
410  INTEGER(i_std), PARAMETER :: icut_lcc_res = 4          !! Site clearing, removal of the stumps
411                                                         !! and branches following LCC
412  INTEGER(i_std), PARAMETER :: icut_crop = 5             !! Crop harvest
413  INTEGER(i_std), PARAMETER :: icut_grass = 6            !! Grazing or cutting
414  INTEGER(i_std), PARAMETER :: icut_cop1 = 7             !! The first coppice cut
415  INTEGER(i_std), PARAMETER :: icut_cop2 = 8             !! The second (and subsequent) coppice cut
416  INTEGER(i_std), PARAMETER :: icut_cop3 = 9             !! The last coppice cut (only for SRC)
417  INTEGER(i_std), PARAMETER :: icut_storm_break = 10     !! Stem breakage due to storm
418  INTEGER(i_std), PARAMETER :: icut_storm_uproot = 11    !! Tee uprooting due to storm
419
420  !! Indices used to define the product pools
421  !! Numbers based on Eggers 2008 - EFI report
422  INTEGER(i_std), PARAMETER :: nshort = 1                !! Length in years of the short-lived product pool (GE 1)
423  INTEGER(i_std), PARAMETER :: nmedium =17              !! Length in years of the medium-lived product pool (GT 4)
424  INTEGER(i_std), PARAMETER :: nlong = 50                !! Length in years of the long-lived product pool (GT 4)
425
426  !! Indices used to check the mass balance closure
427  INTEGER(i_std), PARAMETER :: nmbcomp = 5               !! The total number of components in
428                                                         !! our mass balance check
429  INTEGER(i_std), PARAMETER :: iatm2land = 1             !! atmosphere to land fluxes such as GPP
430                                                         !! and co2_2_bm
431  INTEGER(i_std), PARAMETER :: iland2atm = 2             !! land to atmosphere fluxes such as Rh,
432                                                         !! Ra and product decomposition
433  INTEGER(i_std), PARAMETER :: ilat2out = 3              !! outgoing lateral flux i.e. DOC leaching
434                                                         !! for the litter routine
435  INTEGER(i_std), PARAMETER :: ilat2in = 4               !! incoming lateral flux i.e. N deposition
436                                                         !! for the land
437  INTEGER(i_std), PARAMETER :: ipoolchange = 5           !! change in pool size i.e. change in
438                                                         !! biomass
439
440  !! Indices used for warning tracking
441  INTEGER(i_std), PARAMETER :: nwarns = 1                !! The total number of warnings we track
442  INTEGER(i_std), PARAMETER :: iwphoto = 1               !! A warning about division by zero in photosynthesis
443
444  !! Indices used for wind damage 
445  INTEGER(i_std), PARAMETER :: ibreakage = 1             !! The index for stem breakage dur to wind damage
446  INTEGER(i_std), PARAMETER :: ioverturning = 2          !! The index for the tree overtuning due to wind damage
447
448  !! Indices for orphan fluxes
449  INTEGER(i_std), PARAMETER :: norphans = 8              !! Total number of orphan fluxes (unitless)
450  INTEGER(i_std), PARAMETER :: ivegold = 1               !! Index for veget_max before LCC
451  INTEGER(i_std), PARAMETER :: ivegnew = 2               !! Index for veget_max before LCC (includes veget_max of orphan fluxes)
452  INTEGER(i_std), PARAMETER :: igpp = 3                  !! Index for gpp_daily
453  INTEGER(i_std), PARAMETER :: ico2bm = 4                !! Index for co2_to_bm
454  INTEGER(i_std), PARAMETER :: irmain = 5                !! Index for maintenance respiration
455  INTEGER(i_std), PARAMETER :: irgrow = 6                !! Index for growth respiration
456  INTEGER(i_std), PARAMETER :: inpp = 7                  !! Index for npp_daily
457  INTEGER(i_std), PARAMETER :: irhet = 8                 !! Index for total heterotrophic respiration
458  !
459
460  !! Indices for phenology
461  ! The variable ::plant_status replaces several variables (senescence,
462  ! begin_leaves and allow_phenoinit) that describe the phenological status of the plant
463  ! by storing these different aspects of phenology in a single variable, inconsistencies
464  ! become impossible or at least easier to check.
465  ! When the model starts from scratch the status is set to iprescribe this allows us
466  ! to grow leaves from the first year onwards. The plant should then go through the
467  ! different growth phases: ibudsavail, ibudbreak, icanopy, isenescent, idormant and
468  ! finally idead. Following idormant the status should return ibudsavail to initiate
469  ! another cycle in the subsequent growing season. Following idead new vegetation
470  ! should be prescribed.
471  INTEGER(i_std), PARAMETER :: inone = 0                 !! No plants thus no status
472  INTEGER(i_std), PARAMETER :: iprescribe = 1            !! Prescribe a PFT
473  INTEGER(i_std), PARAMETER :: ibudsavail = 2            !! Buds are present
474  INTEGER(i_std), PARAMETER :: ibudbreak = 3             !! Day that the buds break and leaf
475                                                         !! on-set begins
476  INTEGER(i_std), PARAMETER :: icanopy = 4               !! Canopy is present
477  INTEGER(i_std), PARAMETER :: isenescent = 5            !! The plant is senescent
478  INTEGER(i_std), PARAMETER :: idormant = 6              !! The plant is dormant
479  INTEGER(i_std), PARAMETER :: idead = 7                 !! The plant was killed
480
481  !
482  !! Indices used for analytical spin-up
483  INTEGER(i_std), PARAMETER :: nbpools = 10              !! Total number of carbon pools (unitless)
484  INTEGER(i_std), PARAMETER :: istructural_above = 1    !! Index for structural litter above (unitless)
485  INTEGER(i_std), PARAMETER :: istructural_below = 2    !! Index for structural litter below (unitless)
486  INTEGER(i_std), PARAMETER :: imetabolic_above = 3     !! Index for metabolic litter above (unitless)
487  INTEGER(i_std), PARAMETER :: imetabolic_below = 4     !! Index for metabolic litter below (unitless)
488  INTEGER(i_std), PARAMETER :: iwoody_above = 5         !! Index for woody litter above (unitless)
489  INTEGER(i_std), PARAMETER :: iwoody_below = 6         !! Index for woody litter below (unitless)
490  INTEGER(i_std), PARAMETER :: iactive_pool = 7         !! Index for active carbon pool (unitless)
491  INTEGER(i_std), PARAMETER :: islow_pool   = 8         !! Index for slow carbon pool (unitless)
492  INTEGER(i_std), PARAMETER :: ipassive_pool = 9        !! Index for passive carbon pool (unitless)
493  INTEGER(i_std), PARAMETER :: isurface_pool = 10       !! Index for surface carbon pool (unitless)
494
495  !
496  !! Indices used for canopy structure (Pgap & eff lai)
497  INTEGER(i_std),PARAMETER   :: ndist_types=6           !! the number of distributions we need in the LAI effective routines
498  INTEGER(i_std),PARAMETER   :: iheight=1               !! the tree height distribution
499  INTEGER(i_std),PARAMETER   :: idiameter=2             !! the trunk diameter distribution
500  INTEGER(i_std),PARAMETER   :: icnvol=3                !! the crown volume distribution
501  INTEGER(i_std),PARAMETER   :: icnarea=4               !! the crown area distribution
502  INTEGER(i_std),PARAMETER   :: icndiaver=5             !! the verticle crown diameter distribution
503  INTEGER(i_std),PARAMETER   :: icndiahor=6             !! the horizontal crown diameter distribution
504  !
505  ! NUMERICAL AND PHYSICS CONSTANTS
506  !
507  !
508
509  !-
510  ! 1. Mathematical and numerical constants
511  !-
512  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
513  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
514  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
515  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
516  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
517  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
518  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
519  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
520  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
521  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
522  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
523  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
524  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
525
526  !-
527  ! 2 . Physics
528  !-
529  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
530  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
531  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
532  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! 0 degre Celsius in degre Kelvin (K)
533  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
534  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
535  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
536  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
537  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
538  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
539  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
540  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
541                                                            !! of dry air (unitless)
542  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
543  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
544  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
545       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
546  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
547  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
548                                                            !! vapor minus 1(unitless) 
549  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
550 
551  REAL(r_std), PARAMETER :: rho_h2o= 0.9991_r_std           !! Density of water at 15°C (g cm-3)                                                          !! minus 1 (unitless)
552  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
553  REAL(r_std), PARAMETER :: ct_karman = 0.41_r_std          !! Van Karmann Constant (unitless)
554  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
555  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
556  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gas constant (J.mol^{-1}.K^{-1})
557  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
558
559  REAL(r_std), PARAMETER :: mm_m = 1000._r_std              !! conversion from milimeters to meters
560
561  INTEGER(i_std), SAVE :: testpft = 6
562  !-
563  ! 3. Climatic constants
564  !-
565  !! Constantes of the Louis scheme
566  REAL(r_std), SAVE :: cb = 5._r_std              !! Constant of the Louis scheme (unitless);
567                                                  !! reference to Louis (1979)
568!$OMP THREADPRIVATE(cb)
569  REAL(r_std), SAVE :: cc = 5._r_std              !! Constant of the Louis scheme (unitless);
570                                                  !! reference to Louis (1979)
571!$OMP THREADPRIVATE(cc)
572  REAL(r_std), SAVE :: cd = 5._r_std              !! Constant of the Louis scheme (unitless);
573                                                  !! reference to Louis (1979)
574!$OMP THREADPRIVATE(cd)
575  REAL(r_std), SAVE :: rayt_cste = 125.           !! Constant in the computation of surface resistance (W.m^{-2})
576!$OMP THREADPRIVATE(rayt_cste)
577  REAL(r_std), SAVE :: defc_plus = 23.E-3         !! Constant in the computation of surface resistance (K.W^{-1})
578!$OMP THREADPRIVATE(defc_plus)
579  REAL(r_std), SAVE :: defc_mult = 1.5            !! Constant in the computation of surface resistance (K.W^{-1})
580!$OMP THREADPRIVATE(defc_mult)
581
582  !-
583  ! 4. Soil thermodynamics constants
584  !-
585  ! Look at constantes_soil.f90
586
587
588  !
589  ! OPTIONAL PARTS OF THE MODEL
590  !
591  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
592                                                  !! we provide here a way to catch that in the calling procedure.
593                                                  !! (from Jan Polcher)(true/false)
594  LOGICAL, SAVE     :: almaoutput =.FALSE.        !! Selects the type of output for the model.(true/false)
595                                                  !! Value is read from run.def in intersurf_history
596!$OMP THREADPRIVATE(almaoutput)
597
598  !
599  ! DIVERSE
600  !
601  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
602                                                           ! Compatibility with Nicolas Viovy driver.
603!$OMP THREADPRIVATE(stomate_forcing_name)
604  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
605                                                           ! Compatibility with Nicolas Viovy driver.
606!$OMP THREADPRIVATE(stomate_Cforcing_name)
607  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
608!$OMP THREADPRIVATE(forcing_id)
609  LOGICAL, SAVE :: allow_forcing_write=.TRUE.        !! Allow writing of stomate_forcing file.
610                                                     !! This variable will be set to false for teststomate.
611
612
613
614                         !------------------------!
615                         !  SECHIBA PARAMETERS    !
616                         !------------------------!
617 
618
619  !
620  ! GLOBAL PARAMETERS   
621  !
622  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
623!$OMP THREADPRIVATE(min_wind)
624  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occurs (kg.m^{-2})
625!$OMP THREADPRIVATE(snowcri)
626
627
628  !
629  ! FLAGS ACTIVATING SUB-MODELS
630  !
631  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
632!$OMP THREADPRIVATE(treat_expansion)
633  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
634!$OMP THREADPRIVATE(ok_herbivores)
635  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
636!$OMP THREADPRIVATE(harvest_agri)
637  LOGICAL, SAVE :: lpj_gap_const_mort          !! constant moratlity (true/false). Default value depend on OK_DGVM.
638!$OMP THREADPRIVATE(lpj_gap_const_mort)
639  LOGICAL, SAVE :: disable_fire = .FALSE.      !! flag that disable fire (true/false)
640!$OMP THREADPRIVATE(disable_fire)
641  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
642!$OMP THREADPRIVATE(spinup_analytic)
643
644  !
645  ! CONFIGURATION VEGETATION
646  !
647  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
648!$OMP THREADPRIVATE(agriculture)
649  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
650!$OMP THREADPRIVATE(impveg)
651  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
652!$OMP THREADPRIVATE(impsoilt)
653  LOGICAL, SAVE :: impose_ninput_dep = .FALSE. !! Impose N input values ? (true/false)
654!$OMP THREADPRIVATE(impose_ninput_dep)
655  LOGICAL, SAVE :: impose_ninput_fert = .FALSE. !! Impose N input values ? (true/false)       
656!$OMP THREADPRIVATE(impose_ninput_fert)   
657 LOGICAL, SAVE :: impose_ninput_manure = .FALSE. !! Impose N input values ? (true/false)       
658!$OMP THREADPRIVATE(impose_ninput_manure)                     
659  LOGICAL, SAVE :: impose_ninput_bnf = .FALSE. !! Impose N input values ? (true/false)       
660!$OMP THREADPRIVATE(impose_ninput_bnf)
661  LOGICAL, SAVE :: do_now_stomate_lcchange = .FALSE.  !! Time to call lcchange in stomate_lpj
662!$OMP THREADPRIVATE(do_now_stomate_lcchange)
663  LOGICAL, SAVE :: done_stomate_lcchange = .FALSE.    !! If true, call lcchange in stomate_lpj has just been done.
664!$OMP THREADPRIVATE(done_stomate_lcchange)
665  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
666!$OMP THREADPRIVATE(read_lai)
667  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
668!$OMP THREADPRIVATE(veget_reinit)
669  LOGICAL, SAVE :: ninput_reinit = .TRUE.  !! To change N INPUT file in a run. (true/false)
670!$OMP THREADPRIVATE(ninput_reinit)
671
672  !
673  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
674  !
675  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
676!$OMP THREADPRIVATE(max_snow_age)
677  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)
678!$OMP THREADPRIVATE(snow_trans)
679  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
680!$OMP THREADPRIVATE(sneige)
681  REAL(r_std), SAVE :: maxmass_snow = 3000.     !! The maximum mass of snow (kg.m^{-2})
682!$OMP THREADPRIVATE(maxmass_snow)
683
684  !! Heat capacity
685  REAL(r_std), PARAMETER :: capa_ice = 2.228*1.E3       !! Heat capacity of ice (J/kg/K)
686  REAL(r_std), SAVE      :: so_capa_ice                 !! Heat capacity of saturated frozen soil (J/K/m3)
687!$OMP THREADPRIVATE(so_capa_ice)
688  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3)
689  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3)
690
691  !! Thermal conductivities
692  REAL(r_std), PARAMETER :: cond_water = 0.6            !! Thermal conductivity of liquid water (W/m/K)
693  REAL(r_std), PARAMETER :: cond_ice = 2.2              !! Thermal conductivity of ice (W/m/K)
694  REAL(r_std), PARAMETER :: cond_solid = 2.32           !! Thermal conductivity of mineral soil particles (W/m/K)
695
696  !! Time constant of long-term soil humidity (s)
697  REAL(r_std), PARAMETER :: lhf = 0.3336*1.E6           !! Latent heat of fusion (J/kg)
698
699  INTEGER(i_std), PARAMETER :: nsnow=3                  !! Number of levels in the snow for explicit snow scheme   
700  REAL(r_std), PARAMETER    :: XMD    = 28.9644E-3 
701  REAL(r_std), PARAMETER    :: XBOLTZ      = 1.380658E-23 
702  REAL(r_std), PARAMETER    :: XAVOGADRO   = 6.0221367E+23 
703  REAL(r_std), PARAMETER    :: XRD    = XAVOGADRO * XBOLTZ / XMD 
704  REAL(r_std), PARAMETER    :: XCPD   = 7.* XRD /2. 
705  REAL(r_std), PARAMETER    :: phigeoth = 0.057 ! 0. DKtest
706  REAL(r_std), PARAMETER    :: thick_min_snow = .01 
707
708  !! The maximum snow density and water holding characterisicts
709  REAL(r_std), SAVE         :: xrhosmax         = 750.  !! (kg m-3)
710  REAL(r_std), SAVE         :: xwsnowholdmax1   = 0.03  !! (-)
711  REAL(r_std), SAVE         :: xwsnowholdmax2   = 0.10  !! (-)
712  REAL(r_std), SAVE         :: xsnowrhohold     = 200.0 !! (kg/m3)
713  REAL(r_std), SAVE         :: xrhosmin = 50. 
714  REAL(r_std), PARAMETER    :: xci = 2.106e+3 
715  REAL(r_std), PARAMETER    :: xrv = 6.0221367e+23 * 1.380658e-23 /18.0153e-3 
716
717  !! ISBA-ES Critical snow depth at which snow grid thicknesses constant
718  REAL(r_std), PARAMETER    :: xsnowcritd = 0.03  ! (m)
719
720  !! The threshold of snow depth used for preventing numerical problem in thermal calculations
721  REAL(r_std), PARAMETER    :: snowcritd_thermal = 0.01  ! (m) 
722 
723  !! ISBA-ES CROCUS (Pahaut 1976): snowfall density coefficients:
724  REAL(r_std), PARAMETER       :: snowfall_a_sn = 109.0  !! (kg/m3)
725  REAL(r_std), PARAMETER       :: snowfall_b_sn =   6.0  !! (kg/m3/K)
726  REAL(r_std), PARAMETER       :: snowfall_c_sn =  26.0  !! [kg/(m7/2 s1/2)]
727
728  REAL(r_std), PARAMETER       :: dgrain_new_max=  2.0e-4!! (m) : Maximum grain size of new snowfall
729 
730  !! Used in explicitsnow to prevent numerical problems as snow becomes vanishingly thin.
731  REAL(r_std), PARAMETER                :: psnowdzmin = .0001   ! m
732  REAL(r_std), PARAMETER                :: xsnowdmin = .000001  ! m
733
734  REAL(r_std), PARAMETER                :: ph2o = 1000.         !! Water density [kg/m3]
735 
736  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
737  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
738  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND1 = 0.02    ! [W/m/K]
739  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND2 = 2.5E-6  ! [W m5/(kg2 K)]
740 
741  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
742  ! (sig only for new snow OR high altitudes)
743  ! from Sun et al. (1999): based on data from Jordan (1991)
744  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
745  !
746  REAL(r_std), SAVE         :: ZSNOWTHRMCOND_AVAP  = -0.06023 !! (W/m/K)
747  REAL(r_std), SAVE         :: ZSNOWTHRMCOND_BVAP  = -2.5425  !! (W/m)
748  REAL(r_std), SAVE         :: ZSNOWTHRMCOND_CVAP  = -289.99  !! (K)
749 
750  REAL(r_std),SAVE          :: xansmax = 0.85                 !! Maxmimum snow albedo
751  REAL(r_std),SAVE          :: xansmin = 0.50                 !! Miniumum snow albedo
752  REAL(r_std),SAVE          :: xans_todry = 0.008             !! Albedo decay rate for dry snow
753  REAL(r_std),SAVE          :: xans_t = 0.240                 !! Albedo decay rate for wet snow
754
755  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
756  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
757  REAL(r_std), PARAMETER                  :: XP00 = 1.E5
758
759  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
760  ! (sig only for new snow OR high altitudes)
761  ! from Sun et al. (1999): based on data from Jordan (1991)
762  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
763  !
764  REAL(r_std), SAVE          :: ZSNOWCMPCT_RHOD  = 150.0        !! (kg/m3)
765  REAL(r_std), SAVE          :: ZSNOWCMPCT_ACM   = 2.8e-6       !! (1/s)
766  REAL(r_std), SAVE          :: ZSNOWCMPCT_BCM   = 0.04         !! (1/K)
767  REAL(r_std), SAVE          :: ZSNOWCMPCT_CCM   = 460.         !! (m3/kg)
768  REAL(r_std), SAVE          :: ZSNOWCMPCT_V0    = 3.7e7        !! (Pa/s)
769  REAL(r_std), SAVE          :: ZSNOWCMPCT_VT    = 0.081        !! (1/K)
770  REAL(r_std), SAVE          :: ZSNOWCMPCT_VR    = 0.018        !! (m3/kg)
771
772    !
773  ! PARAMETERS USED FOR CANOPY LAYERS (Albedo, photosynthesis, energy budget)
774  !
775
776  INTEGER(i_std), PARAMETER   :: nlevels = 1                  !! Originally the number of levels in the canopy used in 
777                                                              !! calculation of the energy budget. After the
778                                                              !! mleb calculations have been implemented in enerbil,
779                                                              !! the jnlvls levels are determining the levels used
780                                                              !! within the multi-layer energy budget calculations. However,
781                                                              !! nlevels are still used in calculate_z_level_photo. Cannot
782                                                              !! be deleted before any decision regarding the vertical
783                                                              !! layering has been made.
784
785  INTEGER(i_std), SAVE        :: nlevels_photo                !! Number of levels in the canopy used in the photosynthesis
786                                                              !! routine per level dictacted by nlevels. For example, if
787                                                              !! if nlevels = 2 and nlevels_photo = 3, the photosynthesis
788                                                              !! will be calculated for 2*3=6 total levels.
789!$OMP THREADPRIVATE(nlevels_photo)
790  INTEGER(i_std), SAVE        :: nlevels_tot                  !! Total number of levels, nlevels*nlevels_photo. Currently,
791                                                              !! nlevels=1 is used, thus nlevels_tot=nevels_photo.
792                                                              !! Note that when using the multi-layer budget nlevels_photo
793                                                              !! needs to be nlevels_photo=jnlvls_canopy+1
794
795!$OMP THREADPRIVATE(nlevels_tot)
796  INTEGER(i_std), SAVE        :: jnlvls=29                    !! Number of levels in the multilayer energy budget scheme
797!$OMP THREADPRIVATE(jnlvls)
798  INTEGER(i_std), SAVE        :: jnlvls_under=10              !! Number of levels in the understorey of the multilayer energy budget scheme
799!$OMP THREADPRIVATE(jnlvls_under)
800  INTEGER(i_std), SAVE        :: jnlvls_canopy=10             !! Number of levels in the canopy of the multilayer energy budget scheme
801!$OMP THREADPRIVATE(jnlvls_canopy)
802  INTEGER(i_std), SAVE        :: jnlvls_over=9                !! Number of levels in the overstorey of the multilayer energy budget scheme
803!$OMP THREADPRIVATE(jnlvls_over)
804
805
806  INTEGER(i_std), SAVE        :: nlev_top                     !! Maximum number of canopy levels that are used to construct the "top"
807                                                              !! layer of the canopy. The top layer is used in the calculation
808                                                              !! transpiration.
809!$OMP THREADPRIVATE(nlev_top)
810  REAL(r_std), PARAMETER, &
811         DIMENSION (nlevels) :: z_level = (/ 0.0 /)           !! The height of the bottom of each canopy layer                                             
812                                                              !! @tex $(m)$ @endtex
813!$OMP THREADPRIVATE(z_level)
814
815
816
817  !
818  ! Parameters for determining the effective LAI for use in Pinty's albedo scheme
819  !
820  REAL(r_std), SAVE          ::  laieff_solar_angle           !! the zenith angle of the sun which determines our effective LAI
821                                                              !! Pinty et al recommend a value of 60 degrees for this regadless of the true
822                                                              !! solar zenith angle
823!$OMP THREADPRIVATE(laieff_solar_angle)
824  REAL(r_std), SAVE          ::  laieff_zero_cutoff           !! an arbitrary cutoff to prevent too low of values from being passed to
825                                                              !! routines in the calculation of the effective LAI
826!$OMP THREADPRIVATE(laieff_zero_cutoff)
827
828
829  !
830  ! PARAMETERS FOR HYDRAULIC ARCHITECTURE
831  !
832
833  REAL(r_std), SAVE, DIMENSION(2)         :: a_viscosity = (/0.556,0.022/) !! Empirical parameters to adjust the resistance of fine
834                                                                           !! root and sapwood to the temperature dependency of the
835                                                                           !! viscosity of water Cochard et al 2000
836!$OMP THREADPRIVATE(a_viscosity)
837
838  !
839  ! BVOC : Biogenic activity  for each age class
840  !
841  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
842                                                                                       !! age class : isoprene (unitless)
843!$OMP THREADPRIVATE(iso_activity)
844  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
845                                                                                       !! age class : methanol (unnitless)
846!$OMP THREADPRIVATE(methanol_activity)
847
848  !
849  ! condveg.f90
850  !
851
852  ! 1. Scalar
853
854  ! 1.1 Flags used inside the module
855
856  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
857                                            !! albedo (see header of subroutine)
858                                            !! (true/false)
859!$OMP THREADPRIVATE(alb_bare_model)
860  LOGICAL, SAVE :: alb_bg_modis = .FALSE.   !! Switch for choosing values of bare soil
861                                            !! albedo read from file
862                                            !! (true/false)
863!$OMP THREADPRIVATE(alb_bg_modis)
864  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
865                                            !! (see header of subroutine). 
866                                            !! (true/false)
867!$OMP THREADPRIVATE(impaze)
868  LOGICAL, SAVE :: rough_dyn = .FALSE.      !! Chooses between two methods to calculate the
869                                            !! the roughness height : static or dynamic (varying with LAI)
870                                            !! (true/false)
871!$OMP THREADPRIVATE(rough_dyn)
872
873  LOGICAL, SAVE :: new_watstress = .FALSE.
874!$OMP THREADPRIVATE(new_watstress)
875     
876  REAL(r_std), SAVE :: alpha_watstress = 1.
877!$OMP THREADPRIVATE(alpha_watstress)
878
879  LOGICAL, SAVE :: sla_dyn = .FALSE.        !! Chooses between two methods to calculate the
880                                            !! specific leaf area: static or dynamic (varying with LAI or biomass)
881                                            !! (true/false)
882!$OMP THREADPRIVATE(sla_dyn) 
883 
884  ! 1.2 Others
885
886  REAL(r_std), SAVE :: height_displacement = 0.66        !! Factor to calculate the zero-plane displacement
887                                                         !! height from vegetation height (m)
888!$OMP THREADPRIVATE(height_displacement)
889  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
890!$OMP THREADPRIVATE(z0_bare)
891  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
892!$OMP THREADPRIVATE(z0_ice)
893  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)
894!$OMP THREADPRIVATE(tcst_snowa)
895  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
896!$OMP THREADPRIVATE(snowcri_alb)
897  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
898!$OMP THREADPRIVATE(fixed_snow_albedo)
899  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
900!$OMP THREADPRIVATE(z0_scal)
901  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
902                                                         !! displacement height (m) (imposed)
903!$OMP THREADPRIVATE(roughheight_scal)
904  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
905!$OMP THREADPRIVATE(emis_scal)
906
907  REAL(r_std), SAVE :: c1 = 0.32                         !! Constant used in the formulation of the ratio of
908!$OMP THREADPRIVATE(c1)                                  !! friction velocity to the wind speed at the canopy top
909                                                         !! see Ershadi et al. (2015) for more info
910  REAL(r_std), SAVE :: c2 = 0.264                        !! Constant used in the formulation of the ratio of
911!$OMP THREADPRIVATE(c2)                                  !! friction velocity to the wind speed at the canopy top
912                                                         !! see Ershadi et al. (2015) for more info
913  REAL(r_std), SAVE :: c3 = 15.1                         !! Constant used in the formulation of the ratio of
914!$OMP THREADPRIVATE(c3)                                  !! friction velocity to the wind speed at the canopy top
915                                                         !! see Ershadi et al. (2015) for more info
916  REAL(r_std), SAVE :: Cdrag_foliage = 0.2               !! Drag coefficient of the foliage
917!$OMP THREADPRIVATE(Cdrag_foliage)                       !! See Ershadi et al. (2015) and Su et. al (2001) for more info
918  REAL(r_std), SAVE :: Ct = 0.01                         !! Heat transfer coefficient of the leaf
919!$OMP THREADPRIVATE(Ct)                                  !! See Ershadi et al. (2015) and Su et. al (2001) for more info
920  REAL(r_std), SAVE :: Prandtl = 0.71                    !! Prandtl number used in the calculation of Ct_star
921!$OMP THREADPRIVATE(Prandtl)                             !! See Su et. al (2001) for more info
922
923 
924! 2. Arrays
925 
926  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
927!$OMP THREADPRIVATE(alb_deadleaf)
928  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
929!$OMP THREADPRIVATE(alb_ice)
930  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! Albedo values for visible and near-infrared
931                                                                     !! used imposed (unitless)
932!$OMP THREADPRIVATE(albedo_scal)
933  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
934       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
935                                                          !! dry soil albedo values in visible range
936!$OMP THREADPRIVATE(vis_dry)
937  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
938       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
939                                                          !! dry soil albedo values in near-infrared range
940!$OMP THREADPRIVATE(nir_dry)
941  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
942       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
943                                                          !! wet soil albedo values in visible range
944!$OMP THREADPRIVATE(vis_wet)
945  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
946       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
947                                                          !! wet soil albedo values in near-infrared range
948!$OMP THREADPRIVATE(nir_wet)
949  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
950       &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:
951                                                                   !! Averaged of wet and dry soil albedo values
952                                                                   !! in visible and near-infrared range
953!$OMP THREADPRIVATE(albsoil_vis)
954  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
955       &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:
956                                                                !! Averaged of wet and dry soil albedo values
957                                                                !! in visible and near-infrared range
958!$OMP THREADPRIVATE(albsoil_nir)
959  REAL(r_std) :: alb_threshold = 0.0000000001_r_std       !! A threshold for the iteration of the
960                                                          !! multilevel albedo.  Could be externalised.
961                                                          !! Fairly arbitrary, although if a level has
962                                                          !! no LAI the absorption often ends up being
963                                                          !! equal to this value, so it should not
964                                                          !! be high.
965!$OMP THREADPRIVATE(alb_threshold)
966
967
968
969  !
970  ! diffuco.f90
971  !
972
973  ! 0. Constants
974
975  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
976                                                     !! of dry air (unitless)
977  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
978  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
979  REAL(r_std), PARAMETER :: mol_to_m_1 = 0.0244      !!
980  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
981  REAL(r_std), PARAMETER :: W_to_mol = 4.6           !! W_to_mmol * RG_to_PAR = 2.3
982
983  ! 1. Scalar
984
985  INTEGER(i_std), SAVE :: nlai = 10             !! Number of LAI levels (unitless)
986!$OMP THREADPRIVATE(nlai)
987  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
988!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
989  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
990!$OMP THREADPRIVATE(laimax)
991  LOGICAL, SAVE :: downregulation_co2 = .FALSE.            !! Set to .TRUE. if you want CO2 downregulation.
992!$OMP THREADPRIVATE(downregulation_co2)
993  REAL(r_std), SAVE :: downregulation_co2_baselevel = 280. !! CO2 base level (ppm)
994!$OMP THREADPRIVATE(downregulation_co2_baselevel)
995  REAL(r_std), SAVE :: gb_ref = 1./25.                     !! Leaf bulk boundary layer resistance (s m-1)
996!$OMP THREADPRIVATE(gb_ref)
997
998  ! 3. Coefficients of equations
999
1000  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
1001!$OMP THREADPRIVATE(lai_level_depth)
1002!
1003  REAL(r_std), SAVE :: x1_coef =  0.177        !! Multiplicative factor for calculating the pseudo first order rate constant
1004                                               !! of assimilation response to
1005                                               !co2 kt (unitless)
1006!$OMP THREADPRIVATE(x1_coef)
1007  REAL(r_std), SAVE :: x1_Q10 =  0.069         !! Exponential factor in the equation defining kt (unitless)
1008!$OMP THREADPRIVATE(x1_Q10)
1009  REAL(r_std), SAVE :: quantum_yield =  0.092  !!
1010!$OMP THREADPRIVATE(quantum_yield)
1011  REAL(r_std), SAVE :: kt_coef = 0.7           !! Multiplicative factor in the equation defining kt (unitless)
1012!$OMP THREADPRIVATE(kt_coef)
1013  REAL(r_std), SAVE :: kc_coef = 39.09         !! Multiplicative factor for calculating the Michaelis-Menten
1014                                               !! coefficient Kc (unitless)
1015!$OMP THREADPRIVATE(kc_coef)
1016  REAL(r_std), SAVE :: Ko_Q10 = 0.085          !! Exponential factor for calculating the Michaelis-Menten coefficients
1017                                               !! Kc and Ko (unitless)
1018!$OMP THREADPRIVATE(Ko_Q10)
1019  REAL(r_std), SAVE :: Oa = 210000.            !! Intercellular concentration of O2 (ppm)
1020!$OMP THREADPRIVATE(Oa)
1021  REAL(r_std), SAVE :: Ko_coef =  2.412        !! Multiplicative factor for calculating the Michaelis-Menten
1022                                               !! coefficient Ko (unitless)
1023!$OMP THREADPRIVATE(Ko_coef)
1024  REAL(r_std), SAVE :: CP_0 = 42.              !! Multiplicative factor for calculating the CO2 compensation
1025                                               !! point CP (unitless)
1026!$OMP THREADPRIVATE(CP_0)
1027  REAL(r_std), SAVE :: CP_temp_coef = 9.46     !! Exponential factor for calculating the CO2 compensation point CP (unitless)
1028!$OMP THREADPRIVATE(CP_temp_coef)
1029  REAL(r_std), SAVE :: CP_temp_ref = 25.       !! Reference temperature for the CO2 compensation point CP (C)
1030!$OMP THREADPRIVATE(CP_temp_ref)
1031  !
1032  REAL(r_std), SAVE, DIMENSION(2) :: rt_coef = (/ 0.8, 1.3 /)    !!
1033!$OMP THREADPRIVATE(rt_coef)
1034  REAL(r_std), SAVE, DIMENSION(2) :: vc_coef = (/ 0.39, 0.3 /)   !!
1035!$OMP THREADPRIVATE(vc_coef)
1036  REAL(r_std), SAVE               :: c13_a = 4.4      !! fractionation against during diffusion
1037!$OMP THREADPRIVATE(c13_a)
1038  REAL(r_std), SAVE               :: c13_b = 27.      !! fractionation against during carboxylation
1039!$OMP THREADPRIVATE(c13_b)
1040  REAL(r_std), SAVE               :: threshold_c13_assim = 0.01 !! If assimilation falls below this threshold
1041                                                                !! the delta_c13
1042                                                                !is set to zero
1043  !
1044  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
1045  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
1046!$OMP THREADPRIVATE(dew_veg_poly_coeff)
1047!
1048  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
1049!$OMP THREADPRIVATE(Oi)
1050  !
1051  ! slowproc.f90
1052  !
1053
1054  ! 1. Scalar
1055
1056  INTEGER(i_std), SAVE :: veget_year_orig = 0        !!  first year for landuse (number)
1057!$OMP THREADPRIVATE(veget_year_orig)
1058  INTEGER(i_std), SAVE :: ninput_year_orig = 0       !!  first year for N inputs (number)
1059!$OMP THREADPRIVATE(ninput_year_orig)
1060  LOGICAL, SAVE :: ninput_suffix_year = .FALSE.      !! Do the Ninput datasets have a 'year' suffix ? (y/n) 
1061!$OMP THREADPRIVATE(ninput_suffix_year)
1062  REAL(r_std), SAVE :: clayfraction_default = 0.2    !! Default value for clay fraction (0-1, unitless)
1063!$OMP THREADPRIVATE(clayfraction_default)
1064  REAL(r_std), SAVE :: sandfraction_default = 0.3    !! Default value for sand fraction (0-1, unitless)
1065!$OMP THREADPRIVATE(clayfraction_default)
1066  REAL(r_std), SAVE :: siltfraction_default = 0.5    !! Default value for silt fraction (0-1, unitless)
1067!$OMP THREADPRIVATE(siltfraction_default)
1068  REAL(r_std), SAVE :: bulk_default = 1000           !! Default value for bulk density of soil (kg/m3)
1069!$OMP THREADPRIVATE(bulk_default)
1070  REAL(r_std), SAVE :: ph_default = 5.5              !! Default value for pH of soil (-)
1071!$OMP THREADPRIVATE(ph_default)
1072  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
1073!$OMP THREADPRIVATE(min_vegfrac)
1074  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
1075!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
1076 
1077  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
1078!$OMP THREADPRIVATE(stempdiag_bid)
1079
1080
1081                           !-----------------------------!
1082                           !  STOMATE AND LPJ PARAMETERS !
1083                           !-----------------------------!
1084
1085
1086  !
1087  ! lpj_constraints.f90
1088  !
1089 
1090  ! 1. Scalar
1091
1092  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
1093                                           !! regeneration (vernalization) (years)
1094!$OMP THREADPRIVATE(too_long)
1095
1096
1097  !
1098  ! lpj_establish.f90
1099  !
1100
1101  ! 1. Scalar
1102
1103  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (ind/m2/dt_stomate)
1104!$OMP THREADPRIVATE(estab_max_tree)
1105  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (ind/m2/dt_stomate)
1106!$OMP THREADPRIVATE(estab_max_grass)
1107 
1108  ! 3. Coefficients of equations
1109
1110  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
1111!$OMP THREADPRIVATE(establish_scal_fact)
1112  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
1113!$OMP THREADPRIVATE(max_tree_coverage)
1114  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
1115!$OMP THREADPRIVATE(ind_0_estab)
1116
1117
1118  !
1119  ! lpj_fire.f90
1120  !
1121
1122  ! 1. Scalar
1123
1124  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
1125!$OMP THREADPRIVATE(tau_fire)
1126  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
1127                                                !! below which iginitions extinguish
1128                                                !! @tex $(gC m^{-2})$ @endtex
1129!$OMP THREADPRIVATE(litter_crit)
1130  REAL(r_std), SAVE :: fire_resist_lignin = 0.5 !!
1131!$OMP THREADPRIVATE(fire_resist_lignin)
1132  ! 2. Arrays
1133
1134  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
1135       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95, .95 /)       !! compartments emitted to the atmosphere
1136!$OMP THREADPRIVATE(co2frac)                                                         !! when burned (unitless, 0-1) 
1137
1138  ! 3. Coefficients of equations
1139
1140  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
1141!$OMP THREADPRIVATE(bcfrac_coeff)
1142  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
1143!$OMP THREADPRIVATE(firefrac_coeff)
1144
1145  !
1146  ! lpj_gap.f90
1147  !
1148
1149  ! 1. Scalar
1150
1151  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
1152                                                 !! @tex $(year^{-1})$ @endtex
1153!$OMP THREADPRIVATE(ref_greff)
1154
1155  !               
1156  ! lpj_light.f90
1157  !             
1158
1159  ! 1. Scalar
1160 
1161  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
1162                                            !! to fpc of last time step (F)? (true/false)
1163!$OMP THREADPRIVATE(annual_increase)
1164  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
1165                                            !! (due to its branches etc.) (0-1, unitless)
1166                                            !! This means that only a small fraction of its crown area
1167                                            !! can be invaded by other trees.
1168!$OMP THREADPRIVATE(min_cover)
1169  !
1170  ! lpj_pftinout.f90
1171  !
1172
1173  ! 1. Scalar
1174
1175  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
1176!$OMP THREADPRIVATE(min_avail)
1177  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
1178!$OMP THREADPRIVATE(ind_0)
1179  ! 3. Coefficients of equations
1180 
1181  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
1182!$OMP THREADPRIVATE(RIP_time_min)
1183  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
1184!$OMP THREADPRIVATE(npp_longterm_init)
1185  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
1186!$OMP THREADPRIVATE(everywhere_init)
1187
1188
1189
1190
1191  !
1192  ! stomate_data.f90
1193  !
1194
1195  ! 1. Scalar
1196
1197  ! 1.2 climatic parameters
1198
1199  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
1200!$OMP THREADPRIVATE(precip_crit)
1201  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
1202!$OMP THREADPRIVATE(gdd_crit_estab)
1203  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
1204!$OMP THREADPRIVATE(fpc_crit)
1205
1206  ! 1.3 sapling characteristics
1207
1208  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
1209!$OMP THREADPRIVATE(alpha_grass)
1210  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
1211!$OMP THREADPRIVATE(alpha_tree)
1212  REAL(r_std), SAVE :: struct_to_leaves = 0.05  !! Fraction of structural carbon in grass and crops as a share of the leaf
1213                                                !! carbon pool. Only used for grasses and crops (thus NOT for trees)
1214                                                !! (unitless)
1215!$OMP THREADPRIVATE(struct_to_leaves)
1216
1217  REAL(r_std), SAVE :: labile_to_total = 0.01   !! Fraction of the labile pool in trees, grasses and crops as a share of the
1218                                                !! total carbon pool (accounting for the N-content of the different tissues).
1219                                                !! (unitless)
1220!$OMP THREADPRIVATE(labile_to_total)
1221
1222
1223
1224  ! 1.4  time scales for phenology and other processes (in days)
1225  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
1226!$OMP THREADPRIVATE(tau_hum_month)
1227  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
1228!$OMP THREADPRIVATE(tau_hum_week)
1229  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
1230!$OMP THREADPRIVATE(tau_t2m_month)
1231  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
1232!$OMP THREADPRIVATE(tau_t2m_week)
1233  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
1234!$OMP THREADPRIVATE(tau_tsoil_month)
1235  REAL(r_std), SAVE :: tau_soilhum_month = 20.    !! (days)     
1236!$OMP THREADPRIVATE(tau_soilhum_month)
1237  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
1238!$OMP THREADPRIVATE(tau_gpp_week)
1239  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
1240!$OMP THREADPRIVATE(tau_gdd)
1241  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
1242!$OMP THREADPRIVATE(tau_ngd)
1243  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
1244!$OMP THREADPRIVATE(coeff_tau_longterm)
1245  REAL(r_std), SAVE :: tau_longterm_max           !! (days) 
1246!$OMP THREADPRIVATE(tau_longterm_max)
1247
1248  ! 3. Coefficients of equations
1249
1250  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
1251!$OMP THREADPRIVATE(bm_sapl_carbres)
1252  REAL(r_std), SAVE :: bm_sapl_labile = 5.             !!
1253!$OMP THREADPRIVATE(bm_sapl_carbres)
1254  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
1255!$OMP THREADPRIVATE(bm_sapl_sapabove)
1256  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
1257!$OMP THREADPRIVATE(bm_sapl_heartabove)
1258  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
1259!$OMP THREADPRIVATE(bm_sapl_heartbelow)
1260  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
1261!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
1262  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
1263!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
1264  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
1265!$OMP THREADPRIVATE(init_sapl_mass_carbres)
1266  REAL(r_std), SAVE :: init_sapl_mass_labile = 5.      !!
1267!$OMP THREADPRIVATE(init_sapl_mass_carbres)
1268  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
1269!$OMP THREADPRIVATE(init_sapl_mass_root)
1270  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
1271!$OMP THREADPRIVATE(init_sapl_mass_fruit)
1272  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
1273!$OMP THREADPRIVATE(cn_sapl_init)
1274  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
1275!$OMP THREADPRIVATE(migrate_tree)
1276  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
1277!$OMP THREADPRIVATE(migrate_grass)
1278  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
1279!$OMP THREADPRIVATE(lai_initmin_tree)
1280  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
1281!$OMP THREADPRIVATE(lai_initmin_grass)
1282  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
1283!$OMP THREADPRIVATE(dia_coeff)
1284  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
1285!$OMP THREADPRIVATE(maxdia_coeff)
1286  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
1287!$OMP THREADPRIVATE(bm_sapl_leaf)
1288
1289
1290  !
1291  ! stomate_litter.f90
1292  !
1293
1294  ! 0. Constants
1295
1296  REAL(r_std), PARAMETER :: Q10 = 10.               !!
1297
1298  ! 1. Scalar
1299
1300  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
1301!$OMP THREADPRIVATE(z_decomp)
1302
1303  ! 2. Arrays
1304
1305  REAL(r_std), SAVE :: frac_soil_struct_sua = 0.4    !! corresponding to frac_soil(istructural,isurface,iabove)
1306!$OMP THREADPRIVATE(frac_soil_struct_sua)
1307  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
1308!$OMP THREADPRIVATE(frac_soil_struct_ab)
1309  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
1310!$OMP THREADPRIVATE(frac_soil_struct_sa)
1311  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
1312!$OMP THREADPRIVATE(frac_soil_struct_sb)
1313  REAL(r_std), SAVE :: frac_soil_metab_sua = 0.4    !! corresponding to frac_soil(imetabolic,iactive,iabove)
1314!$OMP THREADPRIVATE(frac_soil_metab_sua)
1315  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
1316!$OMP THREADPRIVATE(frac_soil_metab_ab)
1317  REAL(r_std), SAVE :: fungivores = 0.3    !! Fraction of decomposed litter consumed by fungivores   
1318!$OMP THREADPRIVATE(fungivores)
1319  REAL(r_std), SAVE :: frac_woody = 0.65   !! Coefficient for determining the lignin fraction of woody litter
1320!$OMP THREADPRIVATE(frac_woody)
1321  REAL(r_std), SAVE, DIMENSION(nparts) :: CN_fix = & !! C/N ratio of each plant pool (0-100, unitless)
1322       & (/ 40., 40., 40., 40., 40., 40., 40., 40., 40. /) 
1323!$OMP THREADPRIVATE(CN_fix)
1324
1325  ! 3. Coefficients of equations
1326
1327  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
1328!$OMP THREADPRIVATE(metabolic_ref_frac)
1329  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
1330!$OMP THREADPRIVATE(metabolic_LN_ratio)
1331  ! Turnover rate (yr-1) - From Parton et al., 1993
1332  REAL(r_std), SAVE :: turn_metabolic = 15           !!
1333!$OMP THREADPRIVATE(turn_metabolic)
1334  REAL(r_std), SAVE :: turn_struct = 4                !!
1335!$OMP THREADPRIVATE(turn_struct)
1336  REAL(r_std), SAVE :: turn_woody = 1.33              !! from DOFOCO
1337!$OMP THREADPRIVATE(turn_woody)
1338  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
1339!$OMP THREADPRIVATE(soil_Q10)
1340  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
1341!$OMP THREADPRIVATE(tsoil_ref)
1342  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
1343!$OMP THREADPRIVATE(litter_struct_coef)
1344  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
1345!$OMP THREADPRIVATE(moist_coeff)
1346  REAL(r_std), SAVE :: moistcont_min = 0.25  !! minimum soil wetness to limit the heterotrophic respiration
1347!$OMP THREADPRIVATE(moistcont_min)
1348
1349
1350  !
1351  ! stomate_lpj.f90
1352  !
1353
1354  ! 1. Scalar
1355
1356  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
1357!$OMP THREADPRIVATE(frac_turnover_daily)
1358
1359
1360  !
1361  ! stomate_npp.f90
1362  !
1363
1364  ! 1. Scalar
1365
1366  REAL(r_std), SAVE :: tax_max = 0.8 !! Maximum fraction of allocatable biomass used
1367                                     !! for maintenance respiration (0-1, unitless)
1368!$OMP THREADPRIVATE(tax_max)
1369
1370
1371  !
1372  ! stomate_phenology.f90
1373  !
1374
1375  ! 1. Scalar
1376
1377  LOGICAL, SAVE :: always_init = .FALSE.           !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
1378!$OMP THREADPRIVATE(always_init)
1379  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
1380!$OMP THREADPRIVATE(min_growthinit_time)
1381  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
1382                                                   !!  - for trees (0-1, unitless)
1383!$OMP THREADPRIVATE(moiavail_always_tree)
1384  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1385                                                   !! - for grass (0-1, unitless)
1386!$OMP THREADPRIVATE(moiavail_always_grass)
1387  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
1388!$OMP THREADPRIVATE(t_always)
1389  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
1390!$OMP THREADPRIVATE(t_always_add)
1391
1392  ! 3. Coefficients of equations
1393 
1394  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
1395!$OMP THREADPRIVATE(gddncd_ref)
1396  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
1397!$OMP THREADPRIVATE(gddncd_curve)
1398  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
1399!$OMP THREADPRIVATE(gddncd_offset)
1400
1401
1402  !
1403  ! stomate_prescribe.f90
1404  !
1405
1406  ! 3. Coefficients of equations
1407
1408  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
1409!$OMP THREADPRIVATE(bm_sapl_rescale)
1410
1411
1412  !
1413  ! stomate_resp.f90
1414  !
1415
1416  ! 3. Coefficients of equations
1417
1418  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
1419!$OMP THREADPRIVATE(maint_resp_min_vmax)
1420  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
1421!$OMP THREADPRIVATE(maint_resp_coeff)
1422
1423
1424  !
1425  ! stomate_som_dynamics.f90 (in stomate_soilcarbon.f90)   
1426  !
1427
1428  ! 2. Arrays
1429
1430  ! 2.1 Fixed fraction from one pool to another (or to CO2 emission)
1431
1432  REAL(r_std), SAVE :: active_to_pass_ref_frac = 0.003  !! from active pool: depends on clay content  (0-1, unitless)
1433                                                        !! corresponding to frac_carb(:,iactive,ipassive)
1434  REAL(r_std), SAVE :: surf_to_slow_ref_frac = 0.4      !! from surface pool
1435                                                        !! corresponding to frac_carb(:,isurf,islow)
1436  REAL(r_std), SAVE :: active_to_CO2_ref_frac  = 0.85   !! from active pool: depends on clay content  (0-1, unitless)
1437                                                        !! corresponding to frac_resp(:,iactive)
1438!$OMP THREADPRIVATE(active_to_CO2_ref_frac)
1439  REAL(r_std), SAVE :: slow_to_pass_ref_frac   = 0.003  !! from slow pool: depends on clay content  (0-1, unitless)
1440                                                        !! corresponding to frac_carb(:,islow,ipassive)
1441!$OMP THREADPRIVATE(slow_to_pass_ref_frac)
1442  REAL(r_std), SAVE :: slow_to_CO2_ref_frac    = 0.55   !! from slow pool (0-1, unitless)
1443                                                        !! corresponding to frac_resp(:,islow)
1444!$OMP THREADPRIVATE(slow_to_CO2_ref_frac)
1445  REAL(r_std), SAVE :: pass_to_active_ref_frac = 0.45   !! from passive pool (0-1, unitless)
1446                                                        !! corresponding to frac_carb(:,ipassive,iactive)
1447!$OMP THREADPRIVATE(pass_to_active_ref_frac)
1448  REAL(r_std), SAVE :: pass_to_slow_ref_frac   = 0.0    !! from passive pool (0-1, unitless)
1449                                                        !! corresponding to frac_carb(:,ipassive,islow)
1450!$OMP THREADPRIVATE(pass_to_slow_ref_frac)
1451
1452  ! 2.2 som carbon pools
1453
1454  REAL(r_std), SAVE :: som_init_active = 1000           !! Initial active SOM carbon (g m-2)
1455!$OMP THREADPRIVATE(som_init_active)
1456  REAL(r_std), SAVE :: som_init_slow = 3000             !! Initial slow SOM carbon (g m-2)
1457!$OMP THREADPRIVATE(som_init_slow)
1458  REAL(r_std), SAVE :: som_init_passive = 3000          !! Initial passive SOM carbon (g m-2)
1459!$OMP THREADPRIVATE(som_init_passive
1460  REAL(r_std), SAVE :: som_init_surface = 1000          !! Initial surface SOM carbon (g m-2)
1461!$OMP THREADPRIVATE(som_init_surface)
1462
1463  ! 3. Define Variable fraction from one pool to another (function of silt and clay fraction)
1464  REAL(r_std), SAVE :: active_to_pass_clay_frac     = 0.032
1465!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1466  !! residence times in carbon pools (days)
1467
1468  REAL(r_std), SAVE :: active_to_CO2_clay_silt_frac = 0.68
1469!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1470  REAL(r_std), SAVE :: slow_to_pass_clay_frac   = -0.009 
1471!$OMP THREADPRIVATE(slow_to_pass_clay_frac)
1472
1473  ! C to N target ratios of differnt pools
1474  REAL(r_std), SAVE ::  CN_target_iactive_ref  = 15. !! CN target ratio of active pool for soil min N = 0
1475!$OMP THREADPRIVATE(CN_target_iactive_ref)
1476  REAL(r_std), SAVE ::  CN_target_islow_ref    = 20. !! CN target ratio of slow pool for soil min N = 0
1477!$OMP THREADPRIVATE(CN_target_islow_ref)
1478  REAL(r_std), SAVE ::  CN_target_ipassive_ref = 10. !! CN target ratio of passive pool for soil min N = 0
1479!$OMP THREADPRIVATE(CN_target_ipassive_ref)
1480  REAL(r_std), SAVE ::  CN_target_isurface_ref = 20. !! CN target ratio of surface pool for litter nitrogen content = 0
1481!$OMP THREADPRIVATE(CN_target_isurface_ref)
1482
1483  REAL(r_std), SAVE ::  CN_target_iactive_Nmin  = -6.  !! CN target ratio change per mineral N unit (g m-2) for active pool
1484  REAL(r_std), SAVE ::  CN_target_islow_Nmin    = -4.  !! CN target ratio change per mineral N unit (g m-2) for slow pool
1485  REAL(r_std), SAVE ::  CN_target_ipassive_Nmin = -1.5 !! CN target ratio change per mineral N unit (g m-2) for passive pool
1486  REAL(r_std), SAVE ::  CN_target_isurface_pnc  = -5.  !! CN target ratio change per plant nitrogen content unit (%) for surface pool
1487  !! Turnover in SOM pools (year-1)
1488  REAL(r_std), SAVE :: som_turn_isurface    = 6.0      !! turnover of surface pool (year-1)
1489!$OMP THREADPRIVATE(som_turn_isurface)
1490  REAL(r_std), SAVE :: som_turn_iactive     = 7.3      !! turnover of active pool (year-1)
1491!$OMP THREADPRIVATE(som_turn_iactive)
1492  REAL(r_std), SAVE :: som_turn_islow       = 0.2      !! turnover of slow pool (year-1)
1493!$OMP THREADPRIVATE(som_turn_islow)
1494  REAL(r_std), SAVE :: som_turn_ipassive    = 0.0045   !! turnover of passive pool (year-1)
1495!$OMP THREADPRIVATE(som_turn_ipassive)
1496
1497
1498  REAL(r_std), SAVE :: som_turn_iactive_clay_frac = 0.75 !! clay-dependant parameter impacting on turnover rate of active pool
1499                                                         !! Tm parameter of Parton et al. 1993 (-)
1500!$OMP THREADPRIVATE(som_turn_iactive_clay_frac)
1501
1502  !
1503  ! stomate_turnover.f90
1504  !
1505
1506  ! 3. Coefficients of equations
1507
1508  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
1509!$OMP THREADPRIVATE(new_turnover_time_ref)
1510  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
1511!$OMP THREADPRIVATE(leaf_age_crit_tref)
1512  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
1513!$OMP THREADPRIVATE(leaf_age_crit_coeff)
1514
1515
1516  !
1517  ! stomate_vmax.f90
1518  !
1519 
1520  ! 1. Scalar
1521
1522  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
1523!$OMP THREADPRIVATE(vmax_offset)
1524  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1525                                                !! reaches 1 (unitless)
1526!$OMP THREADPRIVATE(leafage_firstmax)
1527  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1528                                                !! falls below 1 (unitless)
1529!$OMP THREADPRIVATE(leafage_lastmax)
1530  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1531                                                !! reaches its minimum (vmax_offset)
1532                                                !! (unitless)
1533!$OMP THREADPRIVATE(leafage_old)
1534
1535
1536  !
1537  ! nitrogen_dynamics (in stomate_soilcarbon.f90)
1538  !
1539
1540  ! 0. Constants
1541  REAL(r_std), PARAMETER :: D_air = 1.73664     !! Oxygen diffusion rate in the air = 0.07236 m2/h
1542                                               !! from Table 2 of Li et al, 2000
1543                                               !! (m**2/day)
1544
1545  REAL(r_std), PARAMETER :: C_molar_mass = 12  !! Carbon Molar mass (gC mol-1)
1546
1547  REAL(r_std), PARAMETER :: Pa_to_hPa    = 0.01      !! Conversion factor from Pa to hPa (-)
1548  REAL(r_std), PARAMETER :: V_O2         = 0.209476  !! Volumetric fraction of O2 in air (-)
1549
1550  REAL(r_std), PARAMETER :: pk_NH4 = 9.25      !! The negative logarithm of the acid dissociation constant K_NH4     
1551                                               !! See Table 4 of Li et al. 1992 and Appendix A of Zhang et al. 2002   
1552
1553                                     
1554  ! 1. Scalar
1555
1556  ! Coefficients for defining maximum porosity
1557  ! From Saxton, K.E., Rawls, W.J., Romberger, J.S., Papendick, R.I., 1986
1558  ! Estimationg generalized soil-water characteristics from texture.
1559  ! Soil Sci. Soc. Am. J. 50, 1031-1036
1560  ! Cited in Table 5 (page 444) of
1561  ! Y. Pachepsky, W.J. Rawls
1562  ! Development of Pedotransfer Functions in Soil Hydrology
1563  ! Elsevier, 23 nov. 2004 - 542 pages
1564  ! http://books.google.fr/books?id=ar_lPXaJ8QkC&printsec=frontcover&hl=fr#v=onepage&q&f=false
1565  REAL(r_std), SAVE :: h_saxton = 0.332          !! h coefficient
1566!$OMP THREADPRIVATE(h_saxton)
1567  REAL(r_std), SAVE :: j_saxton = -7.251*1e-4    !! j coefficient
1568!$OMP THREADPRIVATE(j_saxton)
1569  REAL(r_std), SAVE :: k_saxton = 0.1276         !! k coefficient
1570!$OMP THREADPRIVATE(k_saxton)
1571
1572  ! Values of the power used in the equation defining the diffusion of oxygen in soil
1573  ! from Table 2 of Li et al, 2000
1574  REAL(r_std), SAVE :: diffusionO2_power_1 = 3.33 !! (unitless)
1575!$OMP THREADPRIVATE(diffusionO2_power_1)
1576  REAL(r_std), SAVE :: diffusionO2_power_2 = 2.0  !! (unitless)
1577!$OMP THREADPRIVATE(diffusionO2_power_2)
1578
1579  ! Temperature-related Factors impacting on Oxygen diffusion rate
1580  ! From eq. 2 of Table 2 (Li et al, 2000)
1581  REAL(r_std), SAVE ::   F_nofrost = 1.2          !! (unitless)
1582!$OMP THREADPRIVATE(F_nofrost)
1583  REAL(r_std), SAVE ::   F_frost   = 0.8          !! (unitless)
1584!$OMP THREADPRIVATE(F_frost)
1585
1586  ! Coefficients used in the calculation of Volumetric fraction of anaerobic microsites
1587  ! a and b constants are not specified in Li et al., 2000
1588  ! S. Zaehle used a=0.85 and b=1 without mention to any publication
1589  REAL(r_std), SAVE ::   a_anvf    = 0.85 !! (-)
1590!$OMP THREADPRIVATE(a_anvf)
1591  REAL(r_std), SAVE ::   b_anvf    = 1.   !! (-)
1592!$OMP THREADPRIVATE(b_anvf)
1593
1594  ! Coefficients used in the calculation of the Fraction of adsorbed NH4+
1595  ! Li et al. 1992, JGR, Table 4
1596  REAL(r_std), SAVE ::   a_FixNH4 = 0.41  !! (-)
1597!$OMP THREADPRIVATE(a_FixNH4)
1598  REAL(r_std), SAVE ::   b_FixNH4 = -0.47 !! (-)
1599!$OMP THREADPRIVATE(b_FixNH4)
1600  REAL(r_std), SAVE ::   clay_max = 0.63  !! (-)
1601!$OMP THREADPRIVATE(clay_max)
1602
1603  ! Coefficients used in the calculation of the Response of Nitrification
1604  ! to soil moisture
1605  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1606  REAL(r_std), SAVE ::   fw_0 =  -0.0243  !! (-)
1607!$OMP THREADPRIVATE(fw_0)
1608  REAL(r_std), SAVE ::   fw_1 =   0.9975  !! (-)
1609!$OMP THREADPRIVATE(fw_1)
1610  REAL(r_std), SAVE ::   fw_2 =  -5.5368  !! (-)
1611!$OMP THREADPRIVATE(fw_2)
1612  REAL(r_std), SAVE ::   fw_3 =  17.651   !! (-)
1613!$OMP THREADPRIVATE(fw_3)
1614  REAL(r_std), SAVE ::   fw_4 = -12.904   !! (-)
1615!$OMP THREADPRIVATE(fw_4)
1616
1617  ! Coefficients used in the calculation of the Response of Nitrification
1618  ! to Temperature
1619  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1620  REAL(r_std), SAVE ::   ft_nit_0 =  -0.0233 !! (-)
1621!$OMP THREADPRIVATE(ft_nit_0)
1622  REAL(r_std), SAVE ::   ft_nit_1 =   0.3094 !! (-)
1623!$OMP THREADPRIVATE(ft_nit_1)
1624  REAL(r_std), SAVE ::   ft_nit_2 =  -0.2234 !! (-)
1625!$OMP THREADPRIVATE(ft_nit_2)
1626  REAL(r_std), SAVE ::   ft_nit_3 =   0.1566 !! (-)
1627!$OMP THREADPRIVATE(ft_nit_3)
1628  REAL(r_std), SAVE ::   ft_nit_4 =  -0.0272 !! (-)
1629!$OMP THREADPRIVATE(ft_nit_4)
1630
1631  ! Coefficients used in the calculation of the Response of Nitrification
1632  ! to pH
1633  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1634  REAL(r_std), SAVE ::   fph_0 = -1.2314  !! (-)
1635!$OMP THREADPRIVATE(fph_0)
1636  REAL(r_std), SAVE ::   fph_1 = 0.7347   !! (-)
1637!$OMP THREADPRIVATE(fph_1)
1638  REAL(r_std), SAVE ::   fph_2 = -0.0604  !! (-)
1639!$OMP THREADPRIVATE(fph_2)
1640
1641  ! Coefficients used in the calculation of the response of NO2 or NO
1642  ! production during nitrificationof to Temperature
1643  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 102
1644  REAL(r_std), SAVE ::   ftv_0 = 2.72   !! (-)
1645!$OMP THREADPRIVATE(ftv_0)
1646  REAL(r_std), SAVE ::   ftv_1 = 34.6   !! (-)
1647!$OMP THREADPRIVATE(ftv_1)
1648  REAL(r_std), SAVE ::   ftv_2 = 9615.  !! (-)
1649!$OMP THREADPRIVATE(ftv_2)
1650
1651  REAL(r_std), SAVE ::   k_nitrif = 0.2         !! Nitrification rate at 20 ◩C and field capacity (day-1)
1652                                                !! from Schmid et al., 2001
1653!$OMP THREADPRIVATE(k_nitrif)
1654
1655  REAL(r_std), SAVE ::   n2o_nitrif_p = 0.0006  !! Reference n2o production per N-NO3 produced g N-N2O  (g N-NO3)-1
1656                                                !! From Zhang et al., 2002 - Appendix A p. 102
1657!$OMP THREADPRIVATE(n2o_nitrif_p)
1658  REAL(r_std), SAVE ::   no_nitrif_p = 0.0025   !! Reference NO production per N-NO3 produced g N-NO  (g N-NO3)-1
1659                                                !! From Zhang et al., 2002 - Appendix A p. 102
1660!$OMP THREADPRIVATE(no_nitrif_p)
1661
1662  ! NO production from chemodenitrification
1663  ! based on Kesik et al., 2005, Biogeosciences
1664  ! Coefficients used in the calculation of the Response to Temperature
1665  REAL(r_std), SAVE ::   chemo_t0  = -31494. !! (-)
1666!$OMP THREADPRIVATE(chemo_t0)
1667  ! Coefficients use in the calculation of the Response to pH
1668  REAL(r_std), SAVE ::   chemo_ph0 = -1.62   !! (-)
1669!$OMP THREADPRIVATE(chemo_ph0)
1670  ! Coefficients used in the calculation of NO production from chemodenitrification
1671  REAL(r_std), SAVE ::   chemo_0   = 30.     !! (-)
1672!$OMP THREADPRIVATE(chemo_0)
1673  REAL(r_std), SAVE ::   chemo_1   = 16565.  !! (-)
1674!$OMP THREADPRIVATE(chemo_1)
1675
1676  ! Denitrification processes
1677  ! Li et al, 2000, JGR Table 4 eq 1, 2 and 4
1678  !
1679  ! Coefficients used in the Temperature response of
1680  ! relative growth rate of total denitrifiers - Eq. 2 Table 4 of Li et al., 2000
1681  REAL(r_std), SAVE ::   ft_denit_0 = 2.     !! (-)
1682!$OMP THREADPRIVATE(ft_denit_0)
1683  REAL(r_std), SAVE ::   ft_denit_1 = 22.5   !! (-)
1684!$OMP THREADPRIVATE(ft_denit_1)
1685  REAL(r_std), SAVE ::   ft_denit_2 = 10.    !! (-)
1686!$OMP THREADPRIVATE(ft_denit_2)
1687  !
1688  ! Coefficients used in the pH response of
1689  ! relative growth rate of total denitrifiers - Eq. 2 Table 4 of Li et al., 2000
1690  REAL(r_std), SAVE ::   fph_no3_0  = 4.25    !! (-)
1691!$OMP THREADPRIVATE(fph_no3_0)
1692  REAL(r_std), SAVE ::   fph_no3_1  = 0.5     !! (-)
1693!$OMP THREADPRIVATE(fph_no3_1)
1694  REAL(r_std), SAVE ::   fph_no_0  = 5.25     !! (-)
1695!$OMP THREADPRIVATE(fph_no_0)
1696  REAL(r_std), SAVE ::   fph_no_1  = 1.       !! (-)
1697!$OMP THREADPRIVATE(fph_no_1)
1698  REAL(r_std), SAVE ::   fph_n2o_0  = 6.25    !! (-)
1699!$OMP THREADPRIVATE(fph_n2o_0)
1700  REAL(r_std), SAVE ::   fph_n2o_1  = 1.5     !! (-)
1701!$OMP THREADPRIVATE(fph_n2o_1)
1702
1703  REAL(r_std), SAVE ::   Kn = 0.083           !! Half Saturation of N oxydes (kgN/m3)
1704                                              !! Table 4 of Li et al., 2000
1705!$OMP THREADPRIVATE(Kn)
1706
1707  ! Maximum Relative growth rate of Nox denitrifiers
1708  ! Eq.1 Table 4 Li et al., 2000
1709  REAL(r_std), SAVE ::   mu_no3_max = 0.67   !! (hour-1)
1710!$OMP THREADPRIVATE(mu_no3_max)
1711  REAL(r_std), SAVE ::   mu_no_max  = 0.34   !! (hour-1)
1712!$OMP THREADPRIVATE(mu_no_max)
1713  REAL(r_std), SAVE ::   mu_n2o_max = 0.34   !! (hour-1)
1714!$OMP THREADPRIVATE(mu_n2o_max)
1715
1716  ! Maximum growth yield of NOx denitrifiers on N oxydes
1717  ! Table 4 Li et al., 2000
1718  REAL(r_std), SAVE ::   Y_no3 = 0.401 !! (kgC / kgN)
1719!$OMP THREADPRIVATE(Y_no3)
1720  REAL(r_std), SAVE ::   Y_no  = 0.428 !! (kgC / kgN)
1721!$OMP THREADPRIVATE(Y_no)
1722  REAL(r_std), SAVE ::   Y_n2o = 0.151 !! (kgC / kgN)
1723!$OMP THREADPRIVATE(Y_n2o)
1724
1725  ! Maintenance coefficient on N oxyde
1726  ! Table 4 Li et al., 2000
1727  REAL(r_std), SAVE ::   M_no3 = 0.09   !! (kgN / kgC / hour)
1728!$OMP THREADPRIVATE(M_no3)
1729  REAL(r_std), SAVE ::   M_no  = 0.035  !! (kgN / kgC / hour)
1730!$OMP THREADPRIVATE(M_no)
1731  REAL(r_std), SAVE ::   M_n2o = 0.079  !! (kgN / kgC / hour)
1732!$OMP THREADPRIVATE(M_n2o)
1733
1734       
1735  REAL(r_std), SAVE ::   Maint_c = 0.0076    !! Maintenance coefficient of carbon (kgC/kgC/h)
1736                                        !! Table 4 Li et al., 2000
1737!$OMP THREADPRIVATE(Maint_c)
1738  REAL(r_std), SAVE ::   Yc = 0.503     !! Maximum growth yield on soluble carbon (kgC/kgC)
1739                                        !! Table 4 Li et al., 2000
1740!$OMP THREADPRIVATE(Yc)
1741
1742  !! Coefficients used in the eq. defining the response of N-emission to clay fraction (-)
1743  !! from  Table 4, Li et al. 2000
1744  REAL(r_std), SAVE ::   F_clay_0 = 0.13   
1745!$OMP THREADPRIVATE(F_clay_0)
1746  REAL(r_std), SAVE ::   F_clay_1 = -0.079
1747!$OMP THREADPRIVATE(F_clay_1)
1748
1749
1750  REAL(r_std), SAVE ::   ratio_nh4_fert = 0.875  !! Proportion of ammonium in the fertilizers (ammo-nitrate)
1751                                                 !! = 7./8. (-)
1752!$OMP THREADPRIVATE(ratio_nh4_fert)
1753
1754  ! 2. Arrays
1755  REAL(r_std), SAVE, DIMENSION(2)  :: vmax_uptake = (/ 3. , 3. /) !! Vmax of nitrogen uptake by plants
1756                                                                  !! for Ammonium (ind.1) and Nitrate (ind.2)
1757                                                                  !! (in umol (g DryWeight_root)-1 h-1)
1758                                                                  !! from  Kronzucker et al. (1995, 1996)
1759!$OMP THREADPRIVATE(vmax_uptake)
1760  REAL(r_std), SAVE, DIMENSION(2)  :: vmax_n_uptake = (/ 5.4 , 5.4 /) !! Vmax of nitrogen uptake by plants
1761                                                                      !! for Ammonium (ind.1) and Nitrate (ind.2)
1762                                                                      !! (in umol (g DryWeight_root)-1 h-1)
1763                                                                      !! from Zaehle & Friend (2010) "calibrated"
1764!$OMP THREADPRIVATE(vmax_n_uptake)
1765
1766  REAL(r_std), SAVE, DIMENSION(2)  :: K_N_min = (/ 30., 30. /)    !! [NH4+] (resp. [NO3-]) for which the Nuptake
1767                                                                  !! equals vmax/2.   (umol per litter)
1768                                                                  !! from Kronzucker, 1995
1769!$OMP THREADPRIVATE(K_N_min)
1770
1771  REAL(r_std), SAVE, DIMENSION(2)  :: low_K_N_min = (/ 0.0002, 0.0002 /) !! Rate of N uptake not associated with
1772                                                                         !! Michaelis- Menten Kinetics for Ammonium
1773                                                                         !! (ind.1) and Nitrate (ind.2)
1774                                                                         !! from Kronzucker, 1995 ((umol)-1)
1775!$OMP THREADPRIVATE(low_K_N_min)
1776
1777
1778  !! Other N-related parameters
1779  REAL(r_std), SAVE                                  :: Dmax = 0.25      !! Parameter te be clarified (what it is, units, ...)
1780                                                                         !! used in stomate_growth_fun_all
1781
1782  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
1783                                                   !! carbohydrate reserve may be used for
1784                                                   !! trees (days)
1785!$OMP THREADPRIVATE(reserve_time_tree)
1786 
1787  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
1788                                                   !! carbohydrate reserve may be used for
1789                                                   !! grasses (days)
1790!$OMP THREADPRIVATE(reserve_time_grass)
1791
1792
1793  !
1794  ! stomate_windthrow.f90
1795  !
1796
1797  ! 0. Constants
1798
1799  REAL(r_std), SAVE :: one_third = 0.333              !! This value is used on multiple occasions in
1800                                                      !! stomate_windthrow.f90
1801                                                      !!(unitless)
1802!$OMP THREADPRIVATE(one_third)
1803  REAL(r_std), SAVE :: dbh_height_standard = 1.3      !! The height where the diameter of the tree stem is
1804                                                      !! measured by default.
1805                                                      !@tex $(m)$ @endtex
1806!$OMP THREADPRIVATE(dbh_height_standard)
1807  REAL(r_std), SAVE :: dbh_height_stump = zero        !! The height where the diameter of the tree stem is
1808                                                      !! measured if the middle of the canopy is below 1.3 m.
1809                                                      !! @tex $(m)$ @endtex
1810!$OMP THREADPRIVATE(dbh_height_stump)
1811  REAL(r_std), SAVE :: snow_density = 150.0           !! Density of snow (kg/m3). It should be considered
1812                                                      !! to calculate this value for simulations during
1813                                                      !  future development.
1814!$OMP THREADPRIVATE(snow_density)
1815  REAL(r_std), SAVE :: clear_cut_max = 20000.0        !! The maximum contiguous area allowed to be clearfelled
1816                                                      !! @tex $(m^{2})$ @endtex
1817!$OMP THREADPRIVATE(clear_cut_max)
1818  REAL(r_std), SAVE :: c_surface = 0.003              !! Surface Drag Coefficient (Raupach 1994) (unitless)
1819!$OMP THREADPRIVATE(c_surface)
1820  REAL(r_std), SAVE :: c_drag = 0.3                   !! Element Drag Coefficient (Raupach 1994) (unitless)
1821!$OMP THREADPRIVATE(c_drag)
1822  REAL(r_std), SAVE :: c_displacement = 7.5           !! Used by Raupach to calculate the zero-plane displacement (Raupach 1994) (unitless)
1823!$OMP THREADPRIVATE(c_displacement)
1824  REAL(r_std), SAVE :: c_roughness = 2.0              !! Used by Raupach to calculate the surface roughness length (Raupach 1994) (unitless)
1825!$OMP THREADPRIVATE(c_roughness)
1826  REAL(r_std), SAVE :: air_density = 1.2226           !! The value of air density (kg*m-3). If needed, this can be derived dynamically from
1827                                                      !! other modules of ORCHIDEE, but considering the range of values it can hold, it is probably
1828                                                      !! not worth additional calculations for being used in WINDTHROW.
1829!$OMP THREADPRIVATE(air_density)
1830  REAL(r_std), SAVE :: f_crown_weight = 1.136         !! This factor represents the weight of the overhanging crown when the tree stem is bent.
1831                                                      !! The origin of 1.136 is described in the supplementary material of Hale et al. 2015.
1832!$OMP THREADPRIVATE(f_crown_weight)
1833
1834  INTEGER(i_std), SAVE :: wind_years = 5              !! The years used to calculate the total harvest area with in wind_years and the default is 5 years.
1835!$OMP THREADPRIVATE(wind_years)
1836
1837! 1. Scalar
1838  REAL(r_std), SAVE :: daily_max_tune=0.1155          !! This is a linear tunning factor to adjust the calculated daily maximum wind speed from forcing dataset.
1839!@OMP THREADPRIVATE(daily_max_tune)
1840
1841
1842  !
1843  ! stomate_season.f90
1844  !
1845
1846  ! 1. Scalar
1847
1848  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
1849!$OMP THREADPRIVATE(gppfrac_dormance)
1850  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
1851!$OMP THREADPRIVATE(tau_climatology)
1852  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
1853!$OMP THREADPRIVATE(hvc1)
1854  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
1855!$OMP THREADPRIVATE(hvc2)
1856  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
1857!$OMP THREADPRIVATE(leaf_frac_hvc)
1858  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
1859!$OMP THREADPRIVATE(tlong_ref_max)
1860  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
1861!$OMP THREADPRIVATE(tlong_ref_min)
1862
1863  ! 3. Coefficients of equations
1864
1865  REAL(r_std), SAVE :: ncd_max_year = 3.
1866!$OMP THREADPRIVATE(ncd_max_year)
1867  REAL(r_std), SAVE :: gdd_threshold = 5.
1868!$OMP THREADPRIVATE(gdd_threshold)
1869  REAL(r_std), SAVE :: green_age_ever = 2.
1870!$OMP THREADPRIVATE(green_age_ever)
1871  REAL(r_std), SAVE :: green_age_dec = 0.5
1872!$OMP THREADPRIVATE(green_age_dec)
1873 
1874  REAL(r_std), SAVE :: ngd_min_dormance = 120.
1875!$OMP THREADPRIVATE(ngd_min_dormance)
1876
1877  !
1878  ! sapiens_forestry.f90
1879  !
1880
1881  INTEGER(i_std), SAVE      :: ncirc = 1                !! Number of circumference classes used to calculate C allocation
1882!$OMP THREADPRIVATE(ncirc)
1883
1884  LOGICAL, SAVE             :: lbypass_cc = .FALSE.     !! Set to true for a temporary patch of a known bug, though the underlying
1885!$OMP THREADPRIVATE(lbypass_cc)
1886  LOGICAL, SAVE             :: ld_fake_height=.TRUE.    !! a flag to turn on the statements
1887!$OMP THREADPRIVATE(ld_fake_height)
1888  LOGICAL,PARAMETER         :: ld_biomass=.FALSE.       !! a flag to turn on debug statements
1889  INTEGER(i_std), SAVE      :: test_pft = 31             !! Number of PFT for which detailed output
1890!$OMP THREADPRIVATE(test_pft)
1891
1892!!! If the default value is not one, this can cause crashes in debugging for small regions.
1893  INTEGER(i_std), SAVE      :: test_grid = 1            !! Number of the grid square for which detailed output
1894!$OMP THREADPRIVATE(test_grid)
1895
1896  INTEGER(i_std), SAVE      :: nagec = 1                !! Number of age classes used to calculate C allocation
1897                                                        !! Used in forestry.f90 and lcchange.f90 - this mimics age classes
1898!$OMP THREADPRIVATE(nagec)
1899
1900  INTEGER(i_std), SAVE      :: ndia_harvest             !! The number of diameter classes used for
1901                                                        !! the wood harvest pools.
1902!$OMP THREADPRIVATE(ndia_harvest)
1903
1904  REAL(r_std), SAVE         :: max_harvest_dia          !! The largest diameter for the harvest pools to
1905                                                        !! keep track of harvested wood from forests.
1906!$OMP THREADPRIVATE(max_harvest_dia)
1907
1908  INTEGER(i_std), SAVE      :: n_pai                    !! The number of years used for the cumulative
1909                                                        !! averages of the periodic annual increment.                     
1910!$OMP THREADPRIVATE(n_pai)
1911
1912  INTEGER(i_std), SAVE      :: ntrees_profit            !! The number of trees over which the average
1913                                                        !! height is calculated to determine if the
1914                                                        !! stand will be profitable to thin.
1915!$OMP THREADPRIVATE(ntrees_profit)
1916 
1917 REAL(r_std), SAVE         :: rdi_limit_upper=1         !! The parameters for self-thinning and yield come
1918                                                        !! from different data sets and are not necsassirly
1919                                                        !! fully consistent. The forestry code was written
1920                                                        !! such that it accounts for this consistency issue.
1921                                                        !! However, we still need a parameter that gives
1922                                                        !! us the upper_rdi_harvest in case the inconsistency
1923                                                        !! occurs.
1924 !$OMP THREADPRIVATE(rdi_limit_upper)
1925
1926INTEGER, SAVE             :: species_change_force      !! This is the PFT number which is replanted after a
1927                                                       !! clearcut, if such a thing is being done.
1928                                                       !! To be used with lchange_species = .TRUE. and
1929                                                       !! lread_species_change_map = .FALSE. The
1930                                                       !! forced value is mainly useful for debugging
1931!$OMP THREADPRIVATE(species_change_force)
1932
1933INTEGER, SAVE             :: fm_change_force           !! This is the FM strategy which is used for the replant
1934                                                       !! after a clearcut, if such a thing is being done.
1935                                                       !! To be used with lchange_species = .TRUE. and
1936                                                       !! lread_desired_fm_map = .FALSE. The forced value is
1937                                                       !! mainly useful for debugging
1938!$OMP THREADPRIVATE(fm_change_force)
1939
1940 REAL(r_std), SAVE        :: min_water_stress = 0.1    !! Minimal value for wstress_fac (unitless, 0-1)
1941!$OMP THREADPRIVATE(min_water_stress)
1942
1943REAL(r_std), SAVE         :: max_delta_KF = 0.1        !! Maximum change in KF from one time step to another (m)
1944                                                       !! This is a bit arbitrary.
1945!$OMP THREADPRIVATE(max_delta_KF)
1946
1947REAL(r_std), SAVE         :: maint_from_gpp = 0.8      !! Some carbon needs to remain to support the growth, hence,
1948                                                       !! respiration will be limited. In this case resp_maint
1949                                                       !! (gC m-2 dt-1) should not be more than 80% (::maint_from_gpp)
1950                                                       !! of the GPP (gC m-2 s-1)
1951!$OMP THREADPRIVATE(maint_from_gpp)
1952 
1953  REAL(r_std), PARAMETER :: m2_to_ha = 10000.          !! Conversion from m2 to hectares
1954  REAL(r_std), PARAMETER :: ha_to_m2 = 0.0001          !! Conversion from hectares (forestry) to m2 (rest of the code)
1955  REAL(r_std), PARAMETER :: m_to_cm = 100.             !! Conversion from m to cm
1956  REAL(r_std), PARAMETER :: cm_to_m = 0.01             !! Conversion from cm to m
1957  REAL(r_std), PARAMETER :: peta_to_unit = 1.0E15      !! Convert Peta to unit
1958  REAL(r_std), PARAMETER :: tera_to_unit = 1.0E12      !! Convert Tera to unit
1959  REAL(r_std), PARAMETER :: giga_to_unit = 1.0E09      !! Convert Giga to unit
1960  REAL(r_std), PARAMETER :: mega_to_unit = 1.0E06      !! Convert Mega to unit
1961  REAL(r_std), PARAMETER :: kilo_to_unit = 1.0E03      !! Convert Kilo to unit
1962  REAL(r_std), PARAMETER :: centi_to_unit = 1.0E02     !! Convert centi to unit
1963  REAL(r_std), PARAMETER :: milli_to_unit = 1.0E-03    !! Convert milli to unit
1964  REAL(r_std), PARAMETER :: carbon_to_kilo = 2.0E-03   !! Convert g carbon to kilo biomass
1965
1966  !
1967  ! Debugging
1968  !
1969  INTEGER(i_std), SAVE :: err_act = 1                  !! There are three levels of error checking
1970                                                       !! see constantes.f90 for more details
1971!$OMP THREADPRIVATE(err_act)
1972  INTEGER(i_std), SAVE :: plev = 0                     !! print level of the subroutine ipslerr_p
1973                                                       !! (1:note, 2: warn and 3:stop)
1974!$OMP THREADPRIVATE(plev)
1975  REAL(r_std), SAVE    :: sync_threshold = 0.0001      !! The threshold above which a warning is generated when the
1976!$OMP THREADPRIVATE(sync_threshold)
1977
1978END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.