source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parameters/constantes_mtc.f90 @ 8119

Last change on this file since 8119 was 7684, checked in by josefine.ghattas, 2 years ago

Finalise update of default parameter values according to what is set in orchidee_pft.def_13pft.1ac. No changes should be seen for default offline experiments as the paramers were set in the orchidee_pft.def file. But for LMDZOR exp, results might change.

  • Property svn:keywords set to Date Revision
File size: 137.4 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_mtc
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         This module contains the standard values of the parameters for the 13 metaclasses of vegetation used by ORCHIDEE.
10!!
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S):
14!!
15!! REFERENCE(S) :
16!! - Kuppel, S. (2012): Doctoral Thesis, Assimilation de mesures de flux turbulents d'eau et de carbone dans un modÚle de la biosphÚre
17!! continentale
18!! - Kuppel, S., Peylin, P., Chevallier, F., Bacour, C., Maignan, F., and Richardson, A. D. (2012). Constraining a global ecosystem
19!! model with multi-site eddy-covariance data, Biogeosciences, 9, 3757-3776, DOI 10.5194/bg-9-3757-2012.
20!! - Wohlfahrt, G., M. Bahn, E. Haubner, I. Horak, W. Michaeler, K.Rottmar, U. Tappeiner, and A. Cemusca, 1999: Inter-specific
21!! variation of the biochemical limitation to photosynthesis and related leaf traits of 30 species from mountain grassland
22!! ecosystems under different land use. Plant Cell Environ., 22, 12811296.
23!! - Malhi, Y., Doughty, C., and Galbraith, D. (2011). The allocation of ecosystem net primary productivity in tropical forests,
24!! Philosophical Transactions of the Royal Society B-Biological Sciences, 366, 3225-3245, DOI 10.1098/rstb.2011.0062.
25!! - Earles, J. M., Yeh, S., and Skog, K. E. (2012). Timing of carbon emissions from global forest clearance, Nature Climate Change, 2,
26!! 682-685, Doi 10.1038/Nclimate1535.
27!! - Piao, S. L., Luyssaert, S., Ciais, P., Janssens, I. A., Chen, A. P., Cao, C., Fang, J. Y., Friedlingstein, P., Luo, Y. Q., and
28!! Wang, S. P. (2010). Forest annual carbon cost: A global-scale analysis of autotrophic respiration, Ecology, 91, 652-661,
29!! Doi 10.1890/08-2176.1.
30!! - Verbeeck, H., Peylin, P., Bacour, C., Bonal, D., Steppe, K., and Ciais, P. (2011). Seasonal patterns of co2 fluxes in amazon
31!! forests: Fusion of eddy covariance data and the orchidee model, Journal of Geophysical Research-Biogeosciences, 116,
32!! Artn G02018, Doi 10.1029/2010jg001544.
33!! - MacBean, N., Maignan, F., Peylin, P., Bacour, C., Breon, F. M., & Ciais, P. (2015). Using satellite data to improve the leaf
34!! phenology of a global terrestrial biosphere model. Biogeosciences, 12(23), 7185-7208.
35!!
36!! SVN          :
37!! $HeadURL: $
38!! $Date$
39!! $Revision$
40!! \n
41!_ ================================================================================================================================
42
43MODULE constantes_mtc
44
45  USE defprec
46  USE constantes
47
48  IMPLICIT NONE
49
50  !
51  ! METACLASSES CHARACTERISTICS
52  !
53
54  INTEGER(i_std), PARAMETER :: nvmc = 13                         !! Number of MTCS fixed in the code (unitless)
55
56  CHARACTER(len=34), PARAMETER, DIMENSION(nvmc) :: MTC_name = &  !! description of the MTC (unitless)
57  & (/ 'bare ground                       ', &          !  1
58  &    'tropical  broad-leaved evergreen  ', &          !  2
59  &    'tropical  broad-leaved raingreen  ', &          !  3
60  &    'temperate needleleaf   evergreen  ', &          !  4
61  &    'temperate broad-leaved evergreen  ', &          !  5
62  &    'temperate broad-leaved summergreen', &          !  6
63  &    'boreal    needleleaf   evergreen  ', &          !  7
64  &    'boreal    broad-leaved summergreen', &          !  8
65  &    'boreal    needleleaf   summergreen', &          !  9
66  &    '          C3           grass      ', &          ! 10
67  &    '          C4           grass      ', &          ! 11
68  &    '          C3           agriculture', &          ! 12
69  &    '          C4           agriculture'  /)         ! 13
70
71
72  !
73  ! VEGETATION STRUCTURE
74  !
75  INTEGER(i_std),PARAMETER, DIMENSION(nvmc) :: leaf_tab_mtc  =  &                 !! leaf type (1-4, unitless)
76  & (/  4,   1,   1,   2,   1,   1,   2,   &                                      !! 1=broad leaved tree, 2=needle leaved tree
77  &     1,   2,   3,   3,   3,   3   /)                                           !! 3=grass 4=bare ground
78
79  CHARACTER(len=6), PARAMETER, DIMENSION(nvmc) :: pheno_model_mtc  =  &  !! which phenology model is used? (tabulated)
80  & (/  'none  ',   'none  ',   'moi   ',   'none  ',   'none  ',  &
81  &     'ncdgdd',   'none  ',   'ncdgdd',   'ngd',   'moigdd',  &
82  &     'moigdd',   'moigdd',   'moigdd'  /) 
83
84  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_tropical_mtc  =  &                       !! Is PFT tropical ? (true/false)
85  & (/ .FALSE.,   .TRUE.,    .TRUE.,    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  &
86  &    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE. /)   
87
88  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_temperate_mtc  =  &         !! Is PFT temperate ? (true/false)
89  & (/ .FALSE.,   .FALSE.,   .FALSE.,   .TRUE.,    .TRUE.,    .TRUE.,   .FALSE.,  &
90  &    .FALSE.,   .FALSE.,   .TRUE.,    .TRUE.,    .TRUE.,    .TRUE. /)
91
92  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_boreal_mtc = &              !! Is PFT boreal ? (true/false)
93  & (/ .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .TRUE.,  &
94  &    .TRUE.,    .TRUE.,    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE. /)
95
96  CHARACTER(LEN=5), PARAMETER, DIMENSION(nvmc) :: type_of_lai_mtc  =  &  !! Type of behaviour of the LAI evolution algorithm
97  & (/ 'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! for each vegetation type. (unitless)
98  &    'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! Value of type_of_lai : mean or interp
99  &    'inter', 'inter', 'inter' /)
100
101  LOGICAL, PARAMETER, DIMENSION(nvmc) :: natural_mtc =  &                         !! natural?  (true/false)
102  & (/ .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,    .TRUE.,   .TRUE.,  &
103  &    .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .FALSE.,   .FALSE.  /)
104
105  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: veget_ori_fixed_mtc  =  &  !! Value for veget_ori for tests in
106  & (/ 0.2,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                !! 0-dim simulations (0-1, unitless)
107  &    0.0,   0.0,   0.8,   0.0,   0.0,   0.0  /)
108
109  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimax_mtc  =  &          !! laimax for maximum
110  & (/ 0.0,   8.0,   8.0,   4.0,   4.5,   4.5,   4.0,  &                !! See also type of lai interpolation
111  &    4.5,   4.0,   2.0,   2.0,   2.0,   2.0  /)                       !! @tex $(m^2.m^{-2})$ @endtex
112
113  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimin_mtc  = &           !! laimin for minimum lai
114  & (/ 0.0,   8.0,   0.0,   4.0,   4.5,   0.0,   4.0,  &                !! See also type of lai interpolation (m^2.m^{-2})
115  &    0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                       !! @tex $(m^2.m^{-2})$ @endtex
116
117  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_presc_mtc  =  &     !! prescribed height of vegetation (m)
118  & (/  0.0,   30.0,   30.0,   20.0,   20.0,   20.0,   15.0,  &         !! Value for height_presc : one for each vegetation type
119  &    15.0,   15.0,    0.5,    0.6,    1.0,    1.0  /)
120
121  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: z0_over_height_mtc = &         !! Factor to calculate roughness height from
122  & (/  0.0, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625,  &         !! vegetation height (unitless)   
123  &  0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625  /)
124
125  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ratio_z0m_z0h_mtc = &      !! Ratio between z0m and z0h values (roughness height for momentum and for heat)
126  & (/  1.0,    1.0,    1.0,    1.0,    1.0,    1.0,    1.0,  &         
127  &     1.0,    1.0,    1.0,    1.0,    1.0,    1.0  /)
128
129
130  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rveg_mtc  =  &             !! Potentiometer to set vegetation resistance (unitless)
131  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                !! Nathalie on March 28th, 2006 - from Fred Hourdin,
132  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0   /)
133
134  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: sla_mtc  =  &                       !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
135  & (/ 1.5E-2,   1.53E-2,   2.6E-2,   9.26E-3,     2E-2,   2.6E-2,   9.26E-3,  &
136  &    2.6E-2,    1.9E-2,   2.6E-2,    2.6E-2,   2.6E-2,   2.6E-2  /) 
137
138  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: slainit_mtc  =  &                       !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
139  & (/ 0.026,     0.03963,   0.044,   0.01365,  0.02703,  0.05749, 0.01886, &
140  &    0.04164,   0.04164,   0.031,   0.031,    0.02,     0.02  /) 
141
142  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: availability_fact_mtc  =  &     !! calculate mortality in lpj_gap
143  & (/ undef,   0.14,  0.14,   0.10,   0.10,   0.10,   0.05,  &
144  &     0.05,   0.05,  undef,  undef,  undef,  undef  /)
145
146  !
147  ! EVAPOTRANSPIRATION (sechiba)
148  !
149  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rstruct_const_mtc  =  &  !! Structural resistance.
150  & (/ 0.0,   25.0,   25.0,   25.0,   25.0,   25.0,   25.0,  &        !! @tex $(s.m^{-1})$ @endtex
151  &   25.0,   25.0,    2.5,    2.0,    2.0,    2.0   /)
152
153  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kzero_mtc  =  &                  !! A vegetation dependent constant used in the
154  & (/    0.0,   12.E-5,   12.E-5,   12.E-5,   12.E-5,   25.E-5,   12.E-5,  & !! calculation  of the surface resistance.
155  &    25.E-5,   25.E-5,   30.E-5,   30.E-5,   30.E-5,   30.E-5  /)           !! @tex $(kg.m^2.s^{-1})$ @endtex
156
157
158  !
159  ! WATER (sechiba)
160  !
161  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wmax_veg_mtc  =  &        !! Volumetric available soil water capacity in each PFT
162  & (/ 150.0,   150.0,   150.0,   150.0,   150.0,   150.0,   150.0,  & !! @tex $(kg.m^{-3} of soil)$ @endtex
163  &    150.0,   150.0,   150.0,   150.0,   150.0,   150.0  /)         
164                                                                     
165
166  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref4m  =  &       !! Root profile description for the different
167  & (/ 5.0,   0.4,   0.4,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types. @tex $(m^{-1})$ @endtex
168  &    1.0,   0.8,   4.0,   1.0,   4.0,   1.0  /)                      !! These are the factor in the exponential which gets       
169                                                                       !! the root density as a function of depth
170                                                                       !! Values for zmaxh = 4.0 
171  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_root_depth_ref4m_mtc=&!! Maximum rooting depth for the PFT irrespective of other
172  & (/ 4.0,   4.0,   4.0,   4.0,   4.0,   4.0,   4.0,  &               !! constraints from the active layer thickness @tex $(m)$ @endtex
173  &    4.0,   4.0,   2.0,   2.0,   0.8,   0.8  /)                      !! Values for zmaxh = 4.0
174 
175  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref2m  =  &       !! Root profile description for the different
176  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &               !! vegetations types.  @tex $(m^{-1})$ @endtex
177  &    1.0,   1.0,   0.6,   0.6,   0.6,   0.6  /)                      !! These are the factor in the exponential which gets       
178                                                                       !! the root density as a function of depth
179                                                                       !! Values for zmaxh = 2.0
180
181  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_root_depth_ref2m_mtc=&!! Maximum rooting depth for the PFT irrespective of other
182  & (/ 2.0,   2.0,   2.0,   2.0,   2.0,   2.0,   2.0,  &               !! constraints from the active layer thickness @tex $(m)$ @endtex
183  &    2.0,   2.0,   1.0,   1.0,   0.8,   0.8  /)     
184
185  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: throughfall_by_mtc  =  &  !! Percent by PFT of precip that is not intercepted by the canopy
186  & (/ 30.0,   30.0,   30.0,   30.0,   30.0,   30.0,   30.0,  &        !! (0-100, unitless)
187  &    30.0,   30.0,   30.0,   30.0,   30.0,   30.0  /)
188
189
190  !
191  ! ALBEDO (sechiba)
192  !
193  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_vis_mtc  =  &  !! Minimum snow albedo value for each vegetation type
194  & (/ 0.74,    0.0,    0.0,   0.08,   0.24,   0.07,   0.18,  &        !! after aging (dirty old snow) (unitless), visible albedo
195  &    0.18,    0.33,   0.57,  0.57,   0.57,   0.57  /)                !! Source : Values optimized for ORCHIDEE2.0
196
197  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_nir_mtc  =  &  !! Minimum snow albedo value for each vegetation type
198  & (/ 0.50,    0.0,    0.0,   0.10,   0.37,   0.08,   0.16,  &        !! after aging (dirty old snow) (unitless), near infrared albedo
199  &    0.17,    0.27,   0.44,   0.44,   0.44,   0.44  /)               !! Source : Values optimized for ORCHIDEE2.0
200
201  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_vis_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
202  & (/ 0.21,   0.0,    0.0,   0.14,   0.08,   0.17,   0.05,  &         !! as it will be used in condveg_snow (unitless), visible albedo
203  &    0.06,   0.09,   0.15,  0.15,   0.15,   0.15  /)                 !! Source : Values optimized for ORCHIDEE2.0
204
205  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_nir_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
206  & (/ 0.13,    0.0,    0.0,   0.10,   0.10,   0.16,   0.04,  &        !! as it will be used in condveg_snow (unitless), near infrared albedo
207  &    0.07,    0.08,   0.12,  0.12,   0.12,   0.12  /)                !! Source : Values optimized for ORCHIDEE2.0
208
209  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_vis_mtc  =  &    !! leaf albedo of vegetation type, visible albedo, optimized on 04/07/2016
210  & (/ 0.00,   0.04, 0.04, 0.04, 0.04, 0.03, 0.03,  &                  !! (unitless)
211  &    0.03,   0.03, 0.06, 0.06, 0.06, 0.06  /)
212
213  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_nir_mtc  =  &    !! leaf albedo of vegetation type, near infrared albedo, optimized on 04/07/2016
214  & (/ 0.00,   0.23,  0.18,  0.18,  0.20,  0.24,  0.15,  &             !! (unitless)
215  &    0.26,   0.20,  0.24,  0.27,  0.28,  0.26  /)
216
217  ! albedo values for albedo type 'pinty'
218  ! these next values were determined by fitting to global MODIS data and using the inversion scheme of
219  ! Pinty et al (see Pinty B,Andredakis I, Clerici M, et al. (2011) ! 'Exploiting the MODIS albedos
220  ! with the Two-stream Inversion Package (JRC-TIP): 1. Effective leaf area index,
221  ! vegetation, and soil properties'. Journal of Geophysical Research.
222  !
223  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_ssa_vis_mtc  =  &           !! leaf single scattering albedo, visible light (unitless)
224  (/ 0.17291, 0.12156, 0.17413, 0.13349, 0.1343,  0.17218, 0.14711, &
225     0.14399, 0.15125, 0.17455, 0.16981, 0.17301, 0.17176 /)
226  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_ssa_nir_mtc  =  &           !! leaf single scattering albedo, near infrared (unitless)
227  (/ 0.70275, 0.67834, 0.70136,  0.68984,  0.7341,  0.72176, 0.69501, &
228     0.69201, 0.8498,  0.71212,  0.71501,  0.71259, 0.71295/)
229  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_psd_vis_mtc  =  &           !! leaf preferred scattering direction, visible light (unitless)
230  (/ 1.003, 0.965, 1.001, 0.969, 1.026,  1.036, 0.978, &
231     0.978, 1.175, 1.004, 1.0,   1.003,  1.002 /)
232  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_psd_nir_mtc  =  &           !! leaf preferred scattering direction, NIR light (unitless)
233  (/ 2.006,  1.943,  2.003,  1.975,  2.095,  2.058,  1.988, &
234     1.974,  2.435,  2.024,  2.024,  2.021,  2.024 /)
235   
236  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bgd_reflectance_vis_mtc  =  &    !! background reflectance, visible light (unitless)
237  (/ 0.13128,  0.08002,  0.10057,  0.05125,  0.0559,  0.08873,  0.03511, &
238     0.0597,   0.05174,  0.13085,  0.1177,   0.11008, 0.124 /)
239
240  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bgd_reflectance_nir_mtc  =  &    !! background reflectance, NIR light (unitless)
241  (/ 0.24556,  0.13978,  0.17651,  0.08851,  0.0957,  0.14427,  0.04983, &
242     0.09275,  0.08372,  0.24711,  0.22773,  0.20472, 0.23701 /)
243
244
245  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_to_shoot_clumping_mtc  =  & !! The clumping factor for leaves to shoots in the
246  & (/ un,   un,   un,   un,   un,   un,   un,  &                    !! effective LAI calculation...notice this should be
247  &   un,   un,   un,   un,   un,   un /)                            !! equal to unity for grasslands/croplands
248
249  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_correction_factor_mtc  =  &  !! see the note about this variable in pft_parameters
250  & (/ un,   un,   un,   un,   un,   un,   un,  & 
251  &   un,   un,   un,   un,   un,   un /)
252
253  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_level_sep_mtc  =  & !! The minimum level thickness for photosynthesis [m]
254  & (/ un,   0.1,   0.1,   0.1,   0.1,   0.1,   0.1,  &              !! This number is arbitrary at the moment.  The idea
255  &   0.1,   0.1,   0.1,   0.1,   0.1,   0.1 /)                      !! is to have a small number to make as many levels
256                                                                     !! as possible in the canopies, but not too small which
257                                                                     !! results in too little LAI in all the levels.  If all your
258                                                                     !! levels have less than 0.1 LAI in them, that's probably
259                                                                     !! too small.
260
261  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_top_mtc = &                  !! Diffuco.f90 calculates the stomatal conductance of the
262  (/ 1.0,   0.1,   0.1,   0.2,   0.1,   0.1,   0.2,  &                         !! top layer of the canopy. Because the top layer can contain
263     0.1,   0.1,   5.0,   5.0,   5.0,   5.0 /)                                !! diiferent amounts of LAI depending on the crown diameter
264                                                                              !! we had to define top layer in terms of the LAI it contains.
265                                                                              !! stomatal conductance in the top layer contributes to the
266                                                                              !! transpiration (m2 m-2). Arbitrary values.
267
268  !
269  ! SOIL - VEGETATION
270  !
271  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_mtc  =  &       !! The soil tile number for each vegetation
272  & (/ 1,   2,   2,   2,   2,   2,   2,  &                                   
273  &    2,   2,   3,   3,   3,   3  /)                                         
274
275  !
276  ! VEGETATION - AGE CLASSES
277  !
278  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: agec_group_mtc  =  &       !! The age class group that each PFT belongs to.
279       (/ 1,   2,   3,   4,   5,   6,   7,  &                                   
280       8,   9,   10,   11,   12,   13  /)
281
282  !
283  ! PHOTOSYNTHESIS
284  !
285  !-
286  ! 1 .CO2
287  !-
288  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c4_mtc  =  &                            !! flag for C4 vegetation types (true/false)
289  & (/ .FALSE.,  .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  &
290  &    .FALSE.,  .FALSE.,   .FALSE.,   .TRUE.,    .FALSE.,   .TRUE.  /)
291
292  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_fix_mtc  =  &     !! values used for vcmax when STOMATE is not
293  & (/  0.0,   40.0,   50.0,   30.0,   35.0,   40.0,   30.0,  &      !! activated @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
294  &    40.0,   35.0,   60.0,   60.0,   70.0,   70.0  /)
295
296! For C4 plant we define a very small downregulation effect as C4 plant are
297! currently saturate with respect to CO2 impact on vcmax
298  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: downregulation_co2_coeff_mtc  =  &  !! coefficient for CO2 downregulation
299  & (/  0.0,   0.38,   0.38,   0.28,   0.28,   0.28,   0.22,  &
300  &     0.22,  0.22,   0.26,   0.03,   0.26,   0.03 /)
301
302  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmC_mtc  = &            !! Energy of activation for KmC (J mol-1)
303  & (/undef,  79430.,  79430.,  79430.,  79430.,  79430.,  79430.,  &  !! See Medlyn et al. (2002)
304  &  79430.,  79430.,  79430.,  79430.,  79430.,  79430.  /)           !! from Bernacchi al. (2001)
305
306  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmO_mtc  = &            !! Energy of activation for KmO (J mol-1)
307  & (/undef,  36380.,  36380.,  36380.,  36380.,  36380.,  36380.,  &  !! See Medlyn et al. (2002)
308  &  36380.,  36380.,  36380.,  36380.,  36380.,  36380.  /)           !! from Bernacchi al. (2001)
309
310  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Sco_mtc  = &            !! Energy of activation for Sco (J mol-1)
311  & (/undef, -24460., -24460., -24460., -24460., -24460., -24460.,  &  !! See Table 2 of Yin et al. (2009)
312  & -24460., -24460., -24460., -24460., -24460., -24460.  /)           !! Value for C4 plants is not mentioned - We use C3 for all plants
313
314  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gamma_star_mtc  = &     !! Energy of activation for gamma_star (J mol-1)
315  & (/undef,  37830.,  37830.,  37830.,  37830.,  37830.,  37830.,  &  !! See Medlyn et al. (2002) from Bernacchi al. (2001)
316  &  37830.,  37830.,  37830.,  37830.,  37830.,  37830.  /)           !! for C3 plants - We use the same values for C4 plants
317
318  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Vcmax_mtc  = &          !! Energy of activation for Vcmax (J mol-1)
319  & (/undef,  71513.,  71513.,  71513.,  71513.,  71513.,  71513.,  &  !! See Table 2 of Yin et al. (2009) for C4 plants
320  &  71513.,  71513.,  71513.,  67300.,  71513.,  67300.  /)           !! and Kattge & Knorr (2007) for C3 plants (table 3)
321
322  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Jmax_mtc  = &            !! Energy of activation for Jmax (J mol-1)
323  & (/undef,  49884.,  49884.,  49884.,  49884.,  49884.,  49884.,  &   !! See Table 2 of Yin et al. (2009) for C4 plants
324  &  49884.,  49884.,  49884.,  77900.,  49884.,  77900.  /)            !! and Kattge & Knorr (2007) for C3 plants (table 3)
325
326  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: aSV_mtc     = &            !! a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1)
327  & (/undef,  668.39,  668.39,  668.39,  668.39,  668.39,  668.39,  &   !! See Table 3 of Kattge & Knorr (2007)
328  &  668.39,  668.39,  668.39,  641.64,  668.39,  641.64  /)            !! For C4 plants, we assume that there is no
329                                                                        !! acclimation and that at for a temperature of 25°C, aSV is the same for both C4 and C3 plants (no strong jusitification - need further parametrization)
330
331  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bSV_mtc     = &            !! b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1 °C-1)
332  & (/undef,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,  &   !! See Table 3 of Kattge & Knorr (2007)
333  &   -1.07,   -1.07,   -1.07,      0.,   -1.07,      0.  /)            !! We assume No acclimation term for C4 plants
334
335  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_mtc  =  &       !! minimum photosynthesis temperature (deg C)
336  & (/  undef,   -4.0,    -4.0,   -4.0,   -4.0,   -4.0,   -4.0,  & 
337  &      -4.0,   -20.0,   -4.0,   -4.0,   -4.0,   -4.0  /)
338
339  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_mtc  =  &       !! maximum photosynthesis temperature (deg C)
340  & (/  undef,   55.0,    55.0,   55.0,   55.0,   55.0,   55.0,  & 
341  &      55.0,   55.0,    55.0,   55.0,   55.0,   55.0  /)
342
343  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: aSJ_mtc     = &            !! a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1)
344  & (/undef,  659.70,  659.70,  659.70,  659.70,  659.70,  659.70,  &   !! See Table 3 of Kattge & Knorr (2007)
345  &  659.70,  659.70,  659.70,    630.,  659.70,    630.  /)            !! and Table 2 of Yin et al. (2009) for C4 plants
346
347  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bSJ_mtc     = &            !! b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1 °C-1)
348  & (/undef,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,  &   !! See Table 3 of Kattge & Knorr (2007)
349  &   -0.75,   -0.75,   -0.75,      0.,   -0.75,      0.  /)            !! We assume no acclimation term for C4 plants
350
351  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Vcmax_mtc  = &           !! Energy of deactivation for Vcmax (J mol-1)
352  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! Medlyn et al. (2002) also uses 200000. for C3 plants (same value than D_Jmax)
353  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! 'Consequently', we use the value of D_Jmax for C4 plants
354
355  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Jmax_mtc  = &            !! Energy of deactivation for Jmax (J mol-1)
356  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! See Table 2 of Yin et al. (2009)
357  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! Medlyn et al. (2002) also uses 200000. for C3 plants
358
359  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gm_mtc  = &              !! Energy of activation for gm (J mol-1)
360  & (/undef,  49600.,  49600.,  49600.,  49600.,  49600.,  49600.,  &   !! See Table 2 of Yin et al. (2009)
361  &  49600.,  49600.,  49600.,   undef,  49600.,   undef  /)           
362                 
363  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: S_gm_mtc  = &              !! Entropy term for gm (J K-1 mol-1)
364  & (/undef,   1400.,   1400.,   1400.,   1400.,   1400.,   1400.,  &   !! See Table 2 of Yin et al. (2009)
365  &   1400.,   1400.,   1400.,   undef,   1400.,   undef  /) 
366                 
367  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_gm_mtc  = &              !! Energy of deactivation for gm (J mol-1)
368  & (/undef, 437400., 437400., 437400., 437400., 437400., 437400.,  &   !! See Table 2 of Yin et al. (2009)
369  & 437400., 437400., 437400.,   undef, 437400.,   undef  /)           
370
371  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Rd_mtc  = &              !! Energy of activation for Rd (J mol-1)
372  & (/undef,  46390.,  46390.,  46390.,  46390.,  46390.,  46390.,  &   !! See Table 2 of Yin et al. (2009)
373  &  46390.,  46390.,  46390.,  46390.,  46390.,  46390.  /)           
374
375  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Vcmax25_mtc  =  &          !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
376  & (/ undef,   45.0,    45.0,    35.0,   40.0,   50.0,   45.0,  &      !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
377  &     35.0,   35.0,    50.0,    50.0,   60.0,   60.0  /)
378
379  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: arJV_mtc    = &            !! a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio (mu mol e- (mu mol CO2)-1)
380  & (/undef,    2.1,    2.5,    2.04,    2.22,    2.18,    2.28,  &   !! See Table 3 of Kattge & Knorr (2007)
381  &    2.18,    2.0,    2.0,    2.0,     2.0,     2.0  /)            !! For C4 plants, we assume that there is no
382                                                                        !! acclimation and that for a temperature of 25°C, aSV is the same for both C4 and C3 plants (no strong jusitification - need further parametrization)
383
384  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: brJV_mtc    = &            !! b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio ((mu mol e- (mu mol CO2)-1) (°C)-1)
385  & (/undef,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  &   !! See Table 3 of Kattge & Knorr (2007)
386  &  -0.035,  -0.035,  -0.035,      0.,  -0.035,      0.  /)            !! We assume No acclimation term for C4 plants
387
388  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmC25_mtc  = &             !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
389  & (/undef,   404.9,   404.9,   404.9,   404.9,  404.9,   404.9,  &    !! See Table 2 of Yin et al. (2009) for C4
390  &   404.9,   404.9,   404.9,    650.,   404.9,   650.  /)             !! and Medlyn et al (2002) for C3
391
392  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmO25_mtc  = &             !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
393  & (/undef, 278400., 278400., 278400., 278400., 278400., 278400.,  &   !! See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3
394  & 278400., 278400., 278400., 450000., 278400., 450000.  /)           
395
396  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Sco25_mtc  = &             !! Relative CO2 /O2 specificity factor for Rubisco at 25°C (bar bar-1)
397  & (/undef,   2800.,   2800.,   2800.,   2800.,   2800.,   2800.,  &   !! See Table 2 of Yin et al. (2009)
398  &   2800.,   2800.,   2800.,   2590.,   2800.,   2590.  /)           
399
400  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gm25_mtc  = &              !! Mesophyll diffusion conductance at 25°C (mol m-2 s-1 bar-1)
401  & (/undef,     0.4,     0.4,     0.4,     0.4,    0.4,      0.4,  &   !! See legend of Figure 6 of Yin et al. (2009)
402  &     0.4,     0.4,     0.4,   undef,     0.4,  undef  /)             !! and review by Flexas et al. (2008) - gm is not used for C4 plants
403
404  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gamma_star25_mtc  = &      !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
405  & (/undef,   42.75,   42.75,   42.75,   42.75,   42.75,   42.75,  &   !! See Medlyn et al. (2002) for C3 plants - For C4 plants, we use the same value (probably uncorrect)
406  &   42.75,   42.75,   42.75,   42.75,   42.75,   42.75  /)   
407
408  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
409  & (/undef,    0.95,    0.95,    0.95,    0.95,    0.95,  0.95,  &     !! Adjusted from Table 2 of Yin et al. (2009)
410  &    0.95,    0.95,    0.95,    0.82,    0.95,    0.82  /)           
411
412  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
413  & (/undef,    0.22,    0.22,    0.22,    0.22,    0.22,  0.22,  &     !! Adjusted from Table 2 of Yin et al. (2009)
414  &    0.22,    0.22,    0.22,    0.27,    0.22,    0.27  /)           
415
416  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: g0_mtc  = &                !! Residual stomatal conductance when irradiance approaches zero (mol CO2 m−2 s−1 bar−1)
417  & (/undef, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625,  &   !! Value from ORCHIDEE - No other reference.
418  & 0.00625, 0.00625, 0.00625, 0.01875, 0.00625, 0.01875  /)            !! modofy to account for the conversion for conductance to H2O to CO2
419
420  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: h_protons_mtc  = &         !! Number of protons required to produce one ATP (mol mol-1)
421  & (/undef,      4.,      4.,      4.,      4.,      4.,    4.,  &     !! See Table 2 of Yin et al. (2009) - h parameter
422  &      4.,      4.,      4.,      4.,      4.,      4.  /)           
423
424  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpsir_mtc = &              !! Fraction of PSII e− transport rate
425  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! partitioned to the C4 cycle (-)
426  &   undef,   undef,   undef,     0.4,   undef,    0.4  /)             !! See Table 2 of Yin et al. (2009) - x parameter       
427 
428  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fQ_mtc = &                 !! Fraction of electrons at reduced plastoquinone
429  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! that follow the Q-cycle (-) - Values for C3 platns are not used
430  &   undef,   undef,   undef,      1.,   undef,     1.  /)             !! See Table 2 of Yin et al. (2009)         
431
432  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpseudo_mtc = &            !! Fraction of electrons at PSI that follow
433  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! pseudocyclic transport (-) - Values for C3 platns are not used
434  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)             !! See Table 2 of Yin et al. (2009)   
435
436  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kp_mtc = &                 !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
437  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See Table 2 of Yin et al. (2009)
438  &   undef,   undef,   undef,     0.7,   undef,    0.7  /)                 
439
440  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_mtc = &              !! Fraction of PSII activity in the bundle sheath (-)
441  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
442  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)                 
443
444  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gbs_mtc = &                !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
445  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
446  &   undef,   undef,   undef,   0.003,   undef,  0.003  /)   
447
448  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: theta_mtc = &              !! Convexity factor for response of J to irradiance (-)
449  & (/undef,     0.7,     0.7,     0.7,     0.7,    0.7,    0.7,  &     !! See Table 2 of Yin et al. (2009)
450  &     0.7,     0.7,     0.7,     0.7,     0.7,    0.7  /)
451
452  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_LL_mtc = &           !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
453  & (/undef,     0.53,    0.53,    0.3,     0.3,    0.3,    0.3,  &     !! See comment from Yin et al. (2009) after eq. 4
454  &     0.3,     0.3,     0.3,     0.3,     0.3,    0.3  /)             !! alpha value from Medlyn et al. (2002)   
455                                                                        !! 0.093 mol CO2 fixed per mol absorbed photons
456                                                                        !! times 4 mol e- per mol CO2 produced
457
458  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_vcmax_mtc = &       !! Water stress on vcmax
459  & (/    1.,     1.,     1.,       1.,      1.,     1.,      1., &
460  &      1.,     1.,     1.,       1.,      1.,     1.  /)
461
462  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_gs_mtc = &          !! Water stress on gs
463  & (/    1.,     1.,     1.,       1.,      1.,     1.,      1., &
464  &      1.,     1.,     1.,       1.,      1.,     1.  /)
465
466  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_gm_mtc = &          !! Water stress on gm
467  & (/    1.,     1.,     1.,       1.,      1.,     1.,      1., &
468  &      1.,     1.,     1.,       1.,      1.,     1.  /)
469   
470  !-
471  ! 2 .Stomate
472  !-
473  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_mtc  =  &     !! extinction coefficient of the Monsi&Saeki
474  & (/ 0.5,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &             !! relationship (1953) ((m2[ground]) (m-2[leaf]))
475  &    0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
476  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_vegetfrac_mtc  =  &     !! extinction coefficient used for defining the fraction
477  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                       !!  of bare soil (unitless)
478  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
479  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_N_mtc  =  &    !! extinction coefficient of the leaf N content profile within the canopy
480  & (/ 0.15,  0.15,  0.15,  0.15,  0.15,  0.15,  0.15,  &             !! ((m2[ground]) (m-2[leaf]))
481  &    0.15,  0.15,  0.15,  0.15,  0.15,  0.15  /)                    !! based on Dewar et al. (2012, value of 0.18), on Carswell et al. (2000, value of 0.11 used in OCN)
482  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nue_opt_mtc = &           !! Nitrogen use efficiency of Vcmax
483  & (/ undef,   14.08,    30.0,    20.79,  19.95,  56.61, 20.59, &     !! ((mumol[CO2] s-1) (gN[leaf])-1)
484  &    27.75,   27.75,     45.,    45.,    60.,    60.     /)          !! based on the work of Kattge et al. (2009, GCB)
485  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vmax_uptake_nh4_mtc = &   !! Vmax of nitrogen uptake by plants for ammonium (umol (g DryWeight_root)-1 h-1)).
486  & (/ undef,   13.6,     12.0,   9.241, 18.0,   11.81,   8.217, &     !! from  Kronzucker et al. (1995, 1996) but externalized and tuned for ORC4
487  &    11.15,   11.15,     9.,    9.,     9.,    9. /)
488  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vmax_uptake_no3_mtc = &   !! Vmax of nitrogen uptake by plants for nitrate (umol (g DryWeight_root)-1 h-1))
489  & (/ undef,   13.13,  12.0,  13.03,  5.996,  17.31,   11.92, &       !! from Zaehle & Friend (2010) but externalized and tuned for ORC4
490  &      10.6,  10.6,    9.,    9.,    9.,      9. /)
491
492   
493  !
494  ! RESPIRATION (stomate)
495  !
496  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_mtc  =  &              !! fraction of GPP which is lost as growth respiration
497  & (/   0.28,   0.28,   0.28,   0.28,   0.28,   0.28,   0.28,  &
498  &      0.28,   0.28,   0.28,   0.28,   0.28,   0.28  /)
499
500   REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_c_mtc  =  &          !! slope of maintenance respiration coefficient (1/K),
501  & (/  undef,   0.44, 0.6, 0.2, 0.6, 0.3, 0.3, &                                   !! constant c of aT^2+bT+c, tabulated
502  &     0.4,     0.4,  0.5, 0.5, 0.5, 0.7  /)
503
504  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_b_mtc  =  &           !! slope of maintenance respiration coefficient (1/K),
505  & (/  undef,   -0.01, -0.01, -0.04, -0.02, -0.02, -0.01, &                        !! constant b of aT^2+bT+c, tabulated
506  &     -0.01,   -0.01, -0.01, -0.0,  -0.0, -0.01  /)
507
508  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_a_mtc  =  &           !! slope of maintenance respiration coefficient (1/K),
509  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                         !! constant a of aT^2+bT+c, tabulated
510  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)
511
512  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_maint_init_mtc  =   &            !! maintenance respiration coefficient
513  & (/  undef,  0.04531,  0.04,  0.07758,  0.02938,  0.361,  0.0318, &              !! at 10 deg C - from Sitch et al. 2003 and Zaehle (OCN)
514  &    0.1072,  0.1072,   0.06,  0.05,     0.05,     0.08  /)                       !! @tex $(gC.gN^{-1}.day^{-1})$ @endtex
515
516  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tref_maint_resp_mtc  =   &             !! maintenance respiration Temperature coefficient (deg C)
517  & (/   undef,     10.02,     10.02,     10.02,     10.02,     10.02,     10.02,  & 
518  &      10.02,     10.02,     10.02,     10.02,     10.02,     10.02  /)             
519  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_maint_resp_mtc  =   &             !! maintenance respiration Temperature coefficient (deg C)
520  & (/   undef,    -46.02,    -46.02,    -46.02,    -46.02,    -46.02,    -46.02,  & 
521  &     -46.02,    -46.02,    -46.02,    -46.02,    -46.02,    -46.02  /)             
522  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: e0_maint_resp_mtc  =   &               !! maintenance respiration Temperature coefficient (unitless)
523  & (/   undef,   308.56,     308.56,   308.56,     308.56,   308.56,     308.56,  & 
524  &     308.56,   308.56,     308.56,   308.56,     308.56,   308.56  /) 
525
526
527  !
528  ! Allocation (stomate)
529  !
530  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tref_labile_mtc  =   &                  !! Growth from labile pool - temperature at which all labile C will be allocated to growth (deg C)
531  & (/   undef,   5.0,      5.0,      5.0,      5.0,      5.0,      5.0,  & 
532  &       5.0,    5.0,      5.0,      5.0,      5.0,      5.0  /)             
533  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_labile_mtc  =   &                  !! Growth from labile pool  - temperature above which labile will be allocated to growth (deg C)
534  & (/   undef,    -2.0,    -2.0,    -2.0,    -2.0,    -2.0,    -2.0,  & 
535  &      -2.0,     -2.0,    -2.0,    -2.0,    -2.0,    -2.0  /) 
536  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: e0_labile_mtc  =   &                  !! Growth temperature coefficient - tuned see stomate_growth_fun_all.f90 (unitless)
537  & (/   undef,   15.0,     15.0,   15.0,     15.0,   15.0,     15.0,  & 
538  &      15.0,    15.0,     15.0,   15.0,     15.0,   15.0  /)
539  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: always_labile_mtc = &                 !! share of the labile pool that will remain in the labile pool (unitless)
540  & (/   undef,  0.01,  0.01,  0.01,  0.01,  0.01,  0.01,  0.01, &
541  &      0.01,   0.01,  0.01,  0.01,  0.01/)
542
543  !
544  ! SOM decomposition (stomate)
545  !
546  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_leaf_mtc = &        !! Lignin/C ratio of leaf pool (unitless)
547  & (/   0.15,   0.18,   0.18,   0.24,   0.18,   0.18,   0.24,  &   !! based on CN from White et al. (2000)       
548  &      0.18,   0.24,   0.09,   0.09,   0.09,   0.09  /)
549
550  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_sapabove_mtc = &    !! Lignin/C ratio of sapabove pool (unitless)
551  & (/   0.15,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
552  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
553
554  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_sapbelow_mtc = &    !! Lignin/C ratio of sapbelow pool (unitless)
555  & (/   0.15,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
556  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
557
558  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_heartabove_mtc = &  !! Lignin/C ratio of heartabove pool (unitless)
559  & (/   0.15,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
560  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
561
562  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_heartbelow_mtc = &  !! Lignin/C ratio of heartbelow pool (unitless)
563  & (/   0.15,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
564  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
565
566  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_fruit_mtc = &       !! Lignin/C ratio of fruit pool (unitless)
567  & (/   0.09,   0.09,   0.09,   0.09,   0.09,   0.09,   0.09,  &   !! based on CN from White et al. (2000)       
568  &      0.09,   0.09,   0.09,   0.09,   0.09,   0.09  /)
569
570  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_root_mtc = &        !! Lignin/C ratio of root pool (unitless)
571  & (/   0.22,   0.22,   0.22,   0.22,   0.22,   0.22,   0.22,  &   !! based on CN from White et al. (2000)       
572  &      0.22,   0.22,   0.22,   0.22,   0.22,   0.22  /)
573
574  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_carbres_mtc = &     !! Lignin/C ratio of carbres pool (unitless)
575  & (/   0.15,   0.18,   0.18,   0.24,   0.18,   0.18,   0.24,  &   !! based on CN from White et al. (2000)       
576  &      0.18,   0.24,   0.09,   0.09,   0.09,   0.09  /)
577
578  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_labile_mtc = &      !! Lignin/C ratio of labile pool (unitless)
579  & (/   0.15,   0.18,   0.18,   0.24,   0.18,   0.18,   0.24,  &   !! based on CN from White et al. (2000)       
580  &      0.18,   0.24,   0.09,   0.09,   0.09,   0.09  /)
581
582  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: decomp_factor_mtc  =  &  !! Multpliactive factor modifying the standard decomposition factor for each SOM pool
583  & (/     1.,     1.,     1.,     1.,     1.,     1.,     1.,  &         
584  &        1.,     1.,     1.,     1.,    1.2,    1.4  /)
585  !
586  ! STAND STRUCTURE
587  !
588  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: crown_to_height_mtc = &  !! Crown depth as a function of tree height (unitless)
589  &(/ undef,  0.5,    0.5,   0.7,   0.5,   0.66,   0.75, &
590  &     0.66,  0.66,  1.0, 1.0, 1.0, 1.0 /)
591
592  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: crown_vertohor_dia_mtc = & !! Crown diameter a function of crown depth (and thus tree height) (unitless).
593  &(/ undef,  2.0,    2.0,   0.5,   1.5,   1.0,   0.4, &
594  &     1.0,  1.0,  1.0, 1.0, 1.0, 1.0 /)
595
596  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tree_ff_mtc = &                          !! Tree form factor to reduc
597  &(/ undef, 0.4681,  0.4234,  0.6,  0.6,  0.703, 0.7501, &                           !! the volume of a cylinder
598  &    0.7,  0.8187,  1.0,     1.0,  1.0,  1.0 /)                                     !! to the volume of the real tree shape
599
600  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_density_mtc = &                     !! Wood density @tex $(gC.m^{-3})$ @endtex
601  &(/   undef,   2.87458e5,   2.68753e5,   2.08333e5,   3.0e5,   2.38e5,   1.95e5,  & !! Current values are taken from the trunk.
602  &    2.38e5,  2.4875e5,     2.0e5,       2.0e5,       2.0e5,   2.0e5  /)            !! forestry-branch has more realistic values
603                                                                                      !! in it. Source: AFOCEL 2006
604
605  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune1_mtc = &                       !! cn_area = pipe_tune1*...
606  &(/ undef,  undef,  undef,  undef,  undef,  undef,  undef, &                        !!    stem diameter**pipe_tune_exp_coeff
607  &    undef,  undef, undef, undef, undef, undef /)                                   !! for consistency reason pipe_tune1 is calculated as 0.66*pi/4*pipe_tune2**2
608                                                                                      !! see pft_parameters.f90
609       
610  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune2_mtc = &                       !! height=pipe_tune2 * diameter**pipe_tune3
611  &(/ undef,   55.,   55.,   45.,   14.,   50.,   30., &
612  &     30.,   30., undef, undef, undef, undef /) 
613
614  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune3_mtc = &                       !! height=pipe_tune2 * diameter**pipe_tune3
615  &(/ undef,   0.65,   0.65,   0.57,   0.33,   0.66,  0.58, &
616  &    0.52,   0.52,  undef,  undef,  undef,  undef /)   
617     
618  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune4_mtc = &                       !! CHECK - needed for stem diameter
619  &(/ undef,   0.3,   0.3,   0.3,   0.3,   0.3,   0.3, &
620        0.3,   0.3, undef, undef, undef, undef /)
621
622  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_k1_mtc = &                          !! CHECK
623  &(/ undef,  8.e3,  8.e3,  8.e3,  8.e3,  8.e3,  8.e3, &
624  &    8.e3,  8.e3, undef, undef, undef, undef /) 
625
626  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune_exp_coeff_mtc = &              !! cn_area = pipe_tune1*... 
627  &(/ undef,   undef,   undef,   undef,   undef,   undef,   undef, &                  !!    stem diameter**pipe_tune_exp_coeff
628  &     undef,   undef, undef, undef, undef, undef /)                                 !! for consistency reasons pipe_tune_exp_coeff is calculated as 2*pipe_tune3
629                                                                                      !! see pft_parameters.f90
630   
631  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mass_ratio_heart_sap_mtc = &             !! mass ratio (heartwood+sapwood)/heartwood
632  &(/ undef,    3.,    3.,    3.,    3.,    3.,    3., &
633  &      3.,    3., undef, undef, undef, undef /)
634
635  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: canopy_cover_mtc = &                     !! Prescribed canopy cover (1-gap fraction)
636  & (/ undef,    0.9,   0.9,   0.7,   0.7,   0.7,   0.6, &                            !! of a canopy (unitless)
637  &      0.5,    0.5,   0.9,   0.9,   0.9,   0.9 /) 
638
639  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: nmaxplants_mtc = &                    !! Initial number of trees per ha. This parameter is
640  & (/ undef,  15000.,  15000.,  15000.,  15000.,  15000., 15000.,  &                      !! used at .firstcall. and after clearcuts
641  &    15000.,  15000.,  10000.,  10000.,  10000.,  10000. /)                              !! the value is used by the allometric allocation
642                                                                                      !! and forestry subroutines.
643
644  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_init_mtc = &                      !! The height (m) of a grass or crop when the vegetation is established.
645  &(/ undef,  undef,  undef,  undef,  undef,  undef,  undef, &                        !! In combination with the parameter lai_to_height and the allometric relationships
646  &   undef,  undef,   0.3,   0.3,   0.2,   0.2 /)                                    !! this setting determines all biomass components of a newly establised vegetation
647
648  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: dia_init_min_mtc = &                     !! The minimum (above) diameter (m) of a tree sapling when a forest
649  &(/ undef,    0.02,    0.02,   0.02,    0.02,   0.02,   0.02, &                     !! stand is established. Owing to the allometric
650  &    0.02,    0.02,    undef,  undef,   undef,  undef /)
651                                           
652  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: dia_init_max_mtc = &                     !! The maximum (above) diameter (m) of a tree sapling when a forest
653  &(/ undef,    0.05,    0.05,    0.03,    0.03,   0.03,    0.03, &                   !! stand is established.
654  &    0.03,    0.03,    undef,   undef,   undef,  undef /)                                                       
655
656  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_self_thinning_mtc = &              !! Coefficient of the self-thinning relationship D=alpha*N^beta
657  &(/ undef,  2827.,  3700.,  1348.,  1220.,  2000.,  2827., &                        !! estimated from German, French, Spanish and Swedish
658  &     800.,  800.,  undef,  undef,  undef,  undef/)                                !! forest inventories
659 
660  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: beta_self_thinning_mtc = &               !! Exponent of the self-thinning relationship D=alpha*N^beta
661  &(/ undef,  -0.73,  -0.67,  -0.57,  -0.69,  -0.67,  -0.73, &                        !! estimated from German, French, Spanish and Swedish
662  &    -0.59, -0.59,  undef,  undef,  undef,  undef/)                                 !! forest inventories
663
664  !
665  ! RECRUITMENT (stomate) 
666  !                                                                       
667  LOGICAL, PARAMETER, DIMENSION(nvmc) :: recruitment_pft_mtc = &                      !! Do recruitment? (true/false) 
668  & (/ .FALSE.,   .TRUE.,   .TRUE.,    .TRUE.,    .TRUE.,    .TRUE.,   .TRUE.,  & 
669  &    .TRUE.,    .TRUE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE. /)   
670
671  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recruitment_height_mtc = &               !! Prescribed height (above) for the recruited stems @tex $(m)$ @endtex 
672  & (/ undef, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, &
673  &    undef, undef, undef, undef/)       
674
675  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recruitment_alpha_mtc = &                !! Alpha parameter for the power function (log-log)   
676  & (/ undef, -2.0, -2.0, -2.0, -2.0, -3.0, -2.5, -2.0, -2.0, &                       !! used to model recruitment from light @tex $(unitless)$ @endtex.
677  &    undef, undef, undef, undef/)                                                   !! It represents a measure of the mean log10 of the number of   
678                                                                                      !! recruits to be expected in 25 m2 at average light conditions
679                                                                                      !! (2% at BCI). Observed values for individual species in a tropical
680                                                                                      !! forest in Panama (BCI 50-ha plot) varied between -4.28 and -0.55
681                                                                                      !! with a community mean of -3.0 for typical light levels <20%.   
682                                                                                      !! For details see Ruger et al (2009), J. of Ecol.,
683                                                                                      !! doi:10.1111/j.1365-2745.2009.01552.x   
684
685  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recruitment_beta_mtc = &                 !! Beta parameter for the power function (log-log) used to model
686  &(/ undef, 0.8, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, &                                !! recruitment from light @tex $(unitless)$ @endtex. It measures
687  &   undef, undef, undef, undef/)                                                    !! the strength of the light response. Observed values
688                                                                                      !! for individual species in a tropical  forest in Panama (BCI 50-ha plot)
689                                                                                      !! varied between -0.72 and 3.28 with a community mean of 0.8
690                                                                                      !! (nearly linear response) for typical light levels <20%.
691                                                                                      !! For beta < 0, the number of recruits decreases with increasing light. 
692                                                                                      !! For 0<beta<1, the number of recruits increases in a decelerating
693                                                                                      !! way with increasing light. For beta=1 it is a linear relationship,
694                                                                                      !! and for beta>1 the number of recruits increases in an 
695                                                                                      !! accelerating way with light. For details see Ruger et al (2009),
696                                                                                      !! J. of Ecol., doi: 10.1111/j.1365-2745.2009.01552.x 
697  ! If ok_pest is true
698  LOGICAL, PARAMETER, DIMENSION(nvmc) :: beetle_pft_mtc = &                      !! Do bark beetle attack? (true/false) 
699  & (/ .FALSE.,   .FALSE.,   .FALSE.,   .TRUE.,   .FALSE.,   .FALSE.,.TRUE.,  &
700  &    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE. /)
701
702  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: remaining_beetles_mtc  =  &   !!
703  & (/  undef,   undef,   undef,   0.5,   undef,   undef,   0.5, & !!
704  &      undef,   undef,   undef,  undef,  undef,  undef  /)
705
706  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: pressure_feedback_mtc  =  &   !!
707  & (/  undef,   undef,   undef,   0.75,   undef,   undef,   0.75, & !!
708  &      undef,   undef,   undef,  undef,  undef,  undef  /)
709
710  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: age_susceptibility_a_mtc  =  &   !!
711  & (/  undef,   undef,   undef,   0.2,   undef,   undef,   0.2, & !!
712  &      undef,   undef,   undef,  undef,  undef,  undef  /)
713
714  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: age_susceptibility_b_mtc  =  &   !!
715  & (/  undef,   undef,   undef,  0.01094542,   undef,   undef,   0.01094542, & !!
716  &      undef,   undef,   undef,  undef,  undef,  undef  /)
717
718  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: age_susceptibility_c_mtc  =  &   !!
719  & (/  undef,   undef,   undef,   70.0,   undef,   undef,   70.0, &            !!
720  &      undef,   undef,   undef,  undef,  undef,  undef  /)
721
722  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: rdi_susceptibility_a_mtc  =  &   !!
723  & (/  undef,   undef,   undef,   -15.0,   undef,   undef,   -15.0, & !!
724  &      undef,   undef,   undef,  undef,  undef,  undef  /)
725
726  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: rdi_susceptibility_b_mtc  =  &   !!
727  & (/  undef,   undef,   undef,  0.4,   undef,   undef,   0.4, & !!
728  &      undef,   undef,   undef,  undef,  undef,  undef  /)
729
730  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: rdi_target_suscept_mtc  =  &   !!
731  & (/  undef,   undef,   undef,  0.6,   undef,   undef,   0.6, & !!
732  &      undef,   undef,   undef,  undef,  undef,  undef  /)
733
734  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: share_susceptibility_a_mtc  =  &   !!
735  & (/  undef,   undef,   undef,   15.5,   undef,   undef,   15.5, & !!
736  &      undef,   undef,   undef,  undef,  undef,  undef  /)
737
738  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: share_susceptibility_b_mtc  =  &   !!
739  & (/  undef,   undef,   undef,  0.6,   undef,   undef,   0.6, &!!
740  &      undef,   undef,   undef,  undef,  undef,  undef  /)
741
742  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: drought_susceptibility_a_mtc  =  &   !!
743  & (/  undef,   undef,   undef,   -9.5,   undef,   undef,   -9.5, & !!
744  &      undef,   undef,   undef,  undef,  undef,  undef  /)
745
746  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: drought_susceptibility_b_mtc  =  &   !!
747  & (/  undef,   undef,   undef,   0.4,   undef,   undef,   0.4, & !!
748  &      undef,   undef,   undef,  undef,  undef,  undef  /)
749
750  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: windthrow_susceptibility_tune_mtc  =  & !!
751  & (/  undef,   undef,   undef,   0.3,   undef,   undef,   0.3, &!!
752  &      undef,   undef,   undef,  undef,  undef,  undef  /)
753
754  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: beetle_generation_a_mtc  =& !! a parameter for the calculation of the number of beetle generation per year
755  & (/  undef,   undef,   undef,   3.307963,   undef,   undef, 3.307963, &!!
756  &      undef,   undef,   undef,  undef,  undef,  undef  /)
757
758  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: beetle_generation_b_mtc  =& !! b parameter for the calculation of the number of beetle generation per year
759  & (/  undef,   undef,   undef, 557.0,   undef,   undef, 557.0, &!!
760  &      undef,   undef,   undef,  undef,  undef,  undef  /)
761
762  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: beetle_generation_c_mtc  =& !! c parameter for the calculation of the number of beetle generation per year
763  & (/  undef,   undef,   undef, 1.980938,   undef,   undef, 1.980938, &!!
764  &      undef,   undef,   undef,  undef,  undef,  undef  /)
765
766  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: min_temp_beetle_mtc  =& !! temperature threshold below which Teff is not calculated (*C)
767  & (/  undef,   undef,   undef, 8.3,   undef,   undef, 8.3, &!!
768  &      undef,   undef,   undef,  undef,  undef,  undef  /)
769
770  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: max_temp_beetle_mtc  =& !! temperature threshold above which Teff is not calculated (*C)
771  & (/  undef,   undef,   undef, 38.4,   undef,   undef, 38.4, &!!
772  &      undef,   undef,   undef,  undef,  undef,  undef  /)
773
774  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: opt_temp_beetle_mtc  =& !! optimal temperature to breed bark beetle (*C)
775  & (/  undef,   undef,   undef, 30.3,   undef,   undef, 30.3, &!!
776  &      undef,   undef,   undef,  undef,  undef,  undef  /)
777
778
779  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: eff_temp_beetle_a_mtc  =& !! a parameter for the calculation of the effective temperature used in beetle phenology
780  & (/  undef,   undef,   undef,  0.02876507,   undef,   undef, 0.02876507, &!!
781  &      undef,   undef,   undef,  undef,  undef,  undef  /)
782
783  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: eff_temp_beetle_b_mtc  =& !! b parameter for the calculation of the effective temperature used in beetle phenology
784  & (/  undef,   undef,   undef, 40.9958913,   undef,   undef, 40.9958913, &!!
785  &      undef,   undef,   undef,  undef,  undef,  undef  /)
786
787  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: eff_temp_beetle_c_mtc  =& !! c parameter for the calculation of the effective temperature used in beetle phenology
788  & (/  undef,   undef,   undef, 3.5922336,   undef,   undef, 3.5922336, &!!
789  &      undef,   undef,   undef,  undef,  undef,  undef  /)
790
791  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: eff_temp_beetle_d_mtc  =& !! d parameter for the calculation of the effective temperature used in beetle phenology
792  & (/  undef,   undef,   undef, 1.24657367,   undef,   undef, 1.24657367, &!!
793  &      undef,   undef,   undef,  undef,  undef,  undef  /)
794
795  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: diapause_thres_daylength_mtc  =& !! daylength in hour above which bark beetle start diapause
796  & (/  undef,   undef,   undef,   14.5,   undef,   undef,   14.5, &!!
797  &      undef,   undef,   undef,  undef,  undef,  undef  /)
798
799  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: wght_sirdi_a_mtc  =& !!
800  & (/  undef,   undef,   undef,   -70.0,   undef,   undef,   -50.0, &!!
801  &      undef,   undef,   undef,  undef,  undef,  undef  /)
802  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: wght_sirdi_b_mtc  =& !!
803  & (/  undef,   undef,   undef,   0.1,   undef,   undef,   0.1, &!!
804  &      undef,   undef,   undef,  undef,  undef,  undef  /)
805  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: wght_sid_mtc  =& !!
806  & (/  undef,   undef,   undef,   0.2,   undef,   undef,   0.2, &!!
807  &      undef,   undef,   undef,  undef,  undef,  undef  /)
808  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: wght_sis_mtc  =& !!
809  & (/  undef,   undef,   undef,   0.2,   undef,   undef,   0.2, &!!
810  &      undef,   undef,   undef,  undef,  undef,  undef  /)
811
812
813  !
814  ! WINDFALL (stomate)
815  !
816
817  ! At the moment, species-related parameters are scarce (more tree pulling tests are needed), therefore defining parameters for metaclasses
818  ! is far from being straightforward.
819
820  ! NOTE:  All the parameter values below were originated from six needle-leaf species:
821  ! SS: Sitka Spruce
822  ! NS: Norway Spruce
823  ! SP: Scots Pine
824  ! LP: Lodgepople Pine
825  ! CP: Corsican Pine 
826  ! EL: European Larch
827  !     and three broad leaved species:
828  ! BI: Beech (Fagus)
829  ! BE: Birch (Betula)
830  ! OK: Oak   (Quercus)
831  ! see the parameter table for the detail of combination of species to PFT
832
833  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: streamlining_c_leaf_mtc  =  &   !! Streamlining parameter. @tex $(unitless)$ @endtex. Streamlining is the
834  & (/  undef,   2.34,   2.34,   2.70,   2.66,   2.34,   2.71, &            !! change of shape of the crowns due to wind. Used in the calculation of the
835  &      2.15,   3.07,   undef,  undef,  undef,  undef  /)                   !! critical wind speed according to the GALES (Hale et al. 2015) model.
836                                                                            !! In this case, the tree is in leaf.
837
838  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: streamlining_c_leafless_mtc = & !! Streamlining parameter. @tex $(unitless)$ @endtex. Streamlining is the
839  & (/  undef,   2.34,   2.34,   2.70,   2.66,   2.34,   2.71, &            !! change of shape of the crowns due to wind. Used in the calculation of the
840  &      2.15,   3.07,   undef,  undef,  undef,  undef  /)                   !! critical wind speed according to the GALES (Hale et al. 2015) model.
841                                                                            !! In this case, the tree is leafless.
842
843  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: streamlining_n_leaf_mtc  =  &   !! Streamlining parameter. @tex $(unitless)$ @endtex. Streamlining is the
844  & (/  undef,   0.88,   0.88,   0.64,   0.85,   0.88,   0.63, &            !! change of shape of the crowns due to wind. Used in the calculation of the
845  &      0.88,   0.75,   undef,  undef,  undef,  undef  /)                   !! critical wind speed according to the GALES (Hale et al. 2015) model.
846                                                                            !! In this case, the tree is in leaf.
847
848  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: streamlining_n_leafless_mtc = & !! Streamlining parameter. @tex $(unitless)$ @endtex. Streamlining is the
849  & (/  undef,   0.88,   0.88,   0.64,   0.85,   0.88,   0.63, &            !! change of shape of the crowns due to wind. Used in the calculation of the
850  &      0.88,   0.75,   undef,  undef,  undef,  undef  /)                   !! critical wind speed according to the GALES (Hale et al. 2015) model.
851                                                                            !! In this case, the tree is leafless.
852
853!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: streamlining_rb_leaf_mtc  =  &  !! Streamlining parameter. @tex $(unitless)$ @endtex. Streamlining is the
854!  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0, &                  !! change of shape of the crowns due to wind. Used in the calculation of the
855!  &      0.0,   0.0,   undef,  undef, undef, undef  /)                         !! critical wind speed according to the GALES (Hale et al. 2015) model.
856                                                                            !! In this case, the tree is in leaf.
857
858!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: streamlining_rb_leafless_mtc =& !! Streamlining parameter. @tex $(unitless)$ @endtex. Streamlining is the
859!  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0, &                  !! change of shape of the crowns due to wind. Used in the calculation of the
860!  &      0.0,   0.0,   undef,  undef, undef, undef  /)                         !! critical wind speed according to the GALES (Hale et al. 2015) model.
861                                                                            !! In this case, the tree is leafless.
862
863!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: canopy_density_leaf_mtc  =  &   !! Density of the tree canopy @tex $(kg/m^{3})$ @endtex, i.e. of the
864!  & (/  undef,   2.5,   2.5,   2.5,   2.5,   2.5,   2.5, &                  !! branches and leaves. Used in the calculation of the critical wind speed
865!  &      2.5,   2.5,   undef, undef,  undef, undef  /)                         !! according to the GALES (Hale et al. 2015) model.
866
867!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: canopy_density_leafless_mtc = & !! Density of the tree canopy @tex $(kg/m^{3})$ @endtex, i.e. of the
868!  & (/  undef,   2.5,   2.5,   2.5,   2.5,   2.5,   2.5, &                  !! branches (no leaves). Used in the calculation of the critical wind speed
869!  &      2.5,   2.5,   undef, undef,  undef, undef  /)                         !! according to the GALES (Hale et al. 2015) model.
870
871!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: intercept_breadth_mtc  =  &      !! Intercept in the equation for calculating the canopy breadth.
872!  & (/  undef,   0.5824,   0.5824,   0.5824,   0.5824,   0.5824,   0.5824, & !! @tex $(unitless)$ @endtex
873!  &      0.5824,   0.5824,  undef,  undef,   undef,  undef /)
874
875!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: slope_breadth_mtc  =  &          !! Slope in the equation for calculating the canopy breadth.
876!  & (/  undef,   0.115,   0.115,   0.115,   0.115,   0.115,   0.115, &       !! @tex $(unitless)$ @endtex
877!  &      0.115,   0.115,  undef,  undef,  undef, undef  /)
878
879!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: intercept_depth_mtc  =  &        !! Intercept in the equation for calculating the canopy depth.
880!  & (/  undef,   0.4206,   0.4206,   0.4206,   0.4206,   0.4206,   0.4206, & !! @tex $(unitless)$ @endtex
881!  &      0.4206,   0.4206,  undef,   undef,   undef,   undef  /)
882
883!  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: slope_depth_mtc  =  &            !! Slope in the equation for calculating the canopy depth.
884!  & (/  undef,   0.4368,   0.4368,   0.4368,   0.4368,   0.4368,   0.4368, & !! @tex $(unitless)$ @endtex
885!  &      0.4368,   0.4368,   undef,  undef,  undef,  undef /)
886
887  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: modulus_rupture_mtc  =  &  !! Modulus of rupture @tex $(Pa)$ @endtex. The measure of a species’ strength
888  & (/  undef,   6.23E7, 6.23E7, 4.13E7, 5.90E7, 6.23E7,  4.10E7, &    !! before rupture when being bent. Used in the calculation of the critical
889  &      6.27E7, 5.30E7,  undef,  undef,  undef,  undef  /)            !! wind speed according to the GALES (Hale et al. 2015) model. IMPORTANT:
890                                                                       !! greenwood values are used and not the more frequently available drywood
891                                                                       !! modulus of rupture.
892
893  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: f_knot_mtc  =  &           !! Knot Factor @tex $(unitless)$ @endtex. This modifier represents the knots
894  & (/  undef,   1.0,   1.0,   0.87, 1.0,  1.0,   0.88, &              !! in the wood, and hence the decrease in structural strength. Used in the
895  &      1.0,   0.85,   undef, undef, undef, undef /)                  !! calculation of the critical wind speed according to the GALES
896                                                                       !! (Hale et al. 2015) model.
897
898  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_free_draining_shallow_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
899  & (/  undef,   175.3,   175.3,   134.7,  198.5,   175.3,  132.6, &   !! This is derived from the generic soil type (free_draining mineral soils;
900  &      152.0,  145.2,   undef,   undef,  undef,   undef /)           !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
901                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
902                                                                       !! according to the GALES (Hale et al. 2015) model.
903                                                                       !! In this case, the tree is in leaf.
904
905  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_free_draining_shallow_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
906  & (/  undef,   175.3,  175.3,   134.7,   198.5,   175.3,  132.6,   & !! This is derived from the generic soil type (free_draining mineral soils;
907  &      152.0,  145.2,  undef,   undef,   undef,   undef /)           !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
908                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
909                                                                       !! according to the GALES (Hale et al. 2015) model.
910                                                                       !! In this case, the tree is leafless.
911
912  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_free_draining_deep_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
913  & (/  undef,   203.8,   203.8,   157.2,   230.8,   230.8,   154.8, & !! This is derived from the generic soil type (free_draining mineral soils;
914  &     176.7,   169.4,  undef,   undef,   undef,   undef  /)          !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
915                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
916                                                                       !! according to the GALES (Hale et al. 2015) model.
917                                                                       !! In this case, the tree is in leaf.
918
919  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_free_draining_deep_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
920  & (/  undef,   203.8,   203.8,   157.2,   230.8,   230.8,   154.8, & !! This is derived from the generic soil type (free_draining mineral soils;
921  &      176.7,  169.4,   undef,  undef,   undef,  undef  /)           !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
922                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
923                                                                       !! according to the GALES (Hale et al. 2015) model.
924                                                                       !! In this case, the tree is leafless.
925
926  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_free_draining_average_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
927  & (/  undef,   178.7,   178.7,   137.8,   202.4,   178.7,   135.7, & !! This is derived from the generic soil type (free_draining mineral soils;
928  &      155.0,  148.6,   undef,   undef,  undef,   undef  /)          !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
929                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
930                                                                       !! according to the GALES (Hale et al. 2015) model.
931                                                                       !! In this case, the tree is in leaf.
932
933  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_free_draining_average_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
934  & (/  undef,   178.7,   178.7,   137.8,   202.4,   178.7,   135.7, & !! This is derived from the generic soil type (free_draining mineral soils;
935  &      155.0,  148.6,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
936                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
937                                                                       !! according to the GALES (Hale et al. 2015) model.
938                                                                       !! In this case, the tree is leafless.
939
940  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_gleyed_shallow_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
941  & (/  undef,   155.4,   155.4,   119.4,   176.0,   155.4,   117.6, & !! This is derived from the generic soil type (free_draining mineral soils;
942  &      134.8,  128.7,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
943                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
944                                                                       !! according to the GALES (Hale et al. 2015) model.
945                                                                       !! In this case, the tree is in leaf.
946
947  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_gleyed_shallow_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
948  & (/  undef,   155.4,   155.4,   119.4,   176.0,   155.4,   117.6, & !! This is derived from the generic soil type (free_draining mineral soils;
949  &      134.8,  128.7,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
950                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
951                                                                       !! according to the GALES (Hale et al. 2015) model.
952                                                                       !! In this case, the tree is leafless.
953
954  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_gleyed_deep_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
955  & (/  undef,   180.6,   180.6,   139.3,   204.6,   180.6,   137.2, & !! This is derived from the generic soil type (free_draining mineral soils;
956  &     156.7,   150.2,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
957                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
958                                                                       !! according to the GALES (Hale et al. 2015) model.
959                                                                       !! In this case, the tree is in leaf.
960
961  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_gleyed_deep_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
962  & (/  undef,   180.6,   180.6,   139.3,   204.6,   180.6,   137.2, & !! This is derived from the generic soil type (free_draining mineral soils;
963  &     156.7,   150.2,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
964                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
965                                                                       !! according to the GALES (Hale et al. 2015) model.
966                                                                       !! In this case, the tree is leafless.
967
968  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_gleyed_average_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
969  & (/  undef,   158.5,   158.5,   122.2,   179.5,   158.5,  120.3, &  !! This is derived from the generic soil type (free_draining mineral soils;
970  &     137.4,   131.7,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
971                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
972                                                                       !! according to the GALES (Hale et al. 2015) model.
973                                                                       !! In this case, the tree is in leaf.
974
975  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_gleyed_average_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
976  & (/  undef,   158.8,   158.5,   122.2,   179.5,   158.5,   120.3, & !! This is derived from the generic soil type (free_draining mineral soils;
977  &     137.4,   131.7,   undef,   undef,   undef,   undef /)          !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
978                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
979                                                                       !! according to the GALES (Hale et al. 2015) model.
980                                                                       !! In this case, the tree is leafless.
981
982  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peaty_shallow_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
983  & (/  undef,   169.7,   169.7,   130.4,   192.2,   169.7,   128.4, & !! This is derived from the generic soil type (free_draining mineral soils;
984  &      147.2,  140.6,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
985                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
986                                                                       !! according to the GALES (Hale et al. 2015) model.
987                                                                       !! In this case, the tree is in leaf.
988
989  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peaty_shallow_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
990  & (/  undef,   169.7,   169.7,   130.4,   192.2,   169.7,   128.4, & !! This is derived from the generic soil type (free_draining mineral soils;
991  &      147.2,  140.6,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
992                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
993                                                                       !! according to the GALES (Hale et al. 2015) model.
994                                                                       !! In this case, the tree is leafless.
995
996  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peaty_deep_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
997  & (/  undef,   191.4,   191.4,   152.1,   223.5,   191.4,   141.9, & !! This is derived from the generic soil type (free_draining mineral soils;
998  &      159.2,  164.0,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
999                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1000                                                                       !! according to the GALES (Hale et al. 2015) model.
1001                                                                       !! In this case, the tree is in leaf.
1002
1003  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peaty_deep_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1004  & (/  undef,   191.4,   191.4,   152.1,   223.5,   191.4,   141.9, & !! This is derived from the generic soil type (free_draining mineral soils;
1005  &      159.2,  164.0,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1006                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1007                                                                       !! according to the GALES (Hale et al. 2015) model.
1008                                                                       !! In this case, the tree is leafless.
1009
1010  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peaty_average_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1011  & (/  undef,   178.9,   178.9,   133.4,   195.9,   178.9,  131.4, &  !! This is derived from the generic soil type (free_draining mineral soils;
1012  &     162.0,   143.8,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1013                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1014                                                                       !! according to the GALES (Hale et al. 2015) model.
1015                                                                       !! In this case, the tree is in leaf.
1016
1017  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peaty_average_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1018  & (/  undef,   178.9,   178.9,   133.4,   195.9,   178.9,  131.4, &  !! This is derived from the generic soil type (free_draining mineral soils;
1019  &     162.0,   143.8,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1020                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1021                                                                       !! according to the GALES (Hale et al. 2015) model.
1022                                                                       !! In this case, the tree is leafless.
1023
1024  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peat_shallow_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1025  & (/  undef,   193.0,   193.0,   148.3,  218.6,  193.0,   146.0, &   !! This is derived from the generic soil type (free_draining mineral soils;
1026  &     167.4,   159.9,   undef,   undef,  undef,  undef  /)           !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1027                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1028                                                                       !! according to the GALES (Hale et al. 2015) model.
1029                                                                       !! In this case, the tree is in leaf.
1030
1031  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peat_shallow_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1032  & (/  undef,   193.0,   193.0,   148.3,   218.6, 193.0,   146.0, &   !! This is derived from the generic soil type (free_draining mineral soils;
1033  &     167.4,   159.9,   undef,   undef,   undef, undef  /)           !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1034                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1035                                                                       !! according to the GALES (Hale et al. 2015) model.
1036                                                                       !! In this case, the tree is leafless.
1037
1038  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peat_deep_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1039  & (/  undef,   224.4,  224.4,  173.1,   254.2,  224.4,  170.4, &     !! This is derived from the generic soil type (free_draining mineral soils;
1040  &     194.7,   186.6,  undef,  undef,   undef,  undef  /)            !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1041                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1042                                                                       !! according to the GALES (Hale et al. 2015) model.
1043                                                                       !! In this case, the tree is in leaf.
1044
1045  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peat_deep_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1046  & (/  undef,  224.4,   224.4,  173.1,  254.2,  224.4,   170.4, &     !! This is derived from the generic soil type (free_draining mineral soils;
1047  &     194.7,  186.6,   undef,  undef,  undef,  undef  /)             !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1048                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1049                                                                       !! according to the GALES (Hale et al. 2015) model.
1050                                                                       !! In this case, the tree is leafless.
1051
1052  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peat_average_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1053  & (/  undef,   196.9,   196.9,   151.8,   223.0,   196.9,   149.4, & !! This is derived from the generic soil type (free_draining mineral soils;
1054  &     170.8,   163.6,   undef,   undef,   undef,   undef  /)         !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1055                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1056                                                                       !! according to the GALES (Hale et al. 2015) model.
1057                                                                       !! In this case, the tree is in leaf.
1058
1059  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: overturning_peat_average_leafless_mtc  =  &  !! Overturning moment multiplier @tex $(Nm/kg)$ @endtex.
1060  & (/  undef,  196.9,   196.9,   151.8,   223.0,   196.9,    149.4, & !! This is derived from the generic soil type (free_draining mineral soils;
1061  &     170.8,  163.6,   undef,   undef,   undef,   undef  /)          !! Gleyed mineral soils; Peaty mineral soils; Deep peats) and the soil depth
1062                                                                       !! (shallow, deep, average). Used in the calculation of the critical wind speed
1063                                                                       !! according to the GALES (Hale et al. 2015) model.
1064                                                                       !! In this case, the tree is leafless.
1065
1066  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: max_damage_further_mtc = & !! A tunning parameter for determining wind damage rate/level @text $(unitless)$ @endtex. 
1067  & (/    undef,   0.8,   0.8,   0.8,   0.8,   0.8,   0.8, &           !! The value of this tunning parameter is suggested by filed observation data for
1068  &       0.8,   0.8,  undef,   undef,   undef, undef /)               !! different PFTs.
1069 
1070  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: max_damage_closer_mtc = &  !! A tunning parameter for determining wind damage rate/level @text $(unitless)$ @endtex.
1071  & (/    undef,   0.8,   0.8,   0.8,   0.8,   0.8,   0.8, &           !! The value of this tunning parameter is suggested by filed observation data for
1072  &       0.8,   0.8,  undef,   undef,  undef, undef /)                !! different PFTs.
1073
1074  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: sfactor_further_mtc  =  &  !! A tunning parameter for determining wind damage rate/level @text $(unitless)$ @endtex.
1075  & (/    undef,   0.8,   0.8,   0.8,   0.8,   0.8,   0.8, &           !! The value of this tunning parameter is suggested by filed observation data for
1076  &       0.8,   0.8,  undef,   undef,  undef,  undef /)               !! different PFTs.
1077
1078  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: sfactor_closer_mtc  =  &   !! A tunning parameter for determining wind damage rate/level @text $(unitless)$ @endtex.
1079  & (/    undef,   0.8,   0.8,   0.8,   0.8,   0.8,   0.8, &           !! The value of this tunning parameter is suggested by filed observation data for
1080  &       0.8,   0.8,  undef,  undef,  undef,  undef /)                !! different PFTs.
1081
1082  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: green_density_mtc  =  &    !! The green wood density of the meta classes sepcies @text $(kg/m^3)$ @endtex.
1083  & (/    undef,  1007.,   1007.,   985.,  1060., 1007., 990.,    &    !! 
1084  &       968.,    900.,   undef,  undef,  undef, undef /)             !!
1085
1086  !
1087  ! FIRE (stomate)
1088  !
1089  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: flam_mtc  =  &         !! flamability: critical fraction of water
1090  & (/  undef,   0.15,   0.25,   0.25,   0.25,   0.25,   0.25,  &  !! holding capacity (0-1, unitless)
1091  &      0.25,   0.25,   0.25,   0.25,   0.35,   0.35  /)
1092
1093  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: resist_mtc  =  &       !! fire resistance (0-1, unitless)
1094  & (/ undef,   0.95,   0.90,   0.90,   0.90,   0.90,   0.90,  &
1095  &    0.90,    0.90,    0.0,    0.0,    0.0,    0.0 /) 
1096
1097
1098  !
1099  ! FLUX - LUC
1100  !
1101  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_1_mtc  =  &   !! Coeff of biomass export for the year
1102  & (/  undef,   0.897,   0.897,   0.597,   0.597,   0.597,   0.597,  &   !! (0-1, unitless)
1103  &     0.597,   0.597,   1.000,   1.000,   1.000,   1.000  /)
1104
1105  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_10_mtc  =  &  !! Coeff of biomass export for the decade
1106  & (/  undef,   0.103,   0.103,   0.299,   0.299,   0.299,   0.299,  &   !! (0-1, unitless)
1107  &     0.299,   0.299,   0.000,   0.000,   0.000,   0.000  /) 
1108
1109  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_100_mtc  =  & !! Coeff of biomass export for the century
1110  & (/  undef,     0.0,     0.0,   0.104,   0.104,   0.104,   0.104,  &   !! (0-1, unitless)
1111  &     0.104,   0.104,     0.0,   0.000,   0.000,   0.000  /)
1112
1113  !
1114  ! FLUX - LUC
1115  !
1116  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_s_mtc  =  &   !! Coeff of biomass export for the year
1117  & (/  undef,   0.897,   0.897,   0.597,   0.597,   0.597,   0.597,  &   !! (0-1, unitless)
1118  &     0.597,   0.597,   1.000,   1.000,   1.000,   1.000  /)
1119
1120  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_m_mtc  =  &   !! Coeff of biomass export for the decade
1121  & (/  undef,   0.103,   0.103,   0.299,   0.299,   0.299,   0.299,  &   !! (0-1, unitless)
1122  &     0.299,   0.299,   0.000,   0.000,   0.000,   0.000  /)
1123
1124  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_l_mtc  =  &   !! Coeff of biomass export for the century
1125  & (/  undef,     0.0,     0.0,   0.104,   0.104,   0.104,   0.104,  &   !! (0-1, unitless)
1126  &     0.104,   0.104,     0.0,   0.000,   0.000,   0.000  /)
1127
1128
1129
1130  !
1131  ! PHENOLOGY
1132  !
1133  ! The latest modifications regarding senescence_temp_c, leaffall, hum_min_time and nosenescence_hum are inspired by
1134  ! MacBean et al. (2015), following the optimization of phenology parameters using MODIS NDVI (FM/PP).
1135  !-
1136  ! 1. Stomate
1137  !-
1138  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_max_to_happy_mtc  =  &  !! threshold of LAI below which plant uses carbohydrate reserves
1139  & (/  undef,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &
1140  &       0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
1141
1142  REAL(r_std), PARAMETER, DIMENSION (nvmc) :: lai_max_mtc  =  &          !! maximum LAI, PFT-specific
1143  & (/ undef,   7.0,   5.0,   5.0,   4.0,   5.0,   3.5,  &               !! @tex $(m^2.m^{-2})$ @endtex
1144  &      4.0,   3.0,   2.5,   2.0,   5.0,   5.0  /)
1145
1146  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pheno_type_mtc  =  &     !! type of phenology (0-4, unitless)
1147  & (/  0,   1,   3,   1,   1,   2,   1,  &                              !! 0=bare ground 1=evergreen,  2=summergreen,
1148  &     2,   2,   4,   4,   2,   3  /)                                   !! 3=raingreen,  4=perennial
1149  !-
1150  ! 2. Leaf Onset
1151  !-
1152  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: force_pheno_mtc = &           !! Number of days after the mean
1153  & (/ undef,  undef,  42.,  undef,  undef,  42.,  undef, &                  !! doy at which budbreak occurs
1154  &    28.,  28.,  35.,  35.,  28.,  28. /)                                       !! at which phenology will be forced
1155 
1156  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_c_mtc  =  &    !! critical gdd, tabulated (C),
1157  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant c of aT^2+bT+c
1158  &     undef,   undef,   320.0,   400.0,   400.0,   450.0  /)
1159
1160  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_b_mtc  =  &    !! critical gdd, tabulated (C),
1161  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant b of aT^2+bT+c
1162  &     undef,   undef,    6.25,     0.0,    6.25,     0.0  /)
1163
1164  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_a_mtc  =  &    !! critical gdd, tabulated (C),
1165  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  &  !! constant a of aT^2+bT+c
1166  &     undef,   undef,   0.03125,     0.0,  0.0315,   0.0  /)
1167
1168  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_moigdd_t_crit_mtc  = &  !! temperature threshold for C4 grass(C)
1169  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  & 
1170  &     undef,   undef,     undef,    22.0,   undef,   undef  /)
1171
1172  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ngd_crit_mtc  =  &            !! critical ngd, tabulated.
1173  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! Threshold -5 degrees (days)
1174  &     undef,     5.0,   undef,   undef,   undef,   undef  /)
1175
1176  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ncdgdd_temp_mtc  =  &         !! critical temperature for the ncd vs. gdd
1177  & (/  undef,   undef,   undef,   undef,   undef,     5.0,   undef,  &    !! function in phenology (C)
1178  &     -10.0,   -10.0,   undef,   undef,   undef,   undef  /)
1179
1180  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_frac_mtc  =  &            !! critical humidity (relative to min/max)
1181  & (/  undef,   undef,   0.5,   undef,   undef,   undef,   undef, &       !! for phenology (unitless)
1182  &     undef,   undef,   0.5,     0.5,     0.5,     0.5  /)
1183
1184  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_min_time_mtc  =  &        !! minimum time elapsed since
1185  & (/  undef,   undef,   50.0,   undef,   undef,   undef,   undef,  &     !! moisture minimum (days)
1186  &     undef,   undef,   36.0,    35.0,    50.0,    75.0  /) 
1187
1188  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: longevity_root_mtc  =  &      !! roots longevity (days). This parameter describes the root turnover
1189  & (/  undef,  200.,   200.,    300.,    300.,   300.,   300.,  &         !! within the growing season. A longevity of 1000 days implies that every
1190  &      300.,  300.,   100.,    100.,    100.,   100.  /)                 !! day 1/1000 of the root mass will be replaced. For a temperate PFT this
1191                                                                           !! implies that that 18% of the root mass dies (and thus needs to be
1192                                                                           !! replaced) within the growing season. This definition is straightforward
1193                                                                           !! for evergreen species but needs the above nuance for deciduous PFTs
1194
1195  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: longevity_sap_mtc  =  &       !! time (days). Because the sapwood is always there, the definition of this 
1196  & (/  undef, 7300., 3766., 3600., 6643., 2140., 4046., &                 !! parameter is straightforward for evergeens and deciduous species. A longevity
1197  &     2140., 2140., 180.,  180.,  480.,  480. /)                         !! of 7300 days means that 5% of the sapwood will turnover every year.
1198
1199  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: longevity_leaf_mtc  =  &      !! leaf longevity (days). This parameter describes the leaf
1200  & (/  undef,   730.,   180.,    910.,   730.,   180.,   2000.,  &       !! longevity at a location with the average temperature for the range of the PFT
1201  &      180.,   180.,   180.,    180.,   200.,   200.  /)               !! It is used to calculate leaf_age_crit (as a function of temperature.
1202                                                                           !! The variable leaf_age_crit describes the maximum leaf age. If the
1203                                                                           !! actual leaf age exceeds leaf_age_crit, senescence will start.
1204                                                                           !! This definition is straightforward for evergreen species but needs some
1205                                                                           !! nuance for deciduous PFTs because it is not clear when within season turnover
1206                                                                           !! (describing stochastic processes of leaf mortality due to insects, wind, and
1207                                                                           !! self-shading) are overruled by climatological senescence.
1208
1209  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_age_crit_tref_mtc = &    !! Reference temperature of the PFT (degrees Celsius)
1210  & (/ undef,   25.,   25.,   15.,   20.,   15.,   5.,    &                !! Used to calculate the leaf_age_crit as a function of
1211  &       5.,    5.,   15.,   20.,   15.,   20.    /)                      !! longevity_leaf
1212
1213  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_age_crit_coeff1_mtc = &  !! Coeff1 (unitless) to link leaf_age_crit to leaf_age_crit_tref
1214  & (/ undef,   1.,   1.,   1.,   1.,   1.,   2.0,    &               
1215  &       1.,   1.,   1.5,   1.5,   1.5,   1.5  /)     
1216 
1217  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_age_crit_coeff2_mtc = &  !! Coeff2 (unitless) to link leaf_age_crit to leaf_age_crit_tref
1218  & (/ undef,   1.,   1.,   1.,   1.,   1.,   0.365,    &               
1219  &       1.,   1.,   0.75,   0.75,   0.75,   0.75 /) 
1220
1221  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaf_age_crit_coeff3_mtc = &  !! Coeff3 (unitless) to link leaf_age_crit to leaf_age_crit_tref
1222  & (/ undef,   0.,   0.,   0.,   0.,   0.,   120.,    &               
1223  &       0.,   0.,   10.,   10.,   10.,   10.  /) 
1224
1225  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: longevity_fruit_mtc  =  &     !! fruit lifetime (days)
1226  & (/  undef,  90.0,    90.0,    90.0,    90.0,   90.0,   90.0,  &
1227  &      90.0,  90.0,    undef,   undef,   undef,  undef  /)
1228
1229  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ecureuil_mtc  =  &            !! fraction of primary leaf and root allocation
1230  & (/  undef,   0.0,   1.0,   0.0,   0.0,   1.0,   0.0,  &                !! put into reserve (0-1, unitless)
1231  &       1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
1232
1233  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_min_mtc  =  &           !! NEW - allocation above/below = f(age)
1234  & (/    0.2,   0.2,   0.2,   0.2,   0.2,  0.2,   0.35,  &
1235  &       0.7,   0.2,   0.2,   0.2,   0.2,  0.2  /)
1236
1237  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_max_mtc  =  &           !! NEW - allocation above/below = f(age)
1238  & (/    0.8,   0.8,   0.8,   0.8,   0.8,   0.8,   0.8,  &
1239  &       0.8,   0.8,   0.8,   0.8,   0.8,   0.8  /)
1240
1241  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: demi_alloc_mtc  =  &          !! NEW - allocation above/below = f(age)
1242  & (/  undef,   5.0,     5.0,     5.0,     5.0,    5.0,   5.0,  &         !! - 30/01/04 NV/JO/PF
1243  &       5.0,   5.0,   undef,   undef,   undef,   undef  /)
1244
1245  !-
1246  ! 3. Senescence
1247  !-
1248  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaffall_mtc  =  &             !! length of death of leaves, tabulated (days)
1249  & (/  undef,   undef,   5.0,    undef,    undef,   15.0,   undef,  &
1250  &      25.0,    25.0,    5.0,     5.0,    undef,   undef  /)
1251
1252  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: presenescence_ratio_mtc  =  &  !! The ratio of maintenance respiration to
1253  & (/  undef,   0.6,     0.6,     0.6,     0.6,     0.6,     0.6,  &       !! gpp beyond which presenescence stage of
1254  &       0.6,   0.6,     0.6,     0.6,     0.6,     0.6  /)                !! plant phenology is declared to begin (0-1, unitless)
1255
1256  CHARACTER(LEN=6), PARAMETER, DIMENSION(nvmc) :: senescence_type_mtc  =  & !! type of senescence, tabulated (unitless)
1257  & (/  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ',  &
1258  &     'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ',  &
1259  &     'mixed ',  'crop  ',   'crop  '            /)
1260
1261  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_hum_mtc  =  &       !! critical relative moisture availability
1262  & (/  undef,   undef,   0.3,   undef,   undef,   undef,   undef,  &       !! for senescence (0-1, unitless)
1263  &     undef,   undef,   0.2,     0.2,     0.3,     0.2  /)
1264
1265  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nosenescence_hum_mtc  =  &     !! relative moisture availability above which
1266  & (/  undef,   undef,   0.8,   undef,   undef,   undef,   undef,  &       !! there is no humidity-related senescence
1267  &     undef,   undef,   0.3,     0.3,     0.3,     0.3  /)                !! (0-1, unitless)
1268
1269  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_turnover_time_mtc  =  &    !! maximum turnover time for grasses (days)
1270  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
1271  &     undef,   undef,    80.0,    80.0,    80.0,    80.0  /)
1272
1273  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_turnover_time_mtc  =  &    !! minimum turnover time for grasses (days)
1274  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
1275  &     undef,   undef,    10.0,    10.0,    10.0,    10.0  /)
1276 
1277  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recycle_leaf_mtc = &           !! Fraction of N leaf that is recycled when leaves are senescent
1278  & (/  undef,     0.5,     0.5,     0.5,     0.5,     0.5,     0.5,  &
1279  &       0.5,     0.5,     0.5,     0.5,     0.5,     0.5  /)
1280
1281  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recycle_root_mtc = &           !! Fraction of N leaf that is recycled when leaves are senescent
1282  & (/  undef,     0.2,     0.2,     0.2,     0.2,     0.2,     0.2,  &
1283  &       0.2,     0.2,     0.2,     0.2,     0.2,     0.2  /)
1284
1285  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_leaf_age_for_senescence_mtc  =  &  !! minimum leaf age to allow
1286  & (/  undef,   undef,   90.0,   undef,   undef,   90.0,   undef,  &               !! senescence g (days)
1287  &      60.0,    60.0,   30.0,    30.0,    30.0,   30.0  /)
1288
1289  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_c_mtc  =  &    !! critical temperature for senescence (C)
1290  & (/  undef,   undef,    undef,   undef,   undef,   12.5,   undef,  &     !! constant c of aT^2+bT+c, tabulated
1291  &      12.5,    12.5,      5.0,     5.0,     12.0,    13.0  /)             !! (unitless)
1292
1293  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_b_mtc  =  &    !! critical temperature for senescence (C),
1294  & (/  undef,   undef,   undef,   undef,   undef,   0.0,   undef,  &       !! constant b of aT^2+bT+c, tabulated
1295  &       0.0,     0.0,     0.1,     0.0,     0.0,   0.0  /)                !! (unitless)
1296
1297  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_a_mtc  =  &    !! critical temperature for senescence (C),
1298  & (/  undef,   undef,     undef,   undef,   undef,   0.0,   undef,  &     !! constant a of aT^2+bT+c, tabulated
1299  &       0.0,     0.0,   0.00375,     0.0,     0.0,   0.0  /)              !! (unitless)
1300
1301  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gdd_senescence_mtc  =  &       !! minimum gdd to allow senescence of crops (days)
1302  & (/  undef,   undef,    undef,   undef,     undef,    undef,    undef,  &
1303  &     undef,   undef,    undef,   undef,     2500.,    2500.  /)
1304
1305  LOGICAL, PARAMETER, DIMENSION(nvmc) :: always_init_mtc  =  &              !! take carbon from atmosphere if carbohydrate reserve too small (true/false)
1306  & (/ .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE., &!! default is true for all pfts except pft=11 C4 grass
1307  &    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE. /)   
1308
1309  !-
1310  ! 4. N cycle
1311  !-
1312  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cn_leaf_min_mtc  = &            !! minimum CN ratio of leaves
1313  & (/  undef,     16.,      16.,     28.2,       16.,      16.,      28.2, &  !! (gC/gN)
1314  &       16.,     16.,      16.,     16.,       16.,      16.   /)
1315
1316  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cn_leaf_max_mtc  = &            !! maximum CN ratio of leaves
1317 & (/   undef,     45.5,      45.5,     74.8,       45.5,      45.5,      74.8,  & !! (gC/gN)
1318 &        45.5,     45.5,      45.5,     45.5,       45.5,      45.5   /)
1319
1320  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_soil_n_bnf_mtc   = &        !! Value of total N (NH4+NO3)
1321 & (/     0.0,     1.5,      1.5,     1.5,       1.5,      1.5,      1.5,  & 
1322 &        1.5,     1.5,       2.,      2.,        2.,       2.   /)          !! above which we stop adding N via BNF
1323                                                                             !! (gN/m**2)
1324  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: manure_pftweight_mtc = &        !! Weight of the distribution of manure over the PFT surface
1325 & (/   0.,     0.,      0.,     0.,       0.,      0.,      0.,  &          !!(to a same number correspond the same concentration)
1326 &        0.,     0.,      1.,     1.,       1.,      1.   /)
1327
1328  !
1329  ! DGVM
1330  !
1331  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: residence_time_mtc  =  &    !! residence time of trees (years)
1332  & (/  undef,   1000.0,   1000.0,   1000.0,   1000.0,   1000.0,   1000.0,  &
1333  &     1000.0,  1000.0,   undef,    undef,    undef,    undef  /) 
1334
1335  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_crit_mtc  =  &
1336  & (/  undef,     0.0,     0.0,   -30.0,   -14.0,   -30.0,   -45.0,  &  !! critical tmin, tabulated (C)
1337  &     -45.0,   -60.0,   undef,   undef,   undef,   undef  /)
1338
1339  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tcm_crit_mtc  =  &
1340  & (/  undef,   undef,   undef,     5.0,    15.5,    15.5,   -8.0,  &   !! critical tcm, tabulated (C)
1341  &      -8.0,    -8.0,   undef,   undef,   undef,   undef  /)
1342
1343REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mortality_min_mtc = &       !! Asymptotic mortality if plant growth exceeds long term
1344  & (/  undef,  0.01,  0.01,  0.01,  0.01,  0.01,  0.01,  &               !! NPP (thus a strongly growing PFT)
1345  &      0.01,  0.01,  0.01,  0.01,  0.01,  0.01  /)                      !! @tex $(year^{-1})$ @endtex
1346 
1347  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mortality_max_mtc = &       !! Maximum mortality if plants hardly grows thus
1348  & (/  undef,  0.1,  0.1,  0.1,  0.1,  0.1,  0.1,  &                      !! NPP << NPPlongterm @tex $(year^{-1})$ @endtex
1349  &       0.1,  0.1,  0.1,  0.1,  0.1,  0.1  /)
1350
1351  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ref_mortality_mtc = &       !! Reference mortality rate used to calculate mortality
1352  & (/  undef,  0.035,  0.035,  0.035,  0.035,  0.035,  0.035,  &        !! as a function of the plant vigor
1353  &     0.035,  0.035,  0.035,  0.035,  0.035,  0.035  /)                !! @tex $(year^{-1})$ @endtex
1354
1355  !
1356  ! Biogenic Volatile Organic Compounds
1357  !
1358  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_isoprene_mtc = &     !! Isoprene emission factor
1359  & (/  0.,    24.,   24.,    8.,   16.,   45.,   8.,  &                    !!
1360  &    18.,    0.5,   12.,   18.,    5.,    5.  /)
1361
1362  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_monoterpene_mtc = &  !! Monoterpene emission factor
1363  & (/   0.,   2.0,    2.0,   1.8,    1.4,    1.6,    1.8,  &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1364  &    1.4,    1.8,    0.8,   0.8,    0.22,     0.22  /)
1365
1366  REAL(r_std), PARAMETER :: LDF_mono_mtc = 0.6                                  !! monoterpenes fraction dependancy to light
1367  REAL(r_std), PARAMETER :: LDF_sesq_mtc = 0.5                                  !! sesquiterpenes fraction dependancy to light
1368  REAL(r_std), PARAMETER :: LDF_meth_mtc = 0.8                                  !! methanol fraction dependancy to light
1369  REAL(r_std), PARAMETER :: LDF_acet_mtc = 0.2                                  !! acetone fraction dependancy to light
1370
1371  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_apinene_mtc = &      !! Alfa pinene emission factor percentage
1372  & (/   0.,   0.395,   0.395,   0.354,   0.463,   0.326,   0.354, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1373  &   0.316,   0.662,   0.231,   0.200,   0.277,   0.277 /)
1374
1375  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_bpinene_mtc = &      !! Beta pinene emission factor  percentage     
1376  & (/   0.,   0.110,   0.110,   0.146,   0.122,   0.087,   0.146, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1377  &   0.063,   0.150,   0.123,   0.080,   0.154,   0.154  /)
1378
1379  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_limonene_mtc = &     !! Limonene emission factor percentage
1380  & (/   0.,   0.092,   0.092,   0.083,   0.122,   0.061,   0.083, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1381  &   0.071,   0.037,   0.146,   0.280,   0.092,   0.092  /)
1382
1383  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_myrcene_mtc = &      !! Myrcene emission factor percentage
1384  & (/   0.,   0.073,   0.073,   0.050,   0.054,   0.028,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1385  &   0.019,   0.025,   0.062,   0.057,   0.046,   0.046  /)
1386
1387  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sabinene_mtc = &     !! Sabinene emission factor percentage
1388  & (/   0.,   0.073,   0.073,   0.050,   0.083,   0.304,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1389  &   0.263,   0.030,   0.065,   0.050,   0.062,   0.062  /)
1390
1391  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_camphene_mtc = &     !! Camphene emission factor percentage
1392  & (/   0.,   0.055,   0.055,   0.042,   0.049,   0.004,   0.042, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1393  &   0.005,   0.023,   0.054,   0.053,   0.031,   0.031  /)
1394
1395  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_3carene_mtc = &      !! 3-carene emission factor percentage
1396  & (/   0.,   0.048,   0.048,   0.175,   0.010,   0.024,   0.175, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1397  &   0.013,   0.042,   0.065,   0.057,   0.200,   0.200  /)
1398
1399  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_tbocimene_mtc = &    !! T-beta-ocimene emission factor percentage
1400  & (/   0.,   0.092,   0.092,   0.054,   0.044,   0.113,   0.054, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1401  &   0.105,   0.028,   0.138,   0.120,   0.031,   0.031  /)
1402
1403  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_othermonot_mtc = &   !! Other monoterpenes emission factor percentage
1404  & (/   0.,   0.062,   0.062,   0.046,   0.054,   0.052,   0.046, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
1405  &   0.144,   0.003,   0.115,   0.103,   0.108,   0.108  /)
1406
1407  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sesquiterp_mtc = &   !! Sesquiterpene emission factor
1408  & (/   0.,  0.45,   0.45,   0.13,   0.30,   0.36,   0.15, &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1409  &    0.30,  0.25,   0.60,   0.60,   0.08,   0.08  /)
1410
1411  REAL(r_std), PARAMETER :: beta_mono_mtc = 0.10                            !! Monoterpenes temperature dependency coefficient
1412  REAL(r_std), PARAMETER :: beta_sesq_mtc = 0.17                            !! Sesquiterpenes temperature dependency coefficient
1413  REAL(r_std), PARAMETER :: beta_meth_mtc = 0.08                            !! Methanol temperature dependency coefficient
1414  REAL(r_std), PARAMETER :: beta_acet_mtc = 0.10                            !! Acetone temperature dependency coefficient
1415  REAL(r_std), PARAMETER :: beta_oxyVOC_mtc = 0.13                          !! Other oxygenated BVOC temperature dependency coefficient
1416
1417
1418  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_ORVOC_mtc = &        !! ORVOC emissions factor
1419  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1420  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /) 
1421
1422  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_OVOC_mtc = &         !! OVOC emissions factor
1423  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1424  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /)
1425 
1426  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_MBO_mtc = &          !! MBO emissions factor
1427  & (/     0., 2.e-5, 2.e-5,   1.4, 2.e-5, 2.e-5, 0.14,  &                  !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1428  &     2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5  /) 
1429 
1430  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_methanol_mtc = &     !! Methanol emissions factor
1431  & (/  0.,    0.8,   0.8,   1.8,   0.9,   1.9,   1.8,  &                   !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1432  &    1.8,    1.8,   0.7,   0.9,    2.,     2.  /) 
1433 
1434  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetone_mtc = &      !! Acetone emissions factor
1435  & (/  0.,   0.25,   0.25,   0.30,   0.20,   0.33,   0.30,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1436  &   0.25,   0.25,   0.20,   0.20,   0.08,   0.08  /)
1437 
1438  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetal_mtc = &       !! Acetaldehyde emissions factor
1439  & (/  0.,   0.2,    0.2,     0.2,   0.2,   0.25,   0.25,   0.16,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1440  &   0.16,   0.12,   0.12,   0.035,   0.020  /) 
1441 
1442  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formal_mtc = &       !! Formaldehyde emissions factor
1443  & (/  0.,   0.04,   0.04,  0.08,    0.04,    0.04,  0.04,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1444  &   0.04,   0.04,  0.025, 0.025,   0.013,   0.013  /) 
1445
1446  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetic_mtc = &       !! Acetic Acid emissions factor
1447  & (/   0.,   0.025,   0.025,   0.025,   0.022,   0.08,   0.025,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1448  &   0.022,   0.013,   0.012,   0.012,   0.008,   0.008  /) 
1449
1450  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formic_mtc = &       !! Formic Acid emissions factor
1451  & (/  0.,  0.015,  0.015,   0.02,    0.02,   0.025,  0.025,  &            !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
1452  &  0.015,  0.015,  0.010,  0.010,   0.008,   0.008  /) 
1453
1454  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_wet_mtc = &        !! NOx emissions factor soil emissions and exponential
1455  & (/  0.,   2.6,   0.06,   0.03,   0.03,   0.03,   0.03,  &               !! dependancy factor for wet soils
1456  &  0.03,   0.03,   0.36,   0.36,   0.36,   0.36  /)                       !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
1457
1458  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_dry_mtc = &        !! NOx emissions factor soil emissions and exponential
1459  & (/  0.,   8.60,   0.40,   0.22,   0.22,   0.22,   0.22,  &              !! dependancy factor for dry soils
1460  &   0.22,   0.22,   2.65,   2.65,   2.65,   2.65  /)                      !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
1461
1462  !
1463  ! MORTALITY (stomate)
1464  !
1465
1466  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: death_distribution_factor_mtc = &    !!  The scale factor between the smallest and largest
1467       (/ undef,  1.,  1.,    1.,    1.,    1.,    1.,  &                         !! circ class for tree mortality in stomate_mark_kill.
1468          1.,     1.,  undef, undef, undef, undef /)                              !! (unitless)
1469
1470  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: npp_reset_value_mtc = &  !! The value of the NPP that the long-term value is
1471       (/ undef,  undef,  undef,  undef,  undef,  undef,  undef,  &   !! reset to after a PFT dies in stomate_kill.  This
1472          undef,  undef,   500.,   500.,   500.,   500. /)            !! only seems to be used for non-trees.
1473                                                                      !! @tex $(gC m^{-2})$ @endtex
1474
1475  !
1476  ! ALLOCATION and related
1477  !
1478
1479  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Larch_mtc = &                  !! Larcher 1991 SAI/LAI ratio (unitless)
1480  & (/   0.,   0.015,   0.015,   0.003,   0.005,   0.005,   0.003,  &
1481  &   0.005,   0.003,   0.005,   0.005,   0.008,   0.008  /) 
1482
1483  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_latosa_max_mtc = &  !! Maximum leaf-to-sapwood area ratio as defined in McDowell et al
1484  & (/ undef,  15000., 12000., 11000.,  6000.,  30000., 18000., &  !! 2002, Oecologia and compiled in Hickler et al 2006, Appendix S2
1485  &    30000., 30000., 7000.,   5500.,  9500.,  11000. /)          !! The values for grasses and crops are tuned. More work is needed
1486                                                                   !! to fully justify this approach for the herbacuous PFTs (unitless)
1487
1488  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_latosa_min_mtc = &  !! Minimum leaf-to-sapwood area ratio as defined in McDowell et al
1489  & (/ undef,   7500.,  6000.,  5600.,  2989.,  15310.,  9120., &  !! 2002, Oecologia and compiled in Hickler et al 2006, Appendix S2
1490  &    15310., 15310.,  7000.,  5500.,  9500.,  11000. /)          !! The values for grasses and crops are tuned. More work is needed
1491                                                                   !! to fully justify this approach for the herbacuous PFTs (unitless)
1492
1493  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_to_height_mtc = &                    !! Convertion from lai to height for grasses
1494  &(/ undef, undef, undef, undef, undef, undef, undef, &                              !! and cropland. Convert lai because that way a dynamic
1495  &   undef, undef,   0.1,   0.1,   0.1,   0.1 /)                                     !! sla is accounted for 
1496
1497  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_a_mtc = &                          !! intercept of the intra-tree competition within a stand
1498  & (/ undef,  0.23,  0.23,  0.23,  0.23,  0.23,  0.23, &                               !! based on the competion rule of Deleuze and Dhote 2004
1499  &     0.23,  0.23, undef, undef, undef, undef /)                                      !! Used when n_circ > 6
1500
1501  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_b_mtc = &                          !! slope of the intra-tree competition within a stand
1502  & (/ undef,  0.58,  0.58,  0.58,  0.58,  0.58,  0.58, &                               !! based on the competion rule of Deleuze and Dhote 2004
1503  &     0.58,  0.58, undef, undef, undef, undef /)                                      !! Used when n_circ > 6
1504
1505  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_p_all_mtc = &                      !! Percentile of the circumferences that receives photosynthates
1506  & (/ undef,  0.50,  0.50,  0.70,  0.70,  0.70,  0.70, &                               !! based on the competion rule of Deleuze and Dhote 2004
1507  &     0.70,  0.70, undef, undef, undef, undef /)                                      !! Used when n_circ > 6 for FM1, FM2 and FM4
1508
1509  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_p_coppice_mtc = &                  !! Percentile of the circumferences that receives photosynthates
1510  & (/ undef,  0.50,  0.50,  0.50,  0.50,  0.50,  0.50, &                               !! based on the competion rule of Deleuze and Dhote 2004
1511  &     0.50,  0.50, undef, undef, undef, undef /)                                      !! Used when n_circ > 6 for FM3
1512
1513  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_power_a_mtc = &                    !! slope to calculate divisor of the power for the slope
1514  & (/ undef,  0.0,  0.0,  0.0,  0.0,  0.0,  0.0, &                                     !! of intra-tree competition whithin a stand
1515  &     0.0,  0.0, undef, undef, undef, undef /)                                        !! based on the competition rule of Deleuze and Dhote 2004
1516
1517  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: m_dv_mtc = &                               !! Parameter in the Deleuze & Dhote allocation
1518  & (/ undef,  1.05,  1.05,  1.05,  1.05,  1.05,  1.05, &                               !! rule that relaxes the cut-off imposed by
1519  &     1.05,  1.05,    0.,    0.,    0.,    0. /)                                      !! ::sigma. Owing to m_relax trees still grow
1520                                                                                        !! a little when their ::circ is below ::sigma
1521 
1522  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fruit_alloc_mtc = &   !! Fraction of biomass allocated to fruit production (0-1)
1523  & (/ undef,   0.1,    0.1,    0.1,     0.1,     0.1,    0.1, &   !! currently only parameterized for forest PFTs
1524  &      0.1,   0.1,    0.1,    0.1,     0.2,     0.2 /) 
1525
1526  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_res_lim_mtc = &          !! Fraction of growth respiration expressed as
1527  &(/  0.28,   0.28,   0.28,   0.28,   0.28,   0.28,   0.28, &                        !! share of the total C that is to be allocated
1528  &    0.28,   0.28,   0.28,   0.28,   0.28,   0.28 /) 
1529
1530  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_fun_all_mtc = &          !! Fraction of growth respiration expressed as
1531  &(/  0.28,   0.28,   0.28,   0.28,   0.28,   0.28,   0.28, &                        !! share of the total C that is to be allocated
1532  &    0.28,   0.28,   0.28,   0.28,   0.28,   0.28 /)
1533
1534  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: labile_reserve_mtc = &                   !! The lab_fac is divided by this value to obtain
1535  &(/  0.,   2.0,  2.0,  2.0, 2.0,  2.0,  2.0, &                                      !! a new parameter. This new parameter is a fraction
1536  &    2.0,  2.0,  1.0,   1.0,  4.0,   4.0  /)                                              !! that is multiplied with the plant biomass to obatin
1537                                                                                      !! the optimal size of the labile pool. The dependency
1538                                                                                      !! on lab_fac is a nice feature but the whole
1539                                                                                      !! parameterization is arbitrary
1540
1541  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: evergreen_reserve_mtc = &                !! Fraction of sapwood mass stored in the reserve pool of evergreen
1542  &(/ undef, 0.05, 0.05, 0.05, 0.05, 0.05, 0.05, &                                    !! trees (unitless, 0-1)
1543  &    0.05,  0.05, 0.05, 0.05, 0.05, 0.05 /)
1544
1545  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescense_reserve_mtc = &               !! Fraction of sapwood mass stored in the reserve pool of deciduous
1546  &(/ undef, 0.15, 0.15, 0.15, 0.25, 0.25, 0.15, &                                    !! trees during senescense(unitless, 0-1)
1547  &    0.25,  0.15, 0.15, 0.15, 0.15, 0.15 /)
1548
1549  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deciduous_reserve_mtc = &                !! Fraction of sapwood mass stored in the reserve pool of deciduous
1550  &(/ undef, 0.12, 0.12, 0.12, 0.12, 0.12, 0.12, &                                    !! trees during the growing season (unitless, 0-1)
1551  &    0.24,  0.24, 0.3, 0.3, 0.3, 0.3 /)
1552
1553  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: root_reserve_mtc = &                     !! Fraction of max root biomass which are
1554                                                                               
1555  &(/ undef, 0.3, 1., 0.3, 0.3, 1., 0.3, &                                            !! covered by carbon reserve
1556  &    1.,  1., 1., 1., 1., 1. /)                                                     !! for deciduous species we keep the whole root mass.
1557                                                                                      !! For evergreens we are happy with 30%
1558 
1559  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fcn_root_mtc = &      !! N/C of "root" for allocation relative to leaf N/C  according
1560  & (/ undef,   .86,    .86,    .86,    .86,    .86,   .86,   &    !! to Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
1561  &      .86,   .86,    .86,    .86,    .86,    .86   /)
1562
1563  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fcn_wood_mtc = &      !! N/C of "wood" for allocation relative to leaf N/C  according
1564  & (/ undef,    .087,   .087,   .087,   .087,   .087,  .087,  &   !! to Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
1565  &     .087,    .087,   .087,   .087,   .087,   .087   /)
1566
1567  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: p_use_reserve_mtc = &     
1568  & (/ undef,    .9,   .9,   .9,   .9,   .9,  .9,  & 
1569  &     .9,    .9,   .9,   .9,   .9,   .9   /)
1570
1571
1572
1573  !
1574  ! CROP MANAGEMENT
1575  !
1576  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: harvest_ratio_mtc = &                      !! Share of biomass that is removed from the site during harvest
1577  & (/ undef,  undef,  undef,  undef,  undef,  undef,  undef, &                         !! A high value indicates a high harvest efficiency and thus a
1578  &    undef,  undef,  0.5,  0.5,    0.5,    0.5 /)                                     !! input of residuals. (unitless, 0-1).
1579
1580  !
1581  ! FOREST MANAGEMENT
1582  !
1583  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: dens_target_mtc =  &                       !! Minimal density. Below this density the forest
1584  & (/   0.0,   100.0,   100.0,   100.0,   50.0,   200.0,   300.0,  &                  !! will be clearcut (trees.ha-1)
1585  &    100.0,   100.0,     0.0,     0.0,     0.0,     0.0   /) 
1586
1587  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: thinstrat_mtc =  &                         !! Thinning strategy. The FM code distinguished
1588  & (/   0.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                              !! thinning from above (<0) or from below (>0). 
1589  &    1.0,   1.0,     0.0,     0.0,     0.0,     0.0   /)                             
1590
1591  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: taumin_mtc =  &                            !! Minimum probability that a tree get thinned (unitless)
1592  & (/   0.0,   0.01,   0.01,   0.01,   0.01,   0.01,   0.01,  &
1593  &    0.01,   0.01,     0.0,     0.0,     0.0,     0.0   /) 
1594
1595  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: taumax_mtc =  &                            !! Maximum probability that a tree get thinned (unitless)
1596  & (/   0.0,   0.05,   0.05,   0.05,   0.05,   0.05,   0.05,  &
1597  &    0.05,   0.05,     0.0,     0.0,     0.0,     0.0   /)
1598 
1599  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a_rdi_upper_unman_mtc = &                  !! Intercept of self-thinning relationship justified by
1600  &(/ undef,   0.16,   0.16,   0.16,   0.16,   0.16,   0.16, &                          !! the rdi observed in Luyssaert et al 2011
1601  &    0.16,   0.16,  undef,  undef,  undef,  undef/)                                 
1602 
1603  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b_rdi_upper_unman_mtc = &                  !! Slope of self-thinning relationship justified by
1604  &(/ undef,    0.009082, 0.006269,  0.01933,  0.01748,  0.010638,  0.02492, &          !! the rdi observed in Luyssaert et al 2011
1605  &   0.01156,  0.01156,  undef,     undef,    undef,    undef/)
1606
1607  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: c_rdi_upper_unman_mtc = &                  !! Upper boundary for upper rdi for unmanaged forests
1608  &(/ undef,   0.95,   0.95,   0.95,   0.95,   0.95,   0.95, &
1609  &    0.95,   0.95,  undef,  undef,  undef,  undef/)
1610
1611  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: d_rdi_upper_unman_mtc = &                  !! Lower boundary for upper rdi for unmanaged forests
1612  &(/ undef,    0.4,    0.4,    0.4,    0.4,    0.4,    0.4, &
1613  &     0.4,    0.4,  undef,  undef,  undef,  undef/)
1614
1615  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a_rdi_lower_unman_mtc = &                  !! Intercept of self-thinning relationship justified by
1616  &(/ undef,  0.051,  0.051,  0.051,  0.051,  0.051,  0.051, &                          !! the rdi observed in Luyssaert et al 2011
1617  &   0.051,  0.051,  undef,  undef,  undef,  undef/)                                 
1618 
1619  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b_rdi_lower_unman_mtc = &                  !! Slope of self-thinning relationship justified by
1620  &(/ undef,  0.008182,  0.005369,  0.01843,  .01658,  0.009738,  0.02402, &            !! the rdi observed in Luyssaert et al 2011
1621  &  0.01066, 0.01066,   undef,     undef,    undef,   undef/)
1622
1623  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: c_rdi_lower_unman_mtc = &                  !! Upper boundary for lower rdi for unmanaged forests
1624  &(/ undef,   0.85,   0.85,   0.85,   0.85,   0.85,   0.85, &
1625  &    0.85,   0.85,  undef,  undef,  undef,  undef/)
1626
1627  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: d_rdi_lower_unman_mtc = &                  !! Lower boundary for lower rdi for unmanaged forests
1628  &(/ undef,   0.38,   0.38,  0.38,   0.38,    0.38,   0.38, &
1629  &    0.38,   0.38,  undef,  undef,  undef,  undef/)
1630
1631  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a_rdi_upper_man_mtc = &                    !! Intercept of the yield-table derived thinning relationship
1632  &(/ undef,   0.16,   0.16,   0.16,   0.16,   0.16,   0.16, &                          !! D=alpha*N^beta estimated from JRC yield table database
1633  &    0.16,   0.16,  undef,  undef,  undef,  undef/)                                 
1634 
1635  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b_rdi_upper_man_mtc = &                    !! Slope of the yield-table derived thinning relationship
1636  &(/ undef, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, &                          !! D=alpha*N^beta estimated from JRC yield table database
1637  &  0.0264, 0.0264,  undef,  undef,  undef,  undef/)
1638
1639  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: c_rdi_upper_man_mtc = &                    !! Upper boundary for upper rdi for managed forests
1640  &(/ undef,    0.9,    0.9,    0.9,    0.9,    0.9,    0.9, &
1641  &     0.9,    0.9,  undef,  undef,  undef,  undef/)
1642
1643  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: d_rdi_upper_man_mtc = &                    !! Lower boundary for upper rdi for managed forests
1644  &(/ undef,    0.4,    0.4,    0.4,    0.4,    0.4,    0.4, &
1645  &     0.4,    0.4,  undef,  undef,  undef,  undef/)
1646
1647  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a_rdi_lower_man_mtc = &                    !! Intercept of the yield-table derived thinning relationship
1648  &(/ undef,  0.051,  0.051,  0.051,  0.051,  0.051,  0.051, &                          !! D=alpha*N^beta estimated from JRC yield table database
1649  &   0.051,  0.051,  undef,  undef,  undef,  undef/)                                 
1650
1651  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b_rdi_lower_man_mtc = &                    !! Slope of the yield-table derived thinning relationship
1652  &(/ undef, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, &                          !! D=alpha*N^beta estimated from JRC yield table database
1653  &  0.0255, 0.0255,  undef,  undef,  undef,  undef/)
1654
1655  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: c_rdi_lower_man_mtc = &                    !! Upper boundary for lower rdi for managed forests
1656  &(/ undef,    0.7,    0.7,    0.7,    0.7,    0.7,    0.7, &
1657  &     0.7,    0.7,  undef,  undef,  undef,  undef/)
1658
1659  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: d_rdi_lower_man_mtc = &                    !! Lower boundary for lower rdi for managed forests
1660  &(/ undef,    0.3,    0.3,    0.3,    0.3,    0.3,    0.3, &
1661  &     0.3,    0.3,  undef,  undef,  undef,  undef/)
1662 
1663  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: largest_tree_dia_mtc =  &                  !! Maximal tree diameter (m). If this diameter is exceeded a
1664  & (/   undef,  .5,   .5,     .41,    .35,    .45,   .45,  &                           !! a clearcut will happen.
1665  &      .3,     .3,   undef,  undef,  undef,  undef/) 
1666
1667   REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fuelwood_diameter_mtc = &                 !! Diameter below which the wood harvest is used as fuelwood (m)
1668  &(/ undef,   0.3,   0.3,   0.2,   0.2,   0.2,   0.2, &                                !! Affects the way the wood is used in the dim_product_use   
1669  &     0.1,   0.1, undef, undef, undef, undef/)                                        !! subroutine
1670
1671  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coppice_kill_be_wood_mtc = &               !! The fraction of the belowground wood killed during coppicing.
1672  &(/ undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0, &                                !! (unitless)
1673  &     0.0,   0.0, undef, undef, undef, undef/) 
1674
1675  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: branch_ratio_mtc =  &                      !! Ratio of branches to total woody biomass (unitless)
1676  & (/  0.0,   0.38,   0.38,   0.25,   0.38,   0.38,   0.25,  &
1677  &    0.38,   0.25,    0.0,    0.0,    0.0,    0.0 /)
1678
1679  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: branch_harvest_mtc =  &                    !! Ratio of branches harvested in FM2 management.
1680  & (/  0.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &
1681  &    1.0,   1.0,    0.0,    0.0,    0.0,    0.0 /)
1682 
1683  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coppice_diameter_mtc = &                   !! The trunk diameter above which one coppices
1684  & (/ undef,  0.20,  0.20,  0.20,  0.20,  0.20,  0.20, &                               !! trees. (m)
1685  &     0.20,  0.20,    0.,    0.,    0.,    0. /)                                     
1686
1687  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: shoots_per_stool_mtc = &                !! The number of shoots which regrow on a stool after
1688  (/ 9999,  6,     6,     6,      6,     6,     6, &                                    !! coppicing.
1689  6,  6, 9999, 9999,  9999, 9999 /)   
1690
1691  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: src_rot_length_mtc = &                  !! The number of years between SRC cuttings.
1692  (/ 9999,   3,     3,     3,     3,     3,     3, &                                    !! (-)
1693  3,   3, 9999, 9999, 9999, 9999 /)                           
1694
1695  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: src_nrots_mtc = &                       !! The number of SRC rotations before the whole stand
1696  (/ 9999,   10,    10,    10,    10,    10,    10, &                                   !! is harvested (-)
1697  10,  10, 9999, 9999, 9999, 9999 /)
1698
1699  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cn_leaf_init_mtc = &                       !! C/N of leaves according to Sitch et al 2003
1700  (/ undef,  25.,  25.,  41.7,  25.,  25.,  43.,  &                                     !! (https://doi.org/10.1046/j.1365-2486.2003.00569.x)
1701       25.,  25.,  25.,  25.,  25.,  25.   /)
1702
1703  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ndying_year_mtc = &                       !! Number of years during which the forest will die after reaching the tree stem density threshold   
1704  (/ undef, 15.0, 15.0, 25.0, 15.0, 15.0, 15.0,  &                                     !!
1705       15.0, 15.0, 15.0, 15.0, 15.0, 15.0  /)
1706
1707  !
1708  ! ALLOCATION
1709  !
1710  !+++CHECK+++
1711  ! Ideally k_root (see below) and a value for k_soil_to_root are used to calculate
1712  ! k_belowground which is used in the allocation. Problem is that we need the root biomass
1713  ! to calculate k_soil_to_root and that we need k_soil_to_root to calculate the root
1714  ! biomass. Now allocation starts from Cs, it could be written to start from Cr but that
1715  ! is not an easy task. The benefits would be full consistency between allocation
1716  ! and plant water stress and a dynamic root allocation (as has been observed). The
1717  ! latter has been tried in 2014 but it turned out to be much more difficult than
1718  ! expected. This development needs to be thought throught more carefully. In addition
1719  ! ::k in hydrology is the effective soil conductivity. To use that value we would
1720  ! have reconsider the hydraulic architecture. The solution for the moment is to
1721  ! decouple allocation and hydraulic architecture by defining two related parameters
1722  ! independently.
1723  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_belowground_mtc = &                       !! Belowground (roots + soil) specific conductivity.     
1724  & (/-9999.,     8.944E-08,  6.6E-08,  1.291E-08,  4.04E-08,  3.287E-07,  5.254E-09, &  !! @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex   
1725  &   3.287E-07,  3.287E-08,  4.E-07,   4.E-07,     4.E-07,    4.E-07 /) 
1726  !+++++++++++
1727
1728  !
1729  ! HYDRAULIC ARCHITECTURE
1730  !
1731  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_root_mtc = &                    !! Fine root and soil to root conductivity. Values based on Bonan et al 2014     
1732  & (/ undef,  7.02E-4,  7.02E-4,  7.02E-4,  7.02E-4,  7.02E-4,  7.02E-4, &    !! et al. 2006. @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex   
1733  &       7.02E-4,  7.02E-4,   7.02E-4,  7.02E-4,  7.02E-4,  7.02E-4   /)         
1734                                                             
1735  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_sap_mtc = &                     !! Maximal sapwood specific conductivity. Values compiled in T. Hickler
1736  & (/-9999.,  0.009,  0.002,  0.0011,  0.0002,  0.0012,  0.0013, &            !! et al. 2006. @tex $(m^{2} s^{-1} MPa^{-1})$ @endtex
1737  &   0.0012,  0.0012, 0.0006, 0.0006,  0.0006,  0.0006   /)                   !! Values from DOFOCO run.def
1738
1739  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_leaf_mtc = &        !! Leaf conductivity. Values compiled in T. Hickler et al 2006
1740  & (/ undef,  2.5,  2.5,  1.5,  1.5,  2.5,  1.5,         &        !! @tex $(m s^{-1} MPa^{-1})$ @endtex
1741         2.5,  2.5,  3.0,  3.0,  3.0,  3.0         /)*1.E-7
1742
1743  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: psi_leaf_mtc = &      !! Minimal leaf water potential. Values in T. Hickler et al 2006
1744  & (/ undef, -2.2, -2.2, -1.95, -4.48, -2.2, -1.78,   &           !! @tex $(MPa)$ @endtex
1745        -2.2, -3.0, -3.0, -2.2,  -3.0,  -2.2        /)
1746
1747  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: psi_50_mtc = &        !! Sapwood leaf water potential that causes 50% loss of xylem
1748  & (/ undef, -3.0, -3.0, -3.52, -3.83, -2.4, -2.8, &                !! conductivity through cavitation. @tex $(MPa)$ @endtex
1749        -3.15, -3.66, undef, undef, undef, undef /)
1750
1751  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: c_cavitation_mtc = &  !! Shape parameter for loss of conductance Machado & Tyree, 1994
1752  & (/ undef,  5.,  3.,  2.,  3.,  2.,  3.,  &                     !! (unitless)
1753          3.,  3., undef, undef, undef, undef /)
1754
1755  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: psi_soil_tune_mtc = & !! Additive tuning parameter to account for soil-root interactions
1756  & (/ undef,  0.,  0.,  0.,  0.,  0.,  0.,  &                     !! @tex $(MPa)$ @endtex
1757          0.,  0.,  0.,  0.,  0.,  0. /)                                 
1758
1759  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: srl_mtc = &           !! Specific root length (m g⁻1). Values are obtained from Metcalfe
1760   & (/ undef,  18.3,   18.3,   18.3,  18.3,  18.3,  18.3,  &      !! et al. 2008 and Ostonen et al. 2007 
1761         18.3,  18.3,   18.3,   18.3,  18.3,  18.3 /) 
1762
1763  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: r_froot_mtc = &       !! Fine root radius (m). Values are obtained from Bonan 
1764   & (/ undef,  0.29E-3,   0.29E-3,  0.29E-3,  0.29E-3, &          !! et al.2014 and Ostonen et al. 2007 (Tree physiology)   
1765   &  0.21E-3,  0.24E-3,   0.21E-3,  0.21E-3,  0.075E-3, &
1766   &  0.075E-3, 0.168E-3,  0.168E-3 /)
1767
1768  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: psi_root_mtc = &      !! The minimum root water potential. Tested by Emilie joetzjer
1769   & (/ undef,  -5.,   -5.,   -5.,  -5.,   -5.,  -5.,  &           !! that -4 works for tropical PFT.
1770   &      -5.,  -5.,   -5.,   -5.,  -5.,   -5. /)                  !!
1771
1772
1773
1774END MODULE constantes_mtc
Note: See TracBrowser for help on using the repository browser.