source: branches/publications/ORCHIDEE_CAN_r3069/src_parameters/constantes_var.f90

Last change on this file was 2945, checked in by sebastiaan.luyssaert, 9 years ago

DEV: tested 1 year global. This code contains the latest version for anthropogenic tree species channges, several bug fixes to forest management as well as the code for the fully integrated multi-layer energy budget. This implies that the multi-layer energy budget makes use Pinty's albedo scheme, the rognostic canopy structure as well as a vertical profile for stomatal conductance. This is an intermediate version because species change code is not complete as some management changes have not been implemented yet. Further the multi-layer albedo code needs more work in terms of calculating average fluxes at the pixel rather than the PFT level

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