source: branches/publications/ORCHIDEE_CAN_r2290/src_parameters/constantes_var.f90 @ 7746

Last change on this file since 7746 was 2280, checked in by sebastiaan.luyssaert, 10 years ago

DEV: NOT tested yet. Committed to transfer the code between curie and asterix. Introduced diameter-based product pools

  • Property svn:keywords set to Date Revision
File size: 84.6 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  ! FLAGS
45  !
46  TYPE control_type
47    LOGICAL :: river_routing            !! activate river routing (true/false)
48    LOGICAL :: hydrol_cwrr              !! activate 11 layers hydrolgy model (true/false)
49    LOGICAL :: do_floodplains
50    LOGICAL :: do_irrigation
51    LOGICAL :: ok_sechiba               !! activate physic of the model (true/false)
52    LOGICAL :: ok_co2                   !! activate photosynthesis (true/false)
53    LOGICAL :: ok_stomate               !! activate carbon cycle (true/false)
54    LOGICAL :: ok_dgvm                  !! activate dynamic vegetation (true/false)
55    LOGICAL :: stomate_watchout         !! activate the creation of restart files for STOMATE even if STOMATE is not activated
56                                        !! (true/false)
57    LOGICAL :: ok_pheno                 !! activate the calculation of lai using stomate rather than a prescription (true/false)
58    LOGICAL :: do_land_use              !! ??? NOt clear why this is needed in the control structure
59                                        !! Seems to duplicate ok_land_cover_change (previously lcchange)
60    LOGICAL :: ok_inca                  !! activate biogenic volatile organic coumpounds ? (true/false)
61    LOGICAL :: ok_leafage               !! activate leafage? (true/false)
62    LOGICAL :: ok_radcanopy             !! use canopy radiative transfer model (true/false)
63    LOGICAL :: ok_multilayer            !! use canopy radiative transfer model with multi-layers (true/false)
64    LOGICAL :: ok_pulse_NOx             !! calculate NOx emissions with pulse (true/false)
65    LOGICAL :: ok_bbgfertil_NOx         !! calculate NOx emissions with bbg fertilizing effect (true/false)
66    LOGICAL :: ok_cropsfertil_NOx       !! calculate NOx emissions with fertilizers use (true/false)
67    LOGICAL :: forest_management        !!
68    LOGICAL :: do_new_snow_albedo       !! Use a new type of snow albedo compatible with new albedo schemes (true/false)
69    LOGICAL :: ok_functional_allocation !! Use functional allocation rather than resource limited allocation (true/false)
70    LOGICAL :: ok_cexchange             !! Use photosynthesis according to Friend et al 2010 (true/false)
71    LOGICAL :: ok_hydrol_arch           !! Use hydraulic architecture to calculate supply of water for transpiration from the
72                                        !! leaves (true/false)
73    LOGICAL :: ok_agricultural_harvest  !! Harvest the agricultural PFT's (true/false)
74    LOGICAL :: ok_constant_mortality    !! Uses a prescribed constant mortality. If not activated, mortality is a function of
75                                        !! last year's NPP (true/false)
76    LOGICAL :: ok_herbivory             !! allow herbivory (true/false)
77    LOGICAL :: ok_land_cover_change     !! activate land cover change (true/false)
78    LOGICAL :: ok_dofoco                !! Run a DOFOCO simulation (true/false)
79                                        !! This flag overrides a number of other flags if set to TRUE.
80    LOGICAL :: ok_nenerbil              !! Activate the new energy budget scheme
81    LOGICAL :: ok_gs_feedback           !! Activate water stress feedback on the stomatal conductance
82
83 END TYPE control_type
84
85  !-
86  TYPE(control_type), SAVE :: control  !! Flags that (de)activate parts of the model
87!$OMP THREADPRIVATE(control)
88  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE.  !! ORCHIDEE detects if it is coupled with a GCM or
89                                            !! just use with one driver in OFF-LINE. (true/false)
90!$OMP THREADPRIVATE(OFF_LINE_MODE)
91  CHARACTER(LEN=80), SAVE     :: restname_in       = 'NONE'                 !! Input Restart files name for Sechiba component 
92!$OMP THREADPRIVATE(restname_in)
93  CHARACTER(LEN=80), SAVE     :: restname_out      = 'sechiba_rest_out.nc'  !! Output Restart files name for Sechiba component
94!$OMP THREADPRIVATE(restname_out)
95  CHARACTER(LEN=80), SAVE     :: stom_restname_in  = 'NONE'                 !! Input Restart files name for Stomate component
96!$OMP THREADPRIVATE(stom_restname_in)
97  CHARACTER(LEN=80), SAVE     :: stom_restname_out = 'stomate_rest_out.nc'  !! Output Restart files name for Stomate component
98!$OMP THREADPRIVATE(stom_restname_out)
99
100  !
101  ! DEBUG
102  !
103  INTEGER(i_std), SAVE        :: test_pft = 27                              !! Number of PFT for which detailed output
104                                                                            !! is written to the output file. If set > 26 no extra
105                                                                            !! output is written
106
107
108
109!$OMP THREADPRIVATE(test_pft)
110  INTEGER(i_std), SAVE        :: test_grid                                  !! Number of the grid square for which detailed output
111                                                                            !! is written to the output file.
112!$OMP THREADPRIVATE(test_grid)
113
114  !
115  ! TIME
116  !
117  REAL(r_std), SAVE :: one_day  !! One day in seconds (s)
118!$OMP THREADPRIVATE(one_day)
119  REAL(r_std), SAVE :: one_year !! One year in seconds (s)
120!$OMP THREADPRIVATE(one_year)
121  REAL(r_std), PARAMETER :: one_hour = 3600.0  !! One hour in seconds (s)
122
123  ! TIME STEP
124  REAL(r_std)            :: dt_sechiba         !! Time step for in sechiba
125!$OMP THREADPRIVATE(dt_sechiba)
126
127  !
128  ! SPECIAL VALUES
129  !
130  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
131  !-
132  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
133!$OMP THREADPRIVATE(val_exp)
134  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
135  !-
136  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
137  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
138  !-
139  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
140  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
141
142
143  !
144  !  DIMENSIONING AND INDICES PARAMETERS 
145  !
146  INTEGER(i_std), PARAMETER :: ibare_sechiba = 1 !! Index for bare soil in Sechiba (unitless)
147  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for albedo in visible range (unitless)
148  INTEGER(i_std), PARAMETER :: inir = 2          !! index for albeod i near-infrared range (unitless)
149  INTEGER(i_std), PARAMETER :: n_spectralbands=2  !! number of spectral bands
150  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
151  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
152  !-
153  !! Soil
154  INTEGER(i_std), PARAMETER :: classnb = 9       !! Levels of soil colour classification (unitless)
155  !-
156  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
157  !-
158  !! litter fractions: indices (unitless)
159  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
160  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
161  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
162  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
163  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
164  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
165  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
166  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
167  INTEGER(i_std), PARAMETER :: ilabile = 9       !! Index for reserve compartment (unitless)
168  INTEGER(i_std), PARAMETER :: nparts = 9        !! Number of biomass compartments (unitless)
169  !-
170  !! indices for assimilation parameters
171  INTEGER(i_std), PARAMETER :: itmin = 1         !! Index for minimum photosynthesis temperature (assimilation parameters) (unitless)
172  INTEGER(i_std), PARAMETER :: itopt = 2         !! Index for optimal photosynthesis temperature (assimilation parameters) (unitless)
173  INTEGER(i_std), PARAMETER :: itmax = 3         !! Index for maxmimum photosynthesis temperature (assimilation parameters) (unitless)
174  INTEGER(i_std), PARAMETER :: ivcmax = 4        !! Index for vcmax (assimilation parameters) (unitless)
175  INTEGER(i_std), PARAMETER :: ivjmax = 5        !! Index for vjmax (assimilation parameters) (unitless)
176  INTEGER(i_std), PARAMETER :: npco2 = 5         !! Number of assimilation parameters (unitless)
177  !-
178  !! trees and litter: indices for the parts of heart-
179  !! and sapwood above and below the ground
180  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
181  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
182  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
183  !-
184  !! litter: indices for metabolic and structural part
185  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
186  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
187  INTEGER(i_std), PARAMETER :: iwoody = 3       !! Index for woody litter (unitless)
188  INTEGER(i_std), PARAMETER :: nlitt = 3        !! Number of levels for litter compartments (unitless)
189  !-
190  !! carbon pools: indices
191  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
192  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
193  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
194  INTEGER(i_std), PARAMETER :: ncarb = 3        !! Number of soil carbon pools (unitless)
195  !-
196  !! For isotopes and nitrogen
197  INTEGER(i_std), PARAMETER :: nelements = 1    !! Number of isotopes considered
198  INTEGER(i_std), PARAMETER :: icarbon = 1      !! Index for carbon
199  !
200  !! Indices used for analytical spin-up
201  INTEGER(i_std), PARAMETER :: nbpools = 9              !! Total number of carbon pools (unitless)
202  INTEGER(i_std), PARAMETER :: istructural_above = 1    !! Index for structural litter above (unitless)
203  INTEGER(i_std), PARAMETER :: istructural_below = 2    !! Index for structural litter below (unitless)
204  INTEGER(i_std), PARAMETER :: imetabolic_above = 3     !! Index for metabolic litter above (unitless)
205  INTEGER(i_std), PARAMETER :: imetabolic_below = 4     !! Index for metabolic litter below (unitless)
206  INTEGER(i_std), PARAMETER :: iwoody_above = 5         !! Index for woody litter above (unitless)
207  INTEGER(i_std), PARAMETER :: iwoody_below = 6         !! Index for woody litter below (unitless)
208  INTEGER(i_std), PARAMETER :: iactive_pool = 7         !! Index for active carbon pool (unitless)
209  INTEGER(i_std), PARAMETER :: islow_pool   = 8         !! Index for slow carbon pool (unitless)
210  INTEGER(i_std), PARAMETER :: ipassive_pool = 9        !! Index for passive carbon pool (unitless)
211  !
212  !! Indices for orphan fluxes
213  INTEGER(i_std), PARAMETER :: norphans = 8             !! Total number of orphan fluxes (unitless)
214  INTEGER(i_std), PARAMETER :: ivegold = 1              !! Index for veget_max before LCC
215  INTEGER(i_std), PARAMETER :: ivegnew = 2              !! Index for veget_max before LCC (includes veget_max of orphan fluxes)
216  INTEGER(i_std), PARAMETER :: igpp = 3                 !! Index for gpp_daily
217  INTEGER(i_std), PARAMETER :: ico2bm = 4               !! Index for co2_to_bm
218  INTEGER(i_std), PARAMETER :: irmain = 5               !! Index for maintenance respiration
219  INTEGER(i_std), PARAMETER :: irgrow = 6               !! Index for growth respiration
220  INTEGER(i_std), PARAMETER :: inpp = 7                 !! Index for npp_daily
221  INTEGER(i_std), PARAMETER :: irhet = 8                !! Index for total heterotrophic respiration
222  !
223  !! Indices for circumference classes (output)
224  INTEGER(i_std), PARAMETER :: ic02 = 1                 !! circumeference < 0.2 m
225  INTEGER(i_std), PARAMETER :: ic04 = 2                 !! 0.2 < circ < 0.4
226  INTEGER(i_std), PARAMETER :: ic06 = 3                 !! 0.4 < circ < 0.6
227  INTEGER(i_std), PARAMETER :: ic08 = 4                 !! 0.6 < circ < 0.8
228  INTEGER(i_std), PARAMETER :: ic10 = 5                 !! 0.8 < circ < 1.0
229  INTEGER(i_std), PARAMETER :: ic12 = 6                 !! 1.0 < circ < 1.2
230  INTEGER(i_std), PARAMETER :: ic14 = 7                 !! 1.2 < circ < 1.4
231  INTEGER(i_std), PARAMETER :: ic16 = 8                 !! 1.4 < circ < 1.6
232  INTEGER(i_std), PARAMETER :: ic18 = 9                 !! 1.6 < circ < 1.8
233  INTEGER(i_std), PARAMETER :: ic20 = 10                !! 1.8 < circ < 2.0
234  INTEGER(i_std), PARAMETER :: ic222 = 11               !! circ > 2 m
235  INTEGER(i_std), PARAMETER :: icpo = 12                !! poles, circumference <0.235 m
236  INTEGER(i_std), PARAMETER :: icsw = 13                !! small wood, 0.235 < circ < 0.705
237  INTEGER(i_std), PARAMETER :: icmw = 14                !! medium wood, 0.705 < circ < 1.175
238  INTEGER(i_std), PARAMETER :: iclw = 15                !! large wood, 1.175 < circ
239
240  !
241  ! These next sets of parameters are now used for both circ_class_kill and
242  ! for the harvest_pool.  One source of confusion is what to do with trees that
243  ! die from self-thinning or forest dieoffs.  These happen in all forests, regardless
244  ! of management strategy.  I decided to put death of this kind into ifm_none, since
245  ! it is the only type of mortality found in an unmanaged forest.  If the mortality
246  ! does not kill the whole forest (e.g. self thinning), it goes into icut_thin.  If it
247  ! does (forest dieoff), it goes into icut_clear.  The biomass is killed in lpj_gap.
248
249  !! Indices used for forest management strategies
250  INTEGER(i_std), PARAMETER :: nfm_types = 6             !! The total number of forest management strategies we can use
251  INTEGER(i_std), PARAMETER :: ifm_none = 1              !! No human intervention in the forests.
252  INTEGER(i_std), PARAMETER :: ifm_thin = 2              !! Regular thinning and harvesting of wood based on RDI.
253  INTEGER(i_std), PARAMETER :: ifm_cop = 3               !! Coppicing for fuelwood.
254  INTEGER(i_std), PARAMETER :: ifm_src = 4               !! Short rotation coppices for biomass production.
255  INTEGER(i_std), PARAMETER :: ifm_crop = 5              !! Crop harvest
256  INTEGER(i_std), PARAMETER :: ifm_grass = 6             !! Grazing or cutting
257  !! Indices used for harvest pools
258  INTEGER(i_std), PARAMETER :: ncut_times = 9            !! The total number of times when trees are cut and wood harvested.
259  INTEGER(i_std), PARAMETER :: icut_clear = 1            !! A clearcut where all biomass is removed.
260  INTEGER(i_std), PARAMETER :: icut_thin = 2             !! Thinning of biomass to reduce the number of trees.
261  INTEGER(i_std), PARAMETER :: icut_lcc_wood = 3         !! Wood harvest following land cover change (LCC)
262  INTEGER(i_std), PARAMETER :: icut_lcc_res = 4          !! Site clearing, removal of the stumps and branches following LCC
263  INTEGER(i_std), PARAMETER :: icut_crop = 5             !! Crop harvest
264  INTEGER(i_std), PARAMETER :: icut_grass = 6            !! Grazing or cutting
265  INTEGER(i_std), PARAMETER :: icut_cop1 = 7             !! The first coppice cut
266  INTEGER(i_std), PARAMETER :: icut_cop2 = 8             !! The second (and subsequent) coppice cut
267  INTEGER(i_std), PARAMETER :: icut_cop3 = 9             !! The last coppice cut (only for SRC)
268
269  !! Indices used to define the product pools
270  INTEGER(i_std), PARAMETER :: nshort = 1                !! Length in years of the short-lived product pool (GE 1)
271  INTEGER(i_std), PARAMETER :: nmedium = 10              !! Length in years of the medium-lived product pool (GT 4)
272  INTEGER(i_std), PARAMETER :: nlong = 100               !! Length in years of the long-lived product pool (GT 4)
273
274  !! Indices used to check the mass balance closure
275  INTEGER(i_std), PARAMETER :: nmbcomp = 5               !! The total nomber of components in our mass balance check
276  INTEGER(i_std), PARAMETER :: iatm2land = 1             !! atmosphere to land fluxes such as GPP and co2_2_bm
277  INTEGER(i_std), PARAMETER :: iland2atm = 2             !! land to atmosphere fluxes such as Rh, Ra and product decomposition
278  INTEGER(i_std), PARAMETER :: ilat2out = 3              !! outgoing lateral flux i.e. DOC leaching for the litter routine
279  INTEGER(i_std), PARAMETER :: ilat2in = 4               !! incoming lateral flux i.e. N deposition for the land
280  INTEGER(i_std), PARAMETER :: ipoolchange = 5           !! change in pool size i.e. change in biomass
281
282  !! Indices used for warning tracking
283  INTEGER(i_std), PARAMETER :: nwarns = 1                !! The total number of warnings we track
284  INTEGER(i_std), PARAMETER :: iwphoto = 1               !! A warning about division by zero in photosynthesis
285  !
286  ! NUMERICAL AND PHYSICS CONSTANTS
287  !
288
289  !-
290  ! 1. Mathematical and numerical constants
291  !-
292  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
293  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
294  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
295  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
296  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
297  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
298  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
299  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
300  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
301  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
302  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
303  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
304  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
305
306  !-
307  ! 2 . Physics
308  !-
309  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
310  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
311  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
312  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! Freezing point (K)
313  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
314  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
315  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
316  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
317  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
318  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
319  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
320  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
321                                                            !! of dry air (unitless)
322  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
323  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
324  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
325       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
326  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
327  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
328                                                            !! vapor minus 1(unitless) 
329  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
330                                                            !! minus 1 (unitless)
331  REAL(r_std), PARAMETER :: rho_h2o= 0.9991_r_std           !! Density of water at 15°C (g cm-3)                       
332  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
333  REAL(r_std), PARAMETER :: ct_karman = 0.35_r_std          !! Van Karmann Constant (unitless)
334  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
335  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
336  REAL(r_std), PARAMETER :: R = 8.314                       !! Ideal gas constant (J.mol^{-1}.K^{-1})
337  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gasconstant (J.mol^{-1}.K^{-1})
338  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
339
340
341  !-
342  ! 3. Climatic constants
343  !-
344  !! Constantes of the Louis scheme
345  REAL(r_std), PARAMETER :: cb = 5._r_std         !! Constant of the Louis scheme (unitless);
346                                                  !! reference to Louis (1979)
347  REAL(r_std), PARAMETER :: cc = 5._r_std         !! Constant of the Louis scheme (unitless);
348                                                  !! reference to Louis (1979)
349  REAL(r_std), PARAMETER :: cd = 5._r_std         !! Constant of the Louis scheme (unitless);
350                                                  !! reference to Louis (1979)
351  !-
352  REAL(r_std), PARAMETER :: rayt_cste = 125.      !! Constant in the computation of surface resistance (W.m^{-2})
353  REAL(r_std), PARAMETER :: defc_plus = 23.E-3    !! Constant in the computation of surface resistance (K.W^{-1})
354  REAL(r_std), PARAMETER :: defc_mult = 1.5       !! Constant in the computation of surface resistance (K.W^{-1})
355
356  !-
357  ! 4. Soil thermodynamics constants
358  !-
359  ! Look at constantes_soil.f90
360
361  !-
362  ! 5. Unit convertions
363  !-
364  REAL(r_std), PARAMETER :: ha_to_m2 = 0.0001       !! Conversion from hectares (forestry) to m2 (rest of the code)
365  REAL(r_std), PARAMETER :: m2_to_ha = 10000.       !! Conversion from m2 to hectares
366  REAL(r_std), PARAMETER :: m_to_cm = 100.          !! Conversion from m to cm
367  REAL(r_std), PARAMETER :: peta_to_unit = 1.0E15   !! Convert Peta to unit
368  REAL(r_std), PARAMETER :: tera_to_unit = 1.0E12   !! Convert Tera to unit
369  REAL(r_std), PARAMETER :: giga_to_unit = 1.0E09   !! Convert Giga to unit
370  REAL(r_std), PARAMETER :: mega_to_unit = 1.0E06   !! Convert Mega to unit
371  REAL(r_std), PARAMETER :: kilo_to_unit = 1.0E03   !! Convert Kilo to unit
372  REAL(r_std), PARAMETER :: centi_to_unit = 1.0E02  !! Convert centi to unit
373  REAL(r_std), PARAMETER :: milli_to_unit = 1.0E-03 !! Convert milli to unit
374  REAL(r_std), PARAMETER :: carbon_to_kilo = 2.0E-03!! Convert g carbon to kilo biomass
375
376  !
377  ! OPTIONAL PARTS OF THE MODEL
378  !
379  LOGICAL, SAVE     :: long_print = .false.       !! To set for more printing
380!$OMP THREADPRIVATE(long_print)
381  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
382                                                  !! we provide here a way to catch that in the calling procedure.
383                                                  !! (from Jan Polcher)(true/false)
384  LOGICAL, SAVE     :: almaoutput                 !! Selects the type of output for the model.(true/false)
385                                                  !! Value is read from run.def in intersurf_history
386!$OMP THREADPRIVATE(almaoutput)
387
388  !
389  ! DIVERSE
390  !
391  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
392                                                           ! Compatibility with Nicolas Viovy driver.
393!$OMP THREADPRIVATE(stomate_forcing_name)
394  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
395                                                           ! Compatibility with Nicolas Viovy driver.
396!$OMP THREADPRIVATE(stomate_Cforcing_name)
397  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
398!$OMP THREADPRIVATE(forcing_id)
399
400
401
402
403                         !------------------------!
404                         !  SECHIBA PARAMETERS    !
405                         !------------------------!
406 
407
408  !
409  ! GLOBAL PARAMETERS   
410  !
411  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
412!$OMP THREADPRIVATE(min_wind)
413  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occures (kg.m^{-2})
414!$OMP THREADPRIVATE(snowcri)
415  INTEGER(i_std), SAVE        :: jnlvls = 1                                 !! Number of levels in the multilayer energy budget scheme
416
417  !
418  ! FLAGS ACTIVATING SUB-MODELS
419  !
420! +++CHECK+++
421! Logical flags that affect the flow of the code should
422! be stored in the control-structure
423
424!!$ Moved to control-structure!!$ Moved to control-structure
425!!$  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
426!!$ !$OMP THREADPRIVATE(ok_herbivores)
427!!$  LOGICAL, SAVE :: lpj_gap_const_mort = .TRUE. !! constant moratlity (true/false)
428!!$ !$OMP THREADPRIVATE(lpj_gap_const_mort)
429!!$  LOGICAL, SAVE :: lcchange = .FALSE.      !! Land cover change flag (true/false)
430!!$ !$OMP THREADPRIVATE(lcchange)
431!!$ LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
432!!$ !$OMP THREADPRIVATE(harvest_agri)
433
434  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
435!$OMP THREADPRIVATE(treat_expansion)
436  LOGICAL, SAVE :: disable_fire = .FALSE.      !! flag that disable fire (true/false)
437!$OMP THREADPRIVATE(disable_fire)
438  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
439!$OMP THREADPRIVATE(spinup_analytic)
440
441  !
442  ! CONFIGURATION VEGETATION
443  !
444  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
445!$OMP THREADPRIVATE(agriculture)
446  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
447!$OMP THREADPRIVATE(impveg)
448  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
449!$OMP THREADPRIVATE(impsoilt)
450  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
451!$OMP THREADPRIVATE(read_lai)
452  LOGICAL, SAVE :: old_lai = .FALSE.       !! Flag for the old LAI map interpolation (SHOULD BE DROPED ??)(true/false)
453!$OMP THREADPRIVATE(old_lai)
454  LOGICAL, SAVE :: old_veget = .FALSE.     !! Flag to use the old vegetation Map interpolation (SHOULD BE DROPED ?)(true/false)
455!$OMP THREADPRIVATE(old_veget)
456  LOGICAL, SAVE :: land_use = .TRUE.       !! flag to account or not for Land Use  (true/false)
457!$OMP THREADPRIVATE(land_use)
458  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
459!$OMP THREADPRIVATE(veget_reinit)
460! +++++++++++
461
462  !
463  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
464  !
465  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
466!$OMP THREADPRIVATE(max_snow_age)
467  REAL(r_std), SAVE :: snow_trans = 0.3_r_std   !! Transformation time constant for snow (m)
468!$OMP THREADPRIVATE(snow_trans)
469  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
470!$OMP THREADPRIVATE(sneige)
471  REAL(r_std), SAVE :: maxmass_glacier = 3000.  !! The maximum mass of a glacier (kg.m^{-2})
472!$OMP THREADPRIVATE(maxmass_glacier)
473
474  !
475  ! PARAMETERS USED BY ALBEDO
476  !
477  CHARACTER(LEN=30), SAVE                 :: albedo_type          !! This stores the type of albedo we are using
478!$OMP THREADPRIVATE(albedo_type)
479  LOGICAL, SAVE                           :: do_new_snow_albedo   !! If true, we use the snow albedo of CLM3 which
480                                                                  !! distinguishes between diffuse, direct, NIR, and VIS
481!$OMP THREADPRIVATE(do_new_snow_albedo)
482  INTEGER(i_std), PARAMETER               :: nlevels = 1          !! Number of levels in the canopy used in the albedo
483                                                                  !! calculation and the energy budget for the Pinty
484                                                                  !! two-stream model
485!$OMP THREADPRIVATE(nlevels)
486
487  INTEGER(i_std), SAVE                    :: nlevels_photo        !! Number of levels in the canopy used in the photosynthesis
488                                                                  !! routine per level dictacted by nlevels.  For example, if
489                                                                  !! if nlevels = 2 and nlevels_photo = 3, the photosynthesis
490                                                                  !! will be calculated for 2*3=6 total levels.
491!$OMP THREADPRIVATE(nlevels_photo)
492  INTEGER(i_std), SAVE                    :: nlevels_tot          !! Total number of levels, including photosythensis and energy
493!$OMP THREADPRIVATE(nlevels_tot)
494
495  INTEGER(i_std), SAVE                    :: nlev_top             !! Maximum number of canopy levels that are used to construct the "top"
496                                                                  !! layer of the canopy. The top layer is used in the calculation
497                                                                  !! transpiration.
498!$OMP THREADPRIVATE(nlev_top)
499
500!  REAL(r_std), PARAMETER, DIMENSION (nlevels)    :: z_level = (/ 0.0, 0.5, 1.0, 1.5, 2.0, 2.5, 3.0, 3.5, 4.0, 4.5/)                                              !! The height of the bottom of each canopy layer
501  REAL(r_std), PARAMETER, DIMENSION (nlevels)    :: z_level = (/ 0.0 /)                                              !! The height of the bottom of each canopy layer
502!  REAL(r_std), PARAMETER, DIMENSION (nlevels)    :: z_level = (/ 0.0, 1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0/)                                              !! The height of the bottom of each canopy layer
503                                                                     !! @tex $(m)$ @endtex
504!$OMP THREADPRIVATE(z_level)
505
506  ! Parameters for the albedo optimization, only used with Pinty's scheme and more than one layer
507  ! These are all somewhat arbitrary
508  !
509  REAL(r_std), SAVE                       ::  step_size_min       !! the value of the optimization step size below which
510                                                                  !! we give up and say it will not converge
511!$OMP THREADPRIVATE(step_size_min)
512  REAL(r_std), SAVE                       ::  step_size_scale     !! the scale factor of the optimization step size
513!$OMP THREADPRIVATE(step_size_scale)
514  REAL(r_std), SAVE                       ::  converged_limit     !! the value of the optimization function below which
515                                                                  !! the optimization is deemed converged
516!$OMP THREADPRIVATE(converged_limit)
517  INTEGER(i_std), SAVE                    ::  max_steps           !! the maximum number of optimization steps we try
518!$OMP THREADPRIVATE(max_steps)
519
520  !
521  ! Parameters for determining the effective LAI for use in Pinty's albedo scheme
522  !
523  REAL(r_std), SAVE                       ::  laieff_solar_angle  !! the zenith angle of the sun which determines our effective LAI
524                                                                  !! Pinty et al recommend a value of 60 degrees for this regadless of the true
525                                                                  !! solar zenith angle
526!$OMP THREADPRIVATE(laieff_solar_angle)
527  REAL(r_std), SAVE                       ::  laieff_zero_cutoff   ! an arbitrary cutoff to prevent too low of values from being passed to
528                                                                  ! routines in the calculation of the effective LAI
529!$OMP THREADPRIVATE(laieff_zero_cutoff)
530  INTEGER(i_std),PARAMETER                :: ndist_types=6       ! the number of distributions we need in the LAI effective routines
531  INTEGER(i_std),PARAMETER                :: iheight=1         ! the tree height distribution
532  INTEGER(i_std),PARAMETER                :: idiameter=2       ! the trunk diameter distribution
533  INTEGER(i_std),PARAMETER                :: icnvol=3          ! the crown volume distribution
534  INTEGER(i_std),PARAMETER                :: icnarea=4         ! the crown area distribution
535  INTEGER(i_std),PARAMETER                :: icndiaver=5       ! the verticle crown diameter distribution
536  INTEGER(i_std),PARAMETER                :: icndiahor=6       ! the horizontal crown diameter distribution
537
538!+++++ DEBUG ++++
539  REAL(r_std), SAVE                       ::  laieff_set_value_upper
540!$OMP THREADPRIVATE(laieff_set_value_upper)
541  REAL(r_std), SAVE                       ::  laieff_set_value_lower
542!$OMP THREADPRIVATE(laieff_set_value_lower)
543  REAL(r_std), SAVE                       ::  laieff_theta
544!$OMP THREADPRIVATE(laieff_theta)
545  ! These flags are all related to debugging.
546  LOGICAL,PARAMETER                       :: ld_warn=.FALSE.      ! a flag to turn on various warnings
547  LOGICAL,PARAMETER                       :: ld_stop=.FALSE.      ! a flag to turn on some stop statements.
548                                                                  ! Right now these are in allocation, and
549                                                                  ! some of them were deemed to be
550                                                                  ! not necessary to kill the code.
551  LOGICAL,PARAMETER                       :: ld_forestry=.FALSE.  ! a flag to turn on debug statements
552                                                                  ! related to forestry
553  LOGICAL,PARAMETER                       :: ld_biomass=.FALSE.   ! a flag to turn on debug statements
554                                                                  ! related to biomass
555  LOGICAL,PARAMETER                       :: ld_albedo=.FALSE.    ! a flag to turn on debug statements
556                                                                  ! related to albedo
557
558  LOGICAL,PARAMETER                       :: ld_alloc=.FALSE.     ! a flag to turn on debug statements
559
560                                                                  ! in functional allocation
561  LOGICAL,PARAMETER                       :: ld_trnov=.FALSE.     ! a flag to turn on debug statements
562                                                                  ! in turnover prognostic
563  LOGICAL,PARAMETER                       :: ld_lcc=.FALSE.       ! a flag to turn on debug statements
564                                                                  ! in function land cover
565  LOGICAL,PARAMETER                       :: ld_laieff=.FALSE.    ! a flag to turn on debug statements
566                                                                  ! related to effective LAI
567  LOGICAL,PARAMETER                       :: ld_massbal=.FALSE.   ! a flag to turn on debug statements
568                                                                  ! related to mass balance closure
569  LOGICAL,PARAMETER                       :: ld_hydrolarch=.FALSE.! a flag to turn on debug statements
570  LOGICAL,PARAMETER                       :: ld_vmax=.FALSE.      ! a flag to turn on debug statements
571  LOGICAL,PARAMETER                       :: ld_photo=.FALSE.     ! a flag to turn on debug statements
572                                                                  ! in photosynthesis
573  LOGICAL,PARAMETER                       :: ld_gstest=.FALSE.     ! a temperal flage to write gs/rveget
574  LOGICAL,PARAMETER                       :: ld_pheno=.FALSE.     ! a flag to turn on debug statements
575                                                                  ! in phenology
576  LOGICAL,PARAMETER                       :: ld_presc=.FALSE.     ! a flag to turn on debug statements
577                                                                  ! in prescribe
578  LOGICAL,PARAMETER                       :: ld_enerbil=.FALSE.   ! a flag to turn on debug statements
579                                                                  ! in the energy budget
580  LOGICAL,PARAMETER                       :: ld_coupled=.FALSE.   ! a flag to turn on debug statements
581                                                                  ! in the coupling
582  LOGICAL,PARAMETER                       :: ld_kill=.FALSE.      ! a flag to turn on debug statements
583                                                                  ! related to plant mortality
584  LOGICAL,PARAMETER                       :: ld_agec=.FALSE.      ! a flag to turn on debug statements
585                                                                  ! related to age classes
586  LOGICAL,PARAMETER                       :: ld_date=.FALSE.      ! writes time stamp to output file
587                                                                  ! used in stomate
588  LOGICAL,PARAMETER                       :: ld_wstress=.FALSE.   ! a flag to turn on relevant write
589                                                                  ! to debug the waterstress calculated
590                                                                  ! in sechiba and used in stomate
591
592  ! JR flags
593  !+++CHECK+++
594  !If this flag really does what the comment text is saying
595  ! it should be defined in intersurf as an ok% flag because
596  ! it strongly affects the flow of the model
597  LOGICAL,PARAMETER                       :: jr_enerbil = .TRUE.    ! set this to TRUE to activate the new
598                                                                    !  energy budget code
599  !+++++++++++
600  LOGICAL,PARAMETER                       :: james_write = .FALSE.  ! toggle for the write statements within
601                                                                    !  enerbil
602
603!+++++++++
604
605  !
606  ! Hydraulic architecture
607  !
608  REAL(r_std), SAVE, DIMENSION(2)         :: a_viscosity = (/0.556, 0.022/) !! Empirical parameters to adjust the resistance of fine
609                                                                            !! root and sapwood to the temperature dependency of the
610                                                                            !! viscosity of water Cochard et al 2000
611!$OMP THREADPRIVATE(a_viscosity)
612 
613
614  !
615  ! BVOC : Biogenic activity  for each age class
616  !
617  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
618                                                                                       !! age class : isoprene (unitless)
619!$OMP THREADPRIVATE(iso_activity)
620  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
621                                                                                       !! age class : methanol (unnitless)
622!$OMP THREADPRIVATE(methanol_activity)
623
624  !
625  ! condveg.f90
626  !
627
628  ! 1. Scalar
629
630  ! 1.1 Flags used inside the module
631
632  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
633                                            !! albedo (see header of subroutine)
634                                            !! (true/false)
635!$OMP THREADPRIVATE(alb_bare_model)
636  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
637                                            !! (see header of subroutine). 
638                                            !! (true/false)
639!$OMP THREADPRIVATE(impaze)
640  LOGICAL, SAVE :: z0cdrag_ave = .TRUE.     !! Chooses between two methods to calculate the
641                                            !! grid average of the roughness (see header of subroutine)   
642                                            !! (true/false)
643!$OMP THREADPRIVATE(z0cdrag_ave)
644  ! 1.2 Others
645
646  REAL(r_std), SAVE :: z0_over_height = un/16.           !! Factor to calculate roughness height from
647                                                         !! vegetation height (unitless)   
648!$OMP THREADPRIVATE(z0_over_height)
649  REAL(r_std), SAVE :: height_displacement = 0.75        !! Factor to calculate the zero-plane displacement
650                                                         !! height from vegetation height (m)
651!$OMP THREADPRIVATE(height_displacement)
652  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
653!$OMP THREADPRIVATE(z0_bare)
654  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
655!$OMP THREADPRIVATE(z0_ice)
656  REAL(r_std), SAVE :: tcst_snowa = 5.0                  !! Time constant of the albedo decay of snow (days)
657!$OMP THREADPRIVATE(tcst_snowa)
658  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
659!$OMP THREADPRIVATE(snowcri_alb)
660  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
661!$OMP THREADPRIVATE(fixed_snow_albedo)
662  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
663!$OMP THREADPRIVATE(z0_scal)
664  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
665                                                         !! displacement height (m) (imposed)
666!$OMP THREADPRIVATE(roughheight_scal)
667  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
668!$OMP THREADPRIVATE(emis_scal)
669  ! 2. Arrays
670
671  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
672!$OMP THREADPRIVATE(alb_deadleaf)
673  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
674!$OMP THREADPRIVATE(alb_ice)
675  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! Albedo values for visible and near-infrared
676                                                                     !! used imposed (unitless)
677!$OMP THREADPRIVATE(albedo_scal)
678  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
679       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
680                                                          !! dry soil albedo values in visible range
681!$OMP THREADPRIVATE(vis_dry)
682  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
683       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
684                                                          !! dry soil albedo values in near-infrared range
685!$OMP THREADPRIVATE(nir_dry)
686  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
687       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
688                                                          !! wet soil albedo values in visible range
689!$OMP THREADPRIVATE(vis_wet)
690  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
691       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
692                                                          !! wet soil albedo values in near-infrared range
693!$OMP THREADPRIVATE(nir_wet)
694  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
695       &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:
696                                                                   !! Averaged of wet and dry soil albedo values
697                                                                   !! in visible and near-infrared range
698!$OMP THREADPRIVATE(albsoil_vis)
699  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
700       &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:
701                                                                !! Averaged of wet and dry soil albedo values
702                                                                !! in visible and near-infrared range
703!$OMP THREADPRIVATE(albsoil_nir)
704  REAL(r_std) :: alb_threshold = 0.0000000001_r_std      !! A threshold for the iteration of the
705                                                          !! multilevel albedo.  Could be externalised.
706                                                          !! Fairly arbitrary, although if a level has
707                                                          !! no LAI the absorption often ends up being
708                                                          !! equal to this value, so it should not
709                                                          !! be high.
710!$OMP THREADPRIVATE(alb_threshold)
711
712  !
713  ! diffuco.f90
714  !
715
716  ! 0. Constants
717
718  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
719                                                     !! of dry air (unitless)
720  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
721  REAL(r_std), PARAMETER :: std_ci_frac = 0.667      !!
722  REAL(r_std), PARAMETER :: alpha_j = 0.8855         !! Quantum yield of RuBP regeneration
723  REAL(r_std), PARAMETER :: curve_assim = 0.7        !! Curvature of the quantum response (unitless)
724  REAL(r_std), PARAMETER :: WJ_coeff1 = 4.5          !! First coefficient for calculating the generation-limited rate RuBP (unitless)
725  REAL(r_std), PARAMETER :: WJ_coeff2 = 10.5         !! Second coefficient for calculating the generation-limited rate RuBP (unitless)
726  REAL(r_std), PARAMETER :: Vc_to_Rd_ratio = 0.011   !!
727  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
728  REAL(r_std), PARAMETER :: mmol_to_m_1 = 0.0244     !!
729  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
730  REAL(r_std), PARAMETER :: W_to_mmol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
731
732  ! 1. Scalar
733
734  INTEGER(i_std), SAVE :: nlai = 20             !! Number of LAI levels (unitless)
735!$OMP THREADPRIVATE(nlai)
736  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
737!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
738  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
739!$OMP THREADPRIVATE(laimax)
740  REAL(r_std), SAVE :: xc4_1 = 0.83             !! Factor in the first Collatz equation for C4 plants (unitless)
741!$OMP THREADPRIVATE(xc4_1)
742  REAL(r_std), SAVE :: xc4_2 = 0.93             !! Factor in the second Collatz equation for C4 plants (unitless)
743!$OMP THREADPRIVATE(xc4_2)
744  LOGICAL, SAVE :: downregulation_co2 = .FALSE.            !! Set to .TRUE. if you want CO2 downregulation.
745!$OMP THREADPRIVATE(downregulation_co2)
746  REAL(r_std), SAVE :: downregulation_co2_baselevel = 280. !! CO2 base level (ppm)
747!$OMP THREADPRIVATE(downregulation_co2_baselevel)
748  LOGICAL, SAVE :: lscale_lcc_nobio = .FALSE.   !! Set to .TRUE. if you want to scale new land cover maps
749                                                !! (be careful with this.  Please check the documentation)
750!$OMP THREADPRIVATE(lscale_lcc_nobio)
751  LOGICAL, SAVE :: lignore_lcc_stops = .FALSE.  !! Set to .TRUE. if you want the code to keep running past
752                                                !! a few places in land cover change where it would ordinarily
753                                                !! stop.  Only use in very specific cases!
754!$OMP THREADPRIVATE(lignore_lcc_stops)
755
756  ! 3. Coefficients of equations
757
758  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
759!$OMP THREADPRIVATE(lai_level_depth)
760  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
761!$OMP THREADPRIVATE(Oi)
762
763  REAL(r_std), SAVE :: x1_coef =  0.177        !! Multiplicative factor for calculating the pseudo first order rate constant
764                                               !! of assimilation response to co2 kt (unitless)
765!$OMP THREADPRIVATE(x1_coef)
766  REAL(r_std), SAVE :: x1_Q10 =  0.069         !! Exponential factor in the equation defining kt (unitless)
767!$OMP THREADPRIVATE(x1_Q10)
768  REAL(r_std), SAVE :: quantum_yield =  0.092  !!
769!$OMP THREADPRIVATE(quantum_yield)
770  REAL(r_std), SAVE :: kt_coef = 0.7           !! Multiplicative factor in the equation defining kt (unitless)
771!$OMP THREADPRIVATE(kt_coef)
772  REAL(r_std), SAVE :: kc_coef = 39.09         !! Multiplicative factor for calculating the Michaelis-Menten
773                                               !! coefficient Kc (unitless)
774!$OMP THREADPRIVATE(kc_coef)
775  REAL(r_std), SAVE :: Ko_Q10 = 0.085          !! Exponential factor for calculating the Michaelis-Menten coefficients
776                                               !! Kc and Ko (unitless)
777!$OMP THREADPRIVATE(Ko_Q10)
778  REAL(r_std), SAVE :: Oa = 210000.            !! Intercellular concentration of O2 (ppm)
779!$OMP THREADPRIVATE(Oa)
780  REAL(r_std), SAVE :: Ko_coef =  2.412        !! Multiplicative factor for calculating the Michaelis-Menten coefficient Ko (unitless)
781!$OMP THREADPRIVATE(Ko_coef)
782  REAL(r_std), SAVE :: CP_0 = 42.              !! Multiplicative factor for calculating the CO2 compensation point CP (unitless)
783!$OMP THREADPRIVATE(CP_0)
784  REAL(r_std), SAVE :: CP_temp_coef = 9.46     !! Exponential factor for calculating the CO2 compensation point CP (unitless)
785!$OMP THREADPRIVATE(CP_temp_coef)
786  REAL(r_std), SAVE :: CP_temp_ref = 25.       !! Reference temperature for the CO2 compensation point CP (C)
787!$OMP THREADPRIVATE(CP_temp_ref)
788  !
789  REAL(r_std), SAVE, DIMENSION(2) :: rt_coef = (/ 0.8, 1.3 /)    !!
790!$OMP THREADPRIVATE(rt_coef)
791  REAL(r_std), SAVE, DIMENSION(2) :: vc_coef = (/ 0.39, 0.3 /)   !!
792!$OMP THREADPRIVATE(vc_coef)
793  !
794  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
795  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
796!$OMP THREADPRIVATE(dew_veg_poly_coeff)
797
798  !
799  ! slowproc.f90
800  !
801
802  ! 1. Scalar
803
804  INTEGER(i_std), SAVE :: veget_year_orig = 0        !!  first year for landuse (number)
805!$OMP THREADPRIVATE(veget_year_orig)
806  REAL(r_std), SAVE :: clayfraction_default = 0.2    !! Default value for clay fraction (0-1, unitless)
807!$OMP THREADPRIVATE(clayfraction_default)
808  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
809!$OMP THREADPRIVATE(min_vegfrac)
810  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
811!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
812 
813  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
814!$OMP THREADPRIVATE(stempdiag_bid)
815
816
817                           !-----------------------------!
818                           !  STOMATE AND LPJ PARAMETERS !
819                           !-----------------------------!
820
821
822  !
823  ! lpj_constraints.f90
824  !
825 
826  ! 1. Scalar
827
828  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
829                                           !! regeneration (vernalization) (years)
830!$OMP THREADPRIVATE(too_long)
831
832
833  !
834  ! lpj_establish.f90
835  !
836
837  ! 1. Scalar
838
839  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (0-1, unitless)
840!$OMP THREADPRIVATE(estab_max_tree)
841  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (0-1, unitless)
842!$OMP THREADPRIVATE(estab_max_grass)
843 
844  ! 3. Coefficients of equations
845
846  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
847!$OMP THREADPRIVATE(establish_scal_fact)
848  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
849!$OMP THREADPRIVATE(max_tree_coverage)
850  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
851!$OMP THREADPRIVATE(ind_0_estab)
852
853
854  !
855  ! lpj_fire.f90
856  !
857
858  ! 1. Scalar
859
860  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
861!$OMP THREADPRIVATE(tau_fire)
862  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
863                                                !! below which iginitions extinguish
864                                                !! @tex $(gC m^{-2})$ @endtex
865!$OMP THREADPRIVATE(litter_crit)
866  REAL(r_std), SAVE :: fire_resist_lignin = 0.5 !!
867!$OMP THREADPRIVATE(fire_resist_lignin)
868  ! 2. Arrays
869
870  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
871       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95, .95/)   !! compartments emitted to the atmosphere
872!$OMP THREADPRIVATE(co2frac)                             !! when burned (unitless, 0-1) 
873
874  ! 3. Coefficients of equations
875
876  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
877!$OMP THREADPRIVATE(bcfrac_coeff)
878  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
879!$OMP THREADPRIVATE(firefrac_coeff)
880
881  !
882  ! lpj_gap.f90
883  !
884
885  ! 1. Scalar
886
887  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
888                                                 !! @tex $(year^{-1})$ @endtex
889!$OMP THREADPRIVATE(ref_greff)
890
891  ! 3. Coefficients of equations
892
893  REAL(r_std), SAVE :: availability_fact = 0.1   !!
894!$OMP THREADPRIVATE(availability_fact)
895
896  !               
897  ! lpj_light.f90
898  !             
899
900  ! 1. Scalar
901 
902  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
903                                            !! to fpc of last time step (F)? (true/false)
904!$OMP THREADPRIVATE(annual_increase)
905  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
906                                            !! (due to its branches etc.) (0-1, unitless)
907                                            !! This means that only a small fraction of its crown area
908                                            !! can be invaded by other trees.
909!$OMP THREADPRIVATE(min_cover)
910
911
912  !
913  ! lpj_pftinout.f90
914  !
915
916  ! 1. Scalar
917
918  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
919!$OMP THREADPRIVATE(min_avail)
920  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
921!$OMP THREADPRIVATE(ind_0)
922  ! 3. Coefficients of equations
923 
924  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
925!$OMP THREADPRIVATE(RIP_time_min)
926  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
927!$OMP THREADPRIVATE(npp_longterm_init)
928  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
929!$OMP THREADPRIVATE(everywhere_init)
930
931
932  !
933  ! stomate_growth_res_lim.f90
934  !
935
936  ! 0. Constants
937
938  REAL(r_std), PARAMETER :: max_possible_lai = 10. !! (m^2.m^{-2})
939  REAL(r_std), PARAMETER :: Nlim_Q10 = 10.         !!
940
941  ! 1. Scalar
942
943  LOGICAL, SAVE :: ok_minres = .TRUE.              !! [DISPENSABLE] Do we try to reach a minimum reservoir even if
944                                                   !! we are severely stressed? (true/false)
945!$OMP THREADPRIVATE(ok_minres)
946  REAL(r_std), SAVE :: tau_leafinit = 10.          !! Time required to develop a minimal LAI
947                                                   !! using the carbohydrate reserve (days)
948!$OMP THREADPRIVATE(tau_leafinit)
949  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
950                                                   !! carbohydrate reserve may be used for
951                                                   !! trees (days)
952!$OMP THREADPRIVATE(reserve_time_tree)
953  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
954                                                   !! carbohydrate reserve may be used for
955                                                   !! grasses (days)
956!$OMP THREADPRIVATE(reserve_time_grass)
957
958  REAL(r_std), SAVE :: R0 = 0.3                    !! Default root allocation (0-1, unitless)
959!$OMP THREADPRIVATE(R0)
960
961  REAL(r_std), SAVE :: f_fruit = 0.1               !! Default fruit allocation (0-1, unitless)
962!$OMP THREADPRIVATE(f_fruit)
963 
964  REAL(r_std), SAVE :: alloc_sap_above_grass = 1.0 !! fraction of sapwood allocation above ground
965                                                   !! for grass (0-1, unitless)
966!$OMP THREADPRIVATE(alloc_sap_above_grass)
967  REAL(r_std), SAVE :: min_LtoLSR = 0.2            !! Prescribed lower bounds for leaf
968                                                   !! allocation (0-1, unitless)
969!$OMP THREADPRIVATE(min_LtoLSR)
970  REAL(r_std), SAVE :: max_LtoLSR = 0.5            !! Prescribed upper bounds for leaf
971                                                   !! allocation (0-1, unitless)
972!$OMP THREADPRIVATE(max_LtoLSR)
973 
974  REAL(r_std), SAVE :: z_nitrogen = 0.2            !! Curvature of the root profile (m)
975!$OMP THREADPRIVATE(z_nitrogen)
976 
977  REAL(r_std), SAVE :: tax_max = 0.8               !! Maximum fraction of allocatable biomass used
978                                                   !! for maintenance respiration (0-1, unitless)
979!$OMP THREADPRIVATE(tax_max)
980
981  ! 3. Coefficients of equations
982
983!! Moved this to constantes_mtc
984!!  REAL(r_std), SAVE :: lai_max_to_happy = 0.5      !! share of the maximum lai required to sustain
985!!                                                   !! plant growth
986!!$OMP THREADPRIVATE(lai_max_to_happy)
987 
988  REAL(r_std), SAVE :: Nlim_tref = 25.             !! (C)
989!$OMP THREADPRIVATE(Nlim_tref)
990
991
992  !
993  ! stomate_growth_fun_all.f90
994  !
995  ! 1. Scalar 
996  INTEGER(i_std), SAVE :: ncirc                    !! Number of circumference classes used to calculate C allocation
997                                                   !! Used in prescribe.f90 and forestry.f90 - this mimics cohorts
998!$OMP THREADPRIVATE(ncirc)
999
1000  INTEGER(i_std), SAVE :: nagec                    !! Number of age classes used to calculate C allocation
1001                                                   !! Used in forestry.f90 and lcchange.f90 - this mimics age classes
1002!$OMP THREADPRIVATE(nagec)
1003
1004  REAL(r_std), SAVE :: min_water_stress = 0.1      !! Minimal value for wstress_fac (unitless, 0-1)
1005!$OMP THREADPRIVATE(min_water_stress)
1006
1007  REAL(r_std), SAVE :: max_delta_KF = 0.1          !! Maximum change in KF from one time step to another (m)
1008                                                   !! This is a bit arbitrary.
1009!$OMP THREADPRIVATE(max_delta_KF)
1010
1011  REAL(r_std), SAVE :: evergreen_reserve = 0.05    !! Fraction of sapwood mass stored in the reserve pool of evergreen
1012                                                   !! trees (unitless, 0-1)
1013!$OMP THREADPRIVATE(evergreen_reserve)
1014
1015  REAL(r_std), SAVE :: deciduous_reserve = 0.12    !! Fraction of sapwood mass stored in the reserve pool of deciduous
1016                                                   !! trees during the growing season (unitless, 0-1)
1017!$OMP THREADPRIVATE(deciduous_reserve)
1018
1019  REAL(r_std), SAVE :: senescense_reserve = 0.15   !! Fraction of sapwood mass stored in the reserve pool of deciduous
1020                                                   !! trees during senescense(unitless, 0-1)
1021!$OMP THREADPRIVATE(senescense_reserve)
1022
1023  REAL(r_std), SAVE :: labile_reserve = 60.        !! The lab_fac is divided by this value to obtain a new parameter
1024                                                   !! This new parameter is a fraction that is multiplied with the plant
1025                                                   !! biomass to obatin the optimal size of the labile pool. The dependency
1026                                                   !! on lab_fac is a nice feature but the whole parameterization is arbitrary
1027!$OMP THREADPRIVATE(labile_reserve)
1028
1029  REAL(r_std), SAVE :: maint_from_labile = 0.2     !! Maintenance respiration should be positive. In case it is
1030                                                   !! very low use ::maint_from_labile of the active labile carbon
1031                                                   !! pool (gC m-2 dt-1)
1032!$OMP THREADPRIVATE(maint_from_labile)
1033
1034  REAL(r_std), SAVE :: maint_from_gpp = 0.8        !! Some carbon needs to remain to support the growth, hence,
1035                                                   !! respiration will be limited. In this case resp_maint
1036                                                   !! (gC m-2 dt-1) should not be more than 80% (::maint_from_gpp)
1037                                                   !! of the GPP (gC m-2 s-1)
1038!$OMP THREADPRIVATE(maint_from_gpp)
1039 
1040
1041  REAL(r_std), SAVE :: sync_threshold = 0.0001     !! The threshold above which a warning is generated when the
1042                                                   !! total biomass is being compared to the sum of circ_class_biomass
1043!$OMP THREADPRIVATE(sync_threshold)
1044
1045  !
1046  ! stomate_data.f90
1047  !
1048
1049  ! 1. Scalar
1050
1051  ! 1.1 climatic parameters
1052
1053  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
1054!$OMP THREADPRIVATE(precip_crit)
1055  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
1056!$OMP THREADPRIVATE(gdd_crit_estab)
1057  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
1058!$OMP THREADPRIVATE(fpc_crit)
1059
1060  ! 1.2 sapling characteristics
1061
1062  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
1063!$OMP THREADPRIVATE(alpha_grass)
1064
1065  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
1066!$OMP THREADPRIVATE(alpha_tree)
1067
1068!!$  REAL(r_std), SAVE :: tune_c0_alloc = 2.3e-4   !! This parameter was tuned such that the ratio between root carbon and LAI is
1069!!$                                                !! similar for grasses and trees. Only used for grasses and crops (thus NOT for
1070!!$                                                !! trees)(unitless)
1071!!$!$OMP THREADPRIVATE(tune_c0_alloc)
1072
1073!!$  REAL(r_std), SAVE :: struct_to_leaves = 0.05  !! Fraction of structural carbon in grass and crops as a share of the leaf
1074!!$                                                !! carbon pool. Only used for grasses and crops (thus NOT for trees)
1075!!$                                                !! (unitless)
1076!!$!$OMP THREADPRIVATE(struct_to_leaves)
1077
1078  REAL(r_std), SAVE :: labile_to_total = 0.01   !! Fraction of the labile pool in trees, grasses and crops as a share of the
1079                                                !! total carbon pool (accounting for the N-content of the different tissues).
1080                                                !! (unitless)
1081!$OMP THREADPRIVATE(labile_to_total)
1082
1083
1084  ! 1.3  time scales for phenology and other processes (in days)
1085
1086  REAL(r_std), SAVE :: tau_hum_month = 20.               !! (days)       
1087!$OMP THREADPRIVATE(tau_hum_month)
1088  REAL(r_std), SAVE :: tau_hum_week = 7.                 !! (days) 
1089!$OMP THREADPRIVATE(tau_hum_week)
1090  REAL(r_std), SAVE :: tau_t2m_month = 20.               !! (days)     
1091!$OMP THREADPRIVATE(tau_t2m_month)
1092  REAL(r_std), SAVE :: tau_t2m_week = 7.                 !! (days) 
1093!$OMP THREADPRIVATE(tau_t2m_week)
1094  REAL(r_std), SAVE :: tau_tsoil_month = 20.             !! (days)     
1095!$OMP THREADPRIVATE(tau_tsoil_month)
1096  REAL(r_std), SAVE :: tau_soilhum_month = 20.           !! (days)     
1097!$OMP THREADPRIVATE(tau_soilhum_month)
1098  REAL(r_std), SAVE :: tau_gpp_week = 7.                 !! (days) 
1099!$OMP THREADPRIVATE(tau_gpp_week)
1100  REAL(r_std), SAVE :: tau_gdd = 40.                     !! (days) 
1101!$OMP THREADPRIVATE(tau_gdd)
1102  REAL(r_std), SAVE :: tau_ngd = 50.                     !! (days) 
1103!$OMP THREADPRIVATE(tau_ngd)
1104  REAL(r_std), SAVE :: coeff_tau_longterm = 3.           !! (unitless)
1105!$OMP THREADPRIVATE(coeff_tau_longterm)
1106  REAL(r_std), SAVE :: tau_longterm                      !! (days) 
1107!$OMP THREADPRIVATE(tau_longterm)
1108  REAL(r_std), SAVE :: tau_hum_growingseason_grass = 30. !! (days) 
1109!$OMP THREADPRIVATE(tau_hum_growingseason_grass)
1110
1111  ! 3. Coefficients of equations
1112
1113  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
1114!$OMP THREADPRIVATE(bm_sapl_carbres)
1115  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
1116!$OMP THREADPRIVATE(bm_sapl_sapabove)
1117  REAL(r_std), SAVE :: bm_sapl_heartabove = 0.2         !! Stich et al 2003 has a value of 0.2 (2 is used in the trunk)
1118!$OMP THREADPRIVATE(bm_sapl_heartabove)
1119  REAL(r_std), SAVE :: bm_sapl_heartbelow = 0.2         !! Stich et al 2003 has a value of 0.2 (2 is used in the trunk
1120!$OMP THREADPRIVATE(bm_sapl_heartbelow)
1121  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !! LAI (m2 m-2) of a natural grassland at the time of its sewing. Similar to woody PFT's
1122                                                        !! the model starts from small plants rather than seeds.
1123!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
1124  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !! LAI (m2 m-2) of a agricultural grassland at the time of its sewing. Similar to woody PFT's
1125                                                        !! the model starts from small plants rather than seeds.
1126!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
1127  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
1128!$OMP THREADPRIVATE(init_sapl_mass_carbres)
1129  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
1130!$OMP THREADPRIVATE(init_sapl_mass_root)
1131  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
1132!$OMP THREADPRIVATE(init_sapl_mass_fruit)
1133  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
1134!$OMP THREADPRIVATE(cn_sapl_init)
1135  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
1136!$OMP THREADPRIVATE(migrate_tree)
1137  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
1138!$OMP THREADPRIVATE(migrate_grass)
1139
1140  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !! Minimum lai. If not available C is taken from the reserves to
1141                                                        !! grow a canopy in phenology
1142!$OMP THREADPRIVATE(lai_initmin_tree)
1143  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
1144!$OMP THREADPRIVATE(lai_initmin_grass)
1145
1146  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
1147!$OMP THREADPRIVATE(dia_coeff)
1148  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
1149!$OMP THREADPRIVATE(maxdia_coeff)
1150  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
1151!$OMP THREADPRIVATE(bm_sapl_leaf)
1152
1153  !
1154  ! sapiens_forestry.f90
1155  !
1156  INTEGER(i_std), SAVE :: ndia_harvest                  !! The number of diameter classes used for
1157                                                        !! the wood harvest pools.
1158!$OMP THREADPRIVATE(ndia_harvest)
1159  REAL(r_std), SAVE      :: rdi_limit_upper=1            !! The parameters for self-thinning and yield come
1160                                                        !! from different data sets and are not necsassirly
1161                                                        !! fully consistent. The forestry code was written
1162                                                        !! such that it accounts for this consistency issue.
1163                                                        !! However, we still need a parameter that gives
1164                                                        !! us the upper_rdi_harvest in case the inconsistency
1165                                                        !! occurs.
1166!$OMP THREADPRIVATE(rdi_limit_upper)
1167  REAL(r_std), SAVE      :: max_harvest_dia             !! The largest diameter for the harvest pools to
1168                                                        !! keep track of harvested wood from forests.
1169!$OMP THREADPRIVATE(max_harvest_dia)
1170  INTEGER(i_std), SAVE   :: n_pai                       !! The number of years used for the cumulative
1171                                                        !! averages of the periodic annual increment.                     
1172!$OMP THREADPRIVATE(n_pai)
1173  LOGICAL, SAVE          :: use_litter_raking           !! If TRUE, this flag will simulate litter raking in
1174                                                        !! in grid squares.  This has the effect of moving litter
1175                                                        !! once a year from forest PFTs to agricultural PFTs, if they
1176                                                        !! are present on this pixel.  If TRUE, you must also provide
1177                                                        !! a map with the litter demand so we know how much litter
1178                                                        !! to remove for each pixel.
1179!$OMP THREADPRIVATE(use_litter_raking)
1180  INTEGER(i_std), SAVE   :: management = 0              !! Use Diego Santarem's optimization for broadleaves
1181!$OMP THREADPRIVATE(management)
1182    LOGICAL, SAVE        :: fake                        !! The model run is fake model run: a given
1183                                                        !! deltavol is forced clear at the first
1184                                                        !! year (default = FALSE). !VB! Replace
1185                                                        !! "fake" by "pseudo" in the description
1186                                                        !! and in the code
1187!$OMP THREADPRIVATE(fake)
1188    LOGICAL, SAVE        :: clearfirst                  !! Start model run with a clearcut (default
1189                                                        !! = TRUE).
1190!$OMP THREADPRIVATE(clearfirst)
1191    INTEGER(i_std), SAVE :: early_cut                   !! Flag determining what happens when
1192                                                        !! density gets below dens_target (minima
1193                                                        !! density threshold, see
1194                                                        !! stomate_constants.f90): 0= nothing, 1 =
1195                                                        !! revert to orch-std when density gets
1196                                                        !! below minimal threshold, 2 = clearcut
1197                                                        !! when density gets below minimal
1198                                                        !! threshold
1199!$OMP THREADPRIVATE(early_cut)
1200    INTEGER(i_std), SAVE :: itinerary                   !! Itinerary type for coppices: 1 = Popface
1201                                                        !! experiment (Liberloo 2006), 3*6 years, 2
1202                                                        !! = Orsay experiment (Pontailler 1999), 1
1203                                                        !! + 2*5 years
1204!$OMP THREADPRIVATE(itinerary)
1205    INTEGER(i_std), SAVE :: age_target_def              !! Age at which clearcut occurs no matter
1206                                                        !! the density of the stand (years). This
1207                                                        !! parameter is read from the run.def file
1208                                                        !! (as others). According to Lanier (1994)
1209                                                        !! and Bottcher (2008), it should most
1210                                                        !! generally be between 100 and 200 years.
1211!$OMP THREADPRIVATE(age_target_def)
1212    INTEGER(i_std), SAVE :: ntrees_profit               !! The number of trees over which the average
1213                                                        !! height is calculated to determine if the
1214                                                        !! stand will be profitable to thin.
1215!$OMP THREADPRIVATE(ntrees_profit)
1216
1217  INTEGER(i_std), SAVE   :: bavard_f                    !! If bavard_f=1, then a lot of "print", if
1218                                                        !! bavard_f=2, even more.
1219!$OMP THREADPRIVATE(bavard_f)
1220
1221  ! Variations for sensitivity analysis
1222
1223  REAL(r_std), SAVE      :: ss_pipe_density = 1.        !! Sensitivity for pipe_density
1224!$OMP THREADPRIVATE(ss_pipe_density)
1225  REAL(r_std), SAVE      :: ss_selfth_curve = 1.        !! Sensitivity for selfth_curve
1226!$OMP THREADPRIVATE(ss_selfth_curve)
1227  REAL(r_std), SAVE      :: ss_sigma = 1.               !! Sensitivity for sigma
1228!$OMP THREADPRIVATE(ss_sigma)
1229  REAL(r_std), SAVE      :: ss_th_strat = 1.            !! Sensitivity for th_strat
1230!$OMP THREADPRIVATE(ss_th_strat)
1231  REAL(r_std), SAVE      :: ss_tau_spread = 1.          !! Sensitivity for tau_spread
1232!$OMP THREADPRIVATE(ss_tau_spread)
1233  REAL(r_std), SAVE      :: ss_lambda = 1.              !! Sensitivity for lambda
1234!$OMP THREADPRIVATE(ss_lambda)
1235  REAL(r_std), SAVE      :: ss_circ_bm = 1.             !! Sensitivity for circ_bm
1236!$OMP THREADPRIVATE(ss_circ_bm)
1237  REAL(r_std), SAVE      :: ss_height_circ = 1.         !! Sensitivity for height_circ
1238!$OMP THREADPRIVATE(ss_height_circ)
1239  REAL(r_std), SAVE      :: ss_min_circ_init = 1.       !! Sensitivity for min_circ_init
1240!$OMP THREADPRIVATE(ss_min_circ_init)
1241  REAL(r_std), SAVE      :: ss_p_max = 1.               !! Sensitivity for p_max
1242!$OMP THREADPRIVATE(ss_p_max)
1243
1244
1245  !
1246  ! stomate_litter.f90
1247  !
1248
1249  ! 0. Constants
1250
1251  REAL(r_std), PARAMETER :: Q10 = 10.               !!
1252
1253  ! 1. Scalar
1254
1255  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
1256!$OMP THREADPRIVATE(z_decomp)
1257  REAL(r_std), SAVE :: moistcont_min = 0.25         !!
1258!$OMP THREADPRIVATE(moistcont_min)
1259
1260  ! 2. Arrays
1261
1262  REAL(r_std), SAVE :: frac_soil_struct_aa = 0.55   !! corresponding to frac_soil(istructural,iactive,iabove)
1263!$OMP THREADPRIVATE(frac_soil_struct_aa)
1264  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
1265!$OMP THREADPRIVATE(frac_soil_struct_ab)
1266  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
1267!$OMP THREADPRIVATE(frac_soil_struct_sa)
1268  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
1269!$OMP THREADPRIVATE(frac_soil_struct_sb)
1270  REAL(r_std), SAVE :: frac_soil_metab_aa = 0.45    !! corresponding to frac_soil(imetabolic,iactive,iabove)
1271!$OMP THREADPRIVATE(frac_soil_metab_aa)
1272  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
1273!$OMP THREADPRIVATE(frac_soil_metab_ab)
1274  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = &    !! C/N ratio of each plant pool (0-100, unitless)
1275       & (/ 40., 40., 40., 40., 40., 40., 40., 40., 40./) 
1276!$OMP THREADPRIVATE(CN)
1277  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = &    !! Lignin/C ratio of different plant parts (0,22-0,35, unitless)
1278       & (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22, 0.22 /)
1279!$OMP THREADPRIVATE(LC)
1280
1281  ! 3. Coefficients of equations
1282
1283  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
1284!$OMP THREADPRIVATE(metabolic_ref_frac)
1285  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
1286!$OMP THREADPRIVATE(metabolic_LN_ratio)
1287  REAL(r_std), SAVE :: tau_metabolic = 0.066        !!
1288!$OMP THREADPRIVATE(tau_metabolic)
1289  REAL(r_std), SAVE :: tau_struct = 0.245           !!
1290!$OMP THREADPRIVATE(tau_struct)
1291  REAL(r_std), SAVE :: tau_woody = 0.75             !!
1292!$OMP THREADPRIVATE(tau_woody)
1293  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
1294!$OMP THREADPRIVATE(soil_Q10)
1295  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
1296!$OMP THREADPRIVATE(tsoil_ref)
1297  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
1298!$OMP THREADPRIVATE(litter_struct_coef)
1299  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ -1.1,  2.4,  -0.29 /) !!
1300!$OMP THREADPRIVATE(moist_coeff)
1301
1302
1303  !
1304  ! stomate_lpj.f90
1305  !
1306
1307  ! 1. Scalar
1308
1309  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
1310!$OMP THREADPRIVATE(frac_turnover_daily)
1311
1312
1313  !
1314  ! stomate_phenology.f90
1315  !
1316
1317  ! 1. Scalar
1318
1319  LOGICAL, SAVE :: always_init = .FALSE.           !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
1320!$OMP THREADPRIVATE(always_init)
1321  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
1322!$OMP THREADPRIVATE(min_growthinit_time)
1323  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
1324                                                   !!  - for trees (0-1, unitless)
1325!$OMP THREADPRIVATE(moiavail_always_tree)
1326  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1327                                                   !! - for grass (0-1, unitless)
1328!$OMP THREADPRIVATE(moiavail_always_grass)
1329  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
1330!$OMP THREADPRIVATE(t_always)
1331  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
1332!$OMP THREADPRIVATE(t_always_add)
1333
1334  ! 3. Coefficients of equations
1335 
1336  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
1337!$OMP THREADPRIVATE(gddncd_ref)
1338  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
1339!$OMP THREADPRIVATE(gddncd_curve)
1340  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
1341!$OMP THREADPRIVATE(gddncd_offset)
1342
1343
1344  !
1345  ! stomate_prescribe.f90
1346  !
1347
1348  ! 1. Scalar
1349    REAL(r_std), SAVE                       :: min_circ_init     !! Minimum initial circumferences of the
1350                                                                 !! truncated exponential distribution (cm)
1351!$OMP THREADPRIVATE(min_circ_init)
1352    REAL(r_std), SAVE                       :: frac_shoot_init   !! Frac_shoot_init is the same for the
1353                                                                 !! initial distribution and is
1354                                                                 !! parameterized based on Litton (2007) and
1355                                                                 !! Mokany (2006).
1356!$OMP THREADPRIVATE(frac_shoot_init)
1357
1358  ! 3. Coefficients of equations
1359
1360  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
1361!$OMP THREADPRIVATE(bm_sapl_rescale)
1362
1363
1364  !
1365  ! stomate_resp.f90
1366  !
1367
1368  ! 3. Coefficients of equations
1369
1370  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
1371!$OMP THREADPRIVATE(maint_resp_min_vmax)
1372 
1373  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
1374!$OMP THREADPRIVATE(maint_resp_coeff)
1375 
1376  REAL(r_std), SAVE :: maint_resp_c = 1.           !!
1377!$OMP THREADPRIVATE(maint_resp_c)
1378
1379
1380  !
1381  ! stomate_soilcarbon.f90
1382  !
1383
1384  ! 2. Arrays
1385
1386  ! 2.1 frac_carb_coefficients
1387
1388  REAL(r_std), SAVE :: frac_carb_ap = 0.004  !! from active pool: depends on clay content  (0-1, unitless)
1389                                             !! corresponding to frac_carb(:,iactive,ipassive)
1390!$OMP THREADPRIVATE(frac_carb_ap)
1391  REAL(r_std), SAVE :: frac_carb_sa = 0.42   !! from slow pool (0-1, unitless)
1392                                             !! corresponding to frac_carb(:,islow,iactive)
1393!$OMP THREADPRIVATE(frac_carb_sa)
1394  REAL(r_std), SAVE :: frac_carb_sp = 0.03   !! from slow pool (0-1, unitless)
1395                                             !! corresponding to frac_carb(:,islow,ipassive)
1396!$OMP THREADPRIVATE(frac_carb_sp)
1397  REAL(r_std), SAVE :: frac_carb_pa = 0.45   !! from passive pool (0-1, unitless)
1398                                             !! corresponding to frac_carb(:,ipassive,iactive)
1399!$OMP THREADPRIVATE(frac_carb_pa)
1400  REAL(r_std), SAVE :: frac_carb_ps = 0.0    !! from passive pool (0-1, unitless)
1401                                             !! corresponding to frac_carb(:,ipassive,islow)
1402!$OMP THREADPRIVATE(frac_carb_ps)
1403
1404  ! 3. Coefficients of equations
1405
1406  REAL(r_std), SAVE :: active_to_pass_clay_frac = 0.68  !! (0-1, unitless)
1407!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1408  !! residence times in carbon pools (days)
1409  REAL(r_std), SAVE :: carbon_tau_iactive = 0.149   !! residence times in active pool (days)
1410!$OMP THREADPRIVATE(carbon_tau_iactive)
1411  REAL(r_std), SAVE :: carbon_tau_islow = 5.48      !! residence times in slow pool (days)
1412!$OMP THREADPRIVATE(carbon_tau_islow)
1413  REAL(r_std), SAVE :: carbon_tau_ipassive = 241.   !! residence times in passive pool (days)
1414!$OMP THREADPRIVATE(carbon_tau_ipassive)
1415  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
1416!$OMP THREADPRIVATE(flux_tot_coeff)
1417
1418
1419  !
1420  ! stomate_turnover.f90
1421  !
1422
1423  ! 3. Coefficients of equations
1424
1425  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
1426!$OMP THREADPRIVATE(new_turnover_time_ref)
1427  REAL(r_std), SAVE :: dt_turnover_time = 10.      !!(days)
1428!$OMP THREADPRIVATE(dt_turnover_time)
1429  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
1430!$OMP THREADPRIVATE(leaf_age_crit_tref)
1431  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
1432!$OMP THREADPRIVATE(leaf_age_crit_coeff)
1433
1434
1435  !
1436  ! stomate_vmax.f90
1437  !
1438 
1439  ! 1. Scalar
1440
1441  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
1442!$OMP THREADPRIVATE(vmax_offset)
1443  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1444                                                !! reaches 1 (unitless)
1445!$OMP THREADPRIVATE(leafage_firstmax)
1446  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1447                                                !! falls below 1 (unitless)
1448!$OMP THREADPRIVATE(leafage_lastmax)
1449  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1450                                                !! reaches its minimum (vmax_offset)
1451                                                !! (unitless)
1452!$OMP THREADPRIVATE(leafage_old)
1453
1454
1455  !
1456  ! stomate_season.f90
1457  !
1458
1459  ! 1. Scalar
1460
1461  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
1462!$OMP THREADPRIVATE(gppfrac_dormance)
1463  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
1464!$OMP THREADPRIVATE(tau_climatology)
1465  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
1466!$OMP THREADPRIVATE(hvc1)
1467  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
1468!$OMP THREADPRIVATE(hvc2)
1469  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
1470!$OMP THREADPRIVATE(leaf_frac_hvc)
1471  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
1472!$OMP THREADPRIVATE(tlong_ref_max)
1473  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
1474!$OMP THREADPRIVATE(tlong_ref_min)
1475  REAL(r_std), SAVE :: tune_waterstress = 1.   !! The calculated values of moiavail are too low to be used as
1476                                               !! multiplier for the allocation factors (::KF and ::LF). Hence,
1477                                               !! ::moiavail_daily is tuned by this factor to calculate
1478                                               !! ::wstress_fac (unitless)
1479!$OMP THREADPRIVATE(tune_waterstress)
1480
1481
1482  ! 3. Coefficients of equations
1483
1484  REAL(r_std), SAVE :: ncd_max_year = 3.
1485!$OMP THREADPRIVATE(ncd_max_year)
1486  REAL(r_std), SAVE :: gdd_threshold = 5.
1487!$OMP THREADPRIVATE(gdd_threshold)
1488  REAL(r_std), SAVE :: green_age_ever = 2.
1489!$OMP THREADPRIVATE(green_age_ever)
1490  REAL(r_std), SAVE :: green_age_dec = 0.5
1491!$OMP THREADPRIVATE(green_age_dec)
1492  REAL(r_std), SAVE :: ngd_min_dormance = 90.
1493!$OMP THREADPRIVATE(ngd_min_dormance)
1494
1495
1496
1497! stomate_io.f90
1498
1499  REAL(r_std), SAVE :: mstemp = 13.9            !! Global Annual Mean Surface Temperature taken from
1500                                                !! http://www.ncdc.noaa.gov/monitoring-references/faq/anomalies.php
1501!$OMP THREADPRIVATE(mstemp)
1502
1503
1504
1505
1506END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.