source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/constantes_mtc.f90 @ 7804

Last change on this file since 7804 was 7804, checked in by xiaoni.wang, 20 months ago

Redefine snow albedo parameter for tropical forest by using temperate forest. For ticket 755 in tag2.2.

  • Property svn:keywords set to Date Revision
File size: 52.8 KB
RevLine 
[720]1! =================================================================================================================================
2! MODULE       : constantes_mtc
3!
[4470]4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
[720]5!
[733]6! LICENCE      : IPSL (2011)
[720]7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
[1383]9!>\BRIEF         This module contains the standard values of the parameters for the 13 metaclasses of vegetation used by ORCHIDEE.
[628]10!!
[720]11!!\n DESCRIPTION: None
[628]12!!
[3041]13!! RECENT CHANGE(S):
[628]14!!
[1383]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
[1882]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.
[1383]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.
[1882]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.
[4640]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.
[720]35!!
36!! SVN          :
37!! $HeadURL: $
38!! $Date$
39!! $Revision$
40!! \n
41!_ ================================================================================================================================
42
[511]43MODULE constantes_mtc
44
[534]45  USE defprec
46  USE constantes
[511]47
[534]48  IMPLICIT NONE
[511]49
50  !
[531]51  ! METACLASSES CHARACTERISTICS
52  !
[720]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)
[531]57  & (/ 'bare ground                       ', &          !  1
[511]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
[531]72  !
73  ! VEGETATION STRUCTURE
74  !
[1091]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
[720]78
[1091]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'  /) 
[720]83
[890]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
[720]88  CHARACTER(LEN=5), PARAMETER, DIMENSION(nvmc) :: type_of_lai_mtc  =  &  !! Type of behaviour of the LAI evolution algorithm
89  & (/ 'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! for each vegetation type. (unitless)
90  &    'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! Value of type_of_lai : mean or interp
[531]91  &    'inter', 'inter', 'inter' /)
[720]92
[1091]93  LOGICAL, PARAMETER, DIMENSION(nvmc) :: natural_mtc =  &                         !! natural?  (true/false)
94  & (/ .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,    .TRUE.,   .TRUE.,  &
95  &    .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .FALSE.,   .FALSE.  /)
96
[720]97  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: veget_ori_fixed_mtc  =  &  !! Value for veget_ori for tests in
98  & (/ 0.2,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                !! 0-dim simulations (0-1, unitless)
[531]99  &    0.0,   0.0,   0.8,   0.0,   0.0,   0.0  /)
[720]100
101  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimax_mtc  =  &          !! laimax for maximum
[1082]102  & (/ 0.0,   8.0,   8.0,   4.0,   4.5,   4.5,   4.0,  &                !! See also type of lai interpolation
103  &    4.5,   4.0,   2.0,   2.0,   2.0,   2.0  /)                       !! @tex $(m^2.m^{-2})$ @endtex
[720]104
105  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimin_mtc  = &           !! laimin for minimum lai
[733]106  & (/ 0.0,   8.0,   0.0,   4.0,   4.5,   0.0,   4.0,  &                !! See also type of lai interpolation (m^2.m^{-2})
[1082]107  &    0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                       !! @tex $(m^2.m^{-2})$ @endtex
[720]108
109  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_presc_mtc  =  &     !! prescribed height of vegetation (m)
110  & (/  0.0,   30.0,   30.0,   20.0,   20.0,   20.0,   15.0,  &         !! Value for height_presc : one for each vegetation type
[531]111  &    15.0,   15.0,    0.5,    0.6,    1.0,    1.0  /)
[720]112
[3524]113  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: z0_over_height_mtc = &         !! Factor to calculate roughness height from
114  & (/  0.0, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625,  &         !! vegetation height (unitless)   
115  &  0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625  /)
116
117  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ratio_z0m_z0h_mtc = &      !! Ratio between z0m and z0h values (roughness height for momentum and for heat)
118  & (/  1.0,    1.0,    1.0,    1.0,    1.0,    1.0,    1.0,  &         
119  &     1.0,    1.0,    1.0,    1.0,    1.0,    1.0  /)
120
121
[1082]122  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rveg_mtc  =  &             !! Potentiometer to set vegetation resistance (unitless)
123  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                !! Nathalie on March 28th, 2006 - from Fred Hourdin,
[531]124  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0   /)
[720]125
[1091]126  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: sla_mtc  =  &                       !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
[531]127  & (/ 1.5E-2,   1.53E-2,   2.6E-2,   9.26E-3,     2E-2,   2.6E-2,   9.26E-3,  &
128  &    2.6E-2,    1.9E-2,   2.6E-2,    2.6E-2,   2.6E-2,   2.6E-2  /) 
[511]129
[2668]130  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: availability_fact_mtc  =  &     !! calculate mortality in lpj_gap
131  & (/ undef,   0.14,  0.14,   0.10,   0.10,   0.10,   0.05,  &
132  &     0.05,   0.05,  undef,  undef,  undef,  undef  /)
[511]133
134  !
[531]135  ! EVAPOTRANSPIRATION (sechiba)
136  !
[1082]137  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rstruct_const_mtc  =  &  !! Structural resistance.
138  & (/ 0.0,   25.0,   25.0,   25.0,   25.0,   25.0,   25.0,  &        !! @tex $(s.m^{-1})$ @endtex
[531]139  &   25.0,   25.0,    2.5,    2.0,    2.0,    2.0   /)
[511]140
[720]141  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kzero_mtc  =  &                  !! A vegetation dependent constant used in the
[1082]142  & (/    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.
143  &    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
[511]144
[720]145
[511]146  !
[531]147  ! WATER (sechiba)
148  !
[1082]149  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wmax_veg_mtc  =  &        !! Volumetric available soil water capacity in each PFT
150  & (/ 150.0,   150.0,   150.0,   150.0,   150.0,   150.0,   150.0,  & !! @tex $(kg.m^{-3} of soil)$ @endtex
151  &    150.0,   150.0,   150.0,   150.0,   150.0,   150.0  /)         
152                                                                     
[720]153
[3041]154  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref4m  =  &       !! Root profile description for the different
[1082]155  & (/ 5.0,   0.4,   0.4,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types. @tex $(m^{-1})$ @endtex
[720]156  &    1.0,   0.8,   4.0,   1.0,   4.0,   1.0  /)                      !! These are the factor in the exponential which gets       
157                                                                       !! the root density as a function of depth
[2928]158                                                                       !! Values for zmaxh = 4.0 
[947]159 
[3041]160  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref2m  =  &       !! Root profile description for the different
[1082]161  & (/ 5.0,   0.8,   0.8,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types.  @tex $(m^{-1})$ @endtex
[947]162  &    1.0,   0.8,   4.0,   4.0,   4.0,   4.0  /)                      !! These are the factor in the exponential which gets       
163                                                                       !! the root density as a function of depth
[2928]164                                                                       !! Values for zmaxh = 2.0
[720]165
[4752]166  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: throughfall_by_mtc  =  &  !! Percent by PFT of precip that is not intercepted by the canopy
[720]167  & (/ 30.0,   30.0,   30.0,   30.0,   30.0,   30.0,   30.0,  &        !! (0-100, unitless)
[531]168  &    30.0,   30.0,   30.0,   30.0,   30.0,   30.0  /)
[511]169
[531]170
[511]171  !
[531]172  ! ALBEDO (sechiba)
173  !
[3599]174  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_vis_mtc  =  &  !! Minimum snow albedo value for each vegetation type
[7804]175  & (/ 0.74,    0.24,    0.07,   0.08,   0.24,   0.07,   0.18,  &        !! after aging (dirty old snow) (unitless), visible albedo
[4962]176  &    0.18,    0.33,   0.57,  0.57,   0.57,   0.57  /)                !! Source : Values optimized for ORCHIDEE2.0
[720]177
[3599]178  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_nir_mtc  =  &  !! Minimum snow albedo value for each vegetation type
[7804]179  & (/ 0.50,    0.37,    0.08,   0.10,   0.37,   0.08,   0.16,  &        !! after aging (dirty old snow) (unitless), near infrared albedo
[4962]180  &    0.17,    0.27,   0.44,   0.44,   0.44,   0.44  /)               !! Source : Values optimized for ORCHIDEE2.0
[720]181
[3599]182  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_vis_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
[7804]183  & (/ 0.21,   0.08,    0.17,   0.14,   0.08,   0.17,   0.05,  &         !! as it will be used in condveg_snow (unitless), visible albedo
[4962]184  &    0.06,   0.09,   0.15,  0.15,   0.15,   0.15  /)                 !! Source : Values optimized for ORCHIDEE2.0
[3599]185
186  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_nir_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
[7804]187  & (/ 0.13,    0.10,    0.16,   0.10,   0.10,   0.16,   0.04,  &        !! as it will be used in condveg_snow (unitless), near infrared albedo
[4962]188  &    0.07,    0.08,   0.12,  0.12,   0.12,   0.12  /)                !! Source : Values optimized for ORCHIDEE2.0
[3599]189
[3605]190  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_vis_mtc  =  &    !! leaf albedo of vegetation type, visible albedo, optimized on 04/07/2016
[4962]191  & (/ 0.00,   0.04, 0.04, 0.04, 0.04, 0.03, 0.03,  &                  !! (unitless)
192  &    0.03,   0.03, 0.06, 0.06, 0.06, 0.06  /)
[720]193
[3605]194  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_nir_mtc  =  &    !! leaf albedo of vegetation type, near infrared albedo, optimized on 04/07/2016
[4962]195  & (/ 0.00,   0.23,  0.18,  0.18,  0.20,  0.24,  0.15,  &             !! (unitless)
196  &    0.26,   0.20,  0.24,  0.27,  0.28,  0.26  /)
[511]197
198  !
[531]199  ! SOIL - VEGETATION
200  !
[947]201  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_mtc  =  &       !! The soil tile number for each vegetation
202  & (/ 1,   2,   2,   2,   2,   2,   2,  &                                   
203  &    2,   2,   3,   3,   3,   3  /)                                         
[511]204
205
[531]206  !
207  ! PHOTOSYNTHESIS
208  !
[511]209  !-
210  ! 1 .CO2
211  !-
[720]212  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c4_mtc  =  &                            !! flag for C4 vegetation types (true/false)
[531]213  & (/ .FALSE.,  .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  &
214  &    .FALSE.,  .FALSE.,   .FALSE.,   .TRUE.,    .FALSE.,   .TRUE.  /)
[720]215
216  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_fix_mtc  =  &     !! values used for vcmax when STOMATE is not
[1082]217  & (/  0.0,   40.0,   50.0,   30.0,   35.0,   40.0,   30.0,  &      !! activated @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
[531]218  &    40.0,   35.0,   60.0,   60.0,   70.0,   70.0  /)
[720]219
[4655]220! For C4 plant we define a very small downregulation effect as C4 plant are
221! currently saturate with respect to CO2 impact on vcmax
[6393]222  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: downregulation_co2_coeff_mtc  =  &  !! Coefficient for CO2 downregulation if downregulation_co2 (used for CMIP6 6.1.0-6.1.10) (unitless)
[2031]223  & (/  0.0,   0.38,   0.38,   0.28,   0.28,   0.28,   0.22,  &
[4655]224  &     0.22,  0.22,   0.26,   0.03,   0.26,   0.03 /)
[6393]225  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: downregulation_co2_coeff_new_mtc  =  &  !! Coefficient for CO2 downregulation if downregulation_co2_new (used for CMIP6 6.1.11) (unitless)
226  & (/  0.0,   0.35,   0.35,   0.26,   0.26,   0.26,   0.20,  &
227  &     0.20,  0.20,   0.24,   0.03,   0.24,   0.03 /)
[720]228
[2031]229  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmC_mtc  = &            !! Energy of activation for KmC (J mol-1)
230  & (/undef,  79430.,  79430.,  79430.,  79430.,  79430.,  79430.,  &  !! See Medlyn et al. (2002)
231  &  79430.,  79430.,  79430.,  79430.,  79430.,  79430.  /)           !! from Bernacchi al. (2001)
[720]232
[2031]233  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmO_mtc  = &            !! Energy of activation for KmO (J mol-1)
234  & (/undef,  36380.,  36380.,  36380.,  36380.,  36380.,  36380.,  &  !! See Medlyn et al. (2002)
235  &  36380.,  36380.,  36380.,  36380.,  36380.,  36380.  /)           !! from Bernacchi al. (2001)
[720]236
[3972]237REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Sco_mtc  = &            !! Energy of activation for Sco (J mol-1)
238  & (/undef, -24460., -24460., -24460., -24460., -24460., -24460.,  &  !! See Table 2 of Yin et al. (2009)
239  & -24460., -24460., -24460., -24460., -24460., -24460.  /)           !! Value for C4 plants is not mentioned - We use C3 for all plants
240
241
[2031]242  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gamma_star_mtc  = &     !! Energy of activation for gamma_star (J mol-1)
243  & (/undef,  37830.,  37830.,  37830.,  37830.,  37830.,  37830.,  &  !! See Medlyn et al. (2002) from Bernacchi al. (2001)
244  &  37830.,  37830.,  37830.,  37830.,  37830.,  37830.  /)           !! for C3 plants - We use the same values for C4 plants
[1882]245
[2031]246  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Vcmax_mtc  = &          !! Energy of activation for Vcmax (J mol-1)
247  & (/undef,  71513.,  71513.,  71513.,  71513.,  71513.,  71513.,  &  !! See Table 2 of Yin et al. (2009) for C4 plants
248  &  71513.,  71513.,  71513.,  67300.,  71513.,  67300.  /)           !! and Kattge & Knorr (2007) for C3 plants (table 3)
[720]249
[2031]250  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Jmax_mtc  = &            !! Energy of activation for Jmax (J mol-1)
251  & (/undef,  49884.,  49884.,  49884.,  49884.,  49884.,  49884.,  &   !! See Table 2 of Yin et al. (2009) for C4 plants
252  &  49884.,  49884.,  49884.,  77900.,  49884.,  77900.  /)            !! and Kattge & Knorr (2007) for C3 plants (table 3)
[720]253
[2031]254  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)
255  & (/undef,  668.39,  668.39,  668.39,  668.39,  668.39,  668.39,  &   !! See Table 3 of Kattge & Knorr (2007)
256  &  668.39,  668.39,  668.39,  641.64,  668.39,  641.64  /)            !! For C4 plants, we assume that there is no
257                                                                        !! 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)
[720]258
[2031]259  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)
260  & (/undef,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,  &   !! See Table 3 of Kattge & Knorr (2007)
261  &   -1.07,   -1.07,   -1.07,      0.,   -1.07,      0.  /)            !! We assume No acclimation term for C4 plants
[720]262
[2031]263  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_mtc  =  &  !! minimum photosynthesis temperature (deg C)
264  & (/  undef,   -4.0,    -4.0,   -4.0,   -4.0,   -4.0,   -4.0,  & 
265  &      -4.0,   -4.0,    -4.0,   -4.0,   -4.0,   -4.0  /)
[720]266
[2031]267  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_mtc  =  &  !! maximum photosynthesis temperature (deg C)
268  & (/  undef,   55.0,    55.0,   55.0,   55.0,   55.0,   55.0,  & 
269  &      55.0,   55.0,    55.0,   55.0,   55.0,   55.0  /)
[720]270
[2031]271  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)
272  & (/undef,  659.70,  659.70,  659.70,  659.70,  659.70,  659.70,  &   !! See Table 3 of Kattge & Knorr (2007)
273  &  659.70,  659.70,  659.70,    630.,  659.70,    630.  /)            !! and Table 2 of Yin et al. (2009) for C4 plants
[720]274
[2031]275  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)
276  & (/undef,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,  &   !! See Table 3 of Kattge & Knorr (2007)
277  &   -0.75,   -0.75,   -0.75,      0.,   -0.75,      0.  /)            !! We assume no acclimation term for C4 plants
[720]278
[2031]279  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Vcmax_mtc  = &           !! Energy of deactivation for Vcmax (J mol-1)
280  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! Medlyn et al. (2002) also uses 200000. for C3 plants (same value than D_Jmax)
281  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! 'Consequently', we use the value of D_Jmax for C4 plants
[720]282
[2031]283  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Jmax_mtc  = &            !! Energy of deactivation for Jmax (J mol-1)
284  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! See Table 2 of Yin et al. (2009)
285  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! Medlyn et al. (2002) also uses 200000. for C3 plants
[720]286
[3972]287  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gm_mtc  = &              !! Energy of activation for gm (J mol-1)
288  & (/undef,  49600.,  49600.,  49600.,  49600.,  49600.,  49600.,  &   !! See Table 2 of Yin et al. (2009)
289  &  49600.,  49600.,  49600.,   undef,  49600.,   undef  /)           
290                 
291  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: S_gm_mtc  = &              !! Entropy term for gm (J K-1 mol-1)
292  & (/undef,   1400.,   1400.,   1400.,   1400.,   1400.,   1400.,  &   !! See Table 2 of Yin et al. (2009)
293  &   1400.,   1400.,   1400.,   undef,   1400.,   undef  /) 
294                 
295  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_gm_mtc  = &              !! Energy of deactivation for gm (J mol-1)
296  & (/undef, 437400., 437400., 437400., 437400., 437400., 437400.,  &   !! See Table 2 of Yin et al. (2009)
297  & 437400., 437400., 437400.,   undef, 437400.,   undef  /)           
298
[2031]299  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Rd_mtc  = &              !! Energy of activation for Rd (J mol-1)
300  & (/undef,  46390.,  46390.,  46390.,  46390.,  46390.,  46390.,  &   !! See Table 2 of Yin et al. (2009)
301  &  46390.,  46390.,  46390.,  46390.,  46390.,  46390.  /)           
[720]302
[2031]303  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Vcmax25_mtc  =  &          !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
[4962]304  & (/ undef,   45.0,    45.0,    35.0,   40.0,   50.0,   45.0,  &      !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
305  &     35.0,   35.0,    50.0,    50.0,   60.0,   60.0  /)
[511]306
[2031]307  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)
308  & (/undef,    2.59,    2.59,    2.59,    2.59,    2.59,    2.59,  &   !! See Table 3 of Kattge & Knorr (2007)
309  &    2.59,    2.59,    2.59,   1.715,    2.59,   1.715  /)            !! For C4 plants, we assume that there is no
310                                                                        !! 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)
311
312  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)
313  & (/undef,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  &   !! See Table 3 of Kattge & Knorr (2007)
314  &  -0.035,  -0.035,  -0.035,      0.,  -0.035,      0.  /)            !! We assume No acclimation term for C4 plants
315
316  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmC25_mtc  = &             !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
317  & (/undef,   404.9,   404.9,   404.9,   404.9,  404.9,   404.9,  &    !! See Table 2 of Yin et al. (2009) for C4
318  &   404.9,   404.9,   404.9,    650.,   404.9,   650.  /)             !! and Medlyn et al (2002) for C3
319
320  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmO25_mtc  = &             !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
321  & (/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
322  & 278400., 278400., 278400., 450000., 278400., 450000.  /)           
323
[3972]324REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Sco25_mtc  = &             !! Relative CO2 /O2 specificity factor for Rubisco at 25°C (bar bar-1)
325  & (/undef,   2800.,   2800.,   2800.,   2800.,   2800.,   2800.,  &   !! See Table 2 of Yin et al. (2009)
326  &   2800.,   2800.,   2800.,   2590.,   2800.,   2590.  /)           
327
328  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gm25_mtc  = &              !! Mesophyll diffusion conductance at 25°C (mol m-2 s-1 bar-1)
329  & (/undef,     0.4,     0.4,     0.4,     0.4,    0.4,      0.4,  &   !! See legend of Figure 6 of Yin et al. (2009)
330  &     0.4,     0.4,     0.4,   undef,     0.4,  undef  /)             !! and review by Flexas et al. (2008) - gm is not used for C4 plants
331
[2031]332  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gamma_star25_mtc  = &      !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
333  & (/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)
334  &   42.75,   42.75,   42.75,   42.75,   42.75,   42.75  /)   
335
336  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
337  & (/undef,    0.85,    0.85,    0.85,    0.85,    0.85,  0.85,  &     !! See Table 2 of Yin et al. (2009)
[3972]338  &    0.85,    0.85,    0.85,    0.72,    0.85,    0.72  /)           
[2031]339
340  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
341  & (/undef,    0.14,    0.14,    0.14,    0.14,    0.14,  0.14,  &     !! See Table 2 of Yin et al. (2009)
342  &    0.14,    0.14,    0.14,    0.20,    0.14,    0.20  /)           
343
344  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: g0_mtc  = &                !! Residual stomatal conductance when irradiance approaches zero (mol CO2 m−2 s−1 bar−1)
345  & (/undef, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625,  &   !! Value from ORCHIDEE - No other reference.
346  & 0.00625, 0.00625, 0.00625, 0.01875, 0.00625, 0.01875  /)            !! modofy to account for the conversion for conductance to H2O to CO2
347
348  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: h_protons_mtc  = &         !! Number of protons required to produce one ATP (mol mol-1)
349  & (/undef,      4.,      4.,      4.,      4.,      4.,    4.,  &     !! See Table 2 of Yin et al. (2009) - h parameter
350  &      4.,      4.,      4.,      4.,      4.,      4.  /)           
351
352  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpsir_mtc = &              !! Fraction of PSII e− transport rate
353  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! partitioned to the C4 cycle (-)
354  &   undef,   undef,   undef,     0.4,   undef,    0.4  /)             !! See Table 2 of Yin et al. (2009) - x parameter       
355 
356  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fQ_mtc = &                 !! Fraction of electrons at reduced plastoquinone
357  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! that follow the Q-cycle (-) - Values for C3 platns are not used
358  &   undef,   undef,   undef,      1.,   undef,     1.  /)             !! See Table 2 of Yin et al. (2009)         
359
360  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpseudo_mtc = &            !! Fraction of electrons at PSI that follow
361  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! pseudocyclic transport (-) - Values for C3 platns are not used
362  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)             !! See Table 2 of Yin et al. (2009)   
363
364  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kp_mtc = &                 !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
365  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See Table 2 of Yin et al. (2009)
366  &   undef,   undef,   undef,     0.7,   undef,    0.7  /)                 
367
368  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_mtc = &              !! Fraction of PSII activity in the bundle sheath (-)
369  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
370  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)                 
371
372  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gbs_mtc = &                !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
373  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
374  &   undef,   undef,   undef,   0.003,   undef,  0.003  /)   
375
376  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: theta_mtc = &              !! Convexity factor for response of J to irradiance (-)
377  & (/undef,     0.7,     0.7,     0.7,     0.7,    0.7,    0.7,  &     !! See Table 2 of Yin et al. (2009)
378  &     0.7,     0.7,     0.7,     0.7,     0.7,    0.7  /)
379
380  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)
381  & (/undef,     0.3,     0.3,     0.3,     0.3,    0.3,    0.3,  &     !! See comment from Yin et al. (2009) after eq. 4
382  &     0.3,     0.3,     0.3,     0.3,     0.3,    0.3  /)             !! alpha value from Medlyn et al. (2002)   
383                                                                        !! 0.093 mol CO2 fixed per mol absorbed photons
384                                                                        !! times 4 mol e- per mol CO2 produced
[3972]385
386  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_vcmax_mtc = &       !! Water stress on vcmax
387  & (/    1.,     1.,     1.,       1.,      1.,     1.,      1., &
388  &      1.,     1.,     1.,       1.,      1.,     1.  /)
389
390  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_gs_mtc = &          !! Water stress on gs
[4962]391  & (/    1.,     1.,     1.,       1.,      1.,     1.,      1., &
392  &      1.,     1.,     1.,       1.,      1.,     1.  /)
[3972]393
394  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_gm_mtc = &          !! Water stress on gm
[4962]395  & (/    1.,     1.,     1.,       1.,      1.,     1.,      1., &
396  &      1.,     1.,     1.,       1.,      1.,     1.  /)
[2031]397   
398  !-
399  ! 2 .Stomate
400  !-
401  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_mtc  =  &     !! extinction coefficient of the Monsi&Saeki
402  & (/ 0.5,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &             !! relationship (1953) (unitless)
403  &    0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
[3524]404  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_vegetfrac_mtc  =  &     !! extinction coefficient used for defining the fraction
405  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                       !!  of bare soil (unitless)
406  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
[2031]407
[1882]408  !
409  ! ALLOCATION (stomate)
410  !
[2282]411  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: R0_mtc = &              !! Default root allocation (0-1, unitless)
412  & (/ undef,   0.30,   0.30,   0.30,   0.30,  0.30,    0.30, &
413  &     0.30,   0.30,   0.30,   0.30,   0.30,  0.30 /)                   
414
[1882]415  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: S0_mtc = &              !! Default sapwood allocation (0-1, unitless)
416  & (/ undef,   0.25,   0.25,   0.30,   0.30,  0.30,    0.30, &
417  &     0.30,   0.30,   0.30,   0.30,   0.30,  0.30 /)                   
[511]418
419  !
[531]420  ! RESPIRATION (stomate)
421  !
[2282]422  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_mtc  =  &  !! fraction of GPP which is lost as growth respiration
[4962]423  & (/  undef,   0.35,   0.35,   0.28,   0.28,   0.28,   0.35,  &
424  &      0.35,   0.35,   0.28,   0.28,   0.28,   0.28  /)
[2282]425
[720]426  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_c_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
[4962]427  & (/  undef,   0.12,   0.12,   0.16,   0.16,   0.16,   0.25,  &          !! constant c of aT^2+bT+c, tabulated
428  &      0.25,   0.25,   0.16,   0.12,   0.16,   0.12  /)
[720]429
430  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_b_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
431  & (/  undef,   0.0,        0.0,   0.0,        0.0,   0.0,   0.0,  &      !! constant b of aT^2+bT+c, tabulated
[531]432  &       0.0,   0.0,   -0.00133,   0.0,   -0.00133,   0.0  /)
[720]433
434  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_a_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
435  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                !! constant a of aT^2+bT+c, tabulated
[531]436  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)
[511]437
[720]438  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_leaf_mtc  =   &                  !! maintenance respiration coefficient
[733]439  & (/   undef,   2.35E-3,   2.62E-3,   1.01E-3,   2.35E-3,   2.62E-3,   1.01E-3,  &  !! at 0 deg C,for leaves, tabulated,
[1082]440  &    2.62E-3,   2.05E-3,   2.62E-3,   2.62E-3,   2.62E-3,   2.62E-3  /)             !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[511]441
[720]442  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapabove_mtc =  &                !! maintenance respiration coefficient
[733]443  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for sapwood above,
[1082]444  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[720]445
446  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapbelow_mtc  =  &               !! maintenance respiration coefficient
[733]447  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for sapwood below,
[1082]448  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[720]449
450  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartabove_mtc  =  &             !! maintenance respiration coefficient
[733]451  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                           !! at 0 deg C, for heartwood above,
[1082]452  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                                  !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[720]453
454  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartbelow_mtc  =  &             !! maintenance respiration coefficient
[733]455  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                           !! at 0 deg C, for heartwood below,
[1082]456  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                                  !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[720]457
458  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_root_mtc  =  &                   !! maintenance respiration coefficient
[733]459  & (/   undef,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,  &  !! at 0 deg C, for roots, tabulated,
[1082]460  &    1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3  /)             !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[720]461
462  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_fruit_mtc  =  &                  !! maintenance respiration coefficient
[733]463  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for fruits, tabulated,
[1082]464  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !!  @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[720]465
466  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_carbres_mtc  =  &                !! maintenance respiration coefficient
[733]467  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for carbohydrate reserve,
[1082]468  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
[720]469
470
[511]471  !
[531]472  ! FIRE (stomate)
473  !
[720]474  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: flam_mtc  =  &         !! flamability: critical fraction of water
475  & (/  undef,   0.15,   0.25,   0.25,   0.25,   0.25,   0.25,  &  !! holding capacity (0-1, unitless)
[531]476  &      0.25,   0.25,   0.25,   0.25,   0.35,   0.35  /)
[720]477
478  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: resist_mtc  =  &       !! fire resistance (0-1, unitless)
[2668]479  & (/ undef,   0.95,   0.90,   0.90,   0.90,   0.90,   0.90,  &
480  &    0.90,    0.90,    0.0,    0.0,    0.0,    0.0 /) 
[511]481
482
483  !
[531]484  ! FLUX - LUC
485  !
[720]486  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_1_mtc  =  &   !! Coeff of biomass export for the year
[1882]487  & (/  undef,   0.897,   0.897,   0.597,   0.597,   0.597,   0.597,  &   !! (0-1, unitless)
[531]488  &     0.597,   0.597,   0.597,   0.597,   0.597,   0.597  /)
[720]489
490  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_10_mtc  =  &  !! Coeff of biomass export for the decade
[1882]491  & (/  undef,   0.103,   0.103,   0.299,   0.299,   0.299,   0.299,  &   !! (0-1, unitless)
[720]492  &     0.299,   0.299,   0.299,   0.403,   0.299,   0.403  /) 
493
494  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_100_mtc  =  & !! Coeff of biomass export for the century
495  & (/  undef,     0.0,     0.0,   0.104,   0.104,   0.104,   0.104,  &   !! (0-1, unitless)
[531]496  &     0.104,   0.104,   0.104,     0.0,   0.104,     0.0  /)
[511]497
498
[531]499  !
500  ! PHENOLOGY
501  !
[4640]502  ! The latest modifications regarding leafagecrit, senescence_temp_c, leaffall, hum_min_time and nosenescence_hum are inspired by
503  ! MacBean et al. (2015), following the optimization of phenology parameters using MODIS NDVI (FM/PP).
[511]504  !-
[531]505  ! 1. Stomate
[511]506  !-
[2282]507  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_max_to_happy_mtc  =  &  !! threshold of LAI below which plant uses carbohydrate reserves
508  & (/  undef,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &
509  &       0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
510
[1082]511  REAL(r_std), PARAMETER, DIMENSION (nvmc) :: lai_max_mtc  =  &          !! maximum LAI, PFT-specific
[4964]512  & (/ undef,   7.0,   5.0,   5.0,   4.0,   5.0,   3.5,  &               !! @tex $(m^2.m^{-2})$ @endtex
[4962]513  &      4.0,   3.0,   2.5,   2.0,   5.0,   5.0  /)
[720]514
515  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pheno_type_mtc  =  &     !! type of phenology (0-4, unitless)
516  & (/  0,   1,   3,   1,   1,   2,   1,  &                              !! 0=bare ground 1=evergreen,  2=summergreen,
517  &     2,   2,   4,   4,   2,   3  /)                                   !! 3=raingreen,  4=perennial
[511]518  !-
519  ! 2. Leaf Onset
520  !-
[720]521  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_c_mtc  =  &    !! critical gdd, tabulated (C),
522  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant c of aT^2+bT+c
[1102]523  &     undef,   undef,   320.0,   400.0,   320.0,   700.0  /)
[720]524
525  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_b_mtc  =  &    !! critical gdd, tabulated (C),
526  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant b of aT^2+bT+c
[1102]527  &     undef,   undef,    6.25,     0.0,    6.25,     0.0  /)
[720]528
529  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_a_mtc  =  &    !! critical gdd, tabulated (C),
530  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  &  !! constant a of aT^2+bT+c
[1102]531  &     undef,   undef,   0.03125,     0.0,  0.0315,   0.0  /)
[720]532
[2665]533  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_moigdd_t_crit_mtc  = &  !! temperature threshold for C4 grass(C)
534  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  & 
535  &     undef,   undef,     undef,    22.0,   undef,   undef  /)
536
[720]537  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ngd_crit_mtc  =  &            !! critical ngd, tabulated.
538  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! Threshold -5 degrees (days)
[531]539  &     undef,    17.0,   undef,   undef,   undef,   undef  /)
[720]540
541  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ncdgdd_temp_mtc  =  &         !! critical temperature for the ncd vs. gdd
542  & (/  undef,   undef,   undef,   undef,   undef,     5.0,   undef,  &    !! function in phenology (C)
[531]543  &       0.0,   undef,   undef,   undef,   undef,   undef  /)
[720]544
545  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_frac_mtc  =  &            !! critical humidity (relative to min/max)
546  & (/  undef,   undef,   0.5,   undef,   undef,   undef,   undef, &       !! for phenology (unitless)
[531]547  &     undef,   undef,   0.5,     0.5,     0.5,     0.5  /)
[720]548
549  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_min_time_mtc  =  &        !! minimum time elapsed since
550  & (/  undef,   undef,   50.0,   undef,   undef,   undef,   undef,  &     !! moisture minimum (days)
[3933]551  &     undef,   undef,   36.0,    35.0,    75.0,    75.0  /) 
[720]552
553  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_sap_mtc  =  &             !! time (days) 
[531]554  & (/  undef,   730.0,   730.0,   730.0,   730.0,   730.0,   730.0,  &
555  &     730.0,   730.0,   undef,   undef,   undef,   undef  /)
[720]556
[2282]557  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_leafinit_mtc  =  &  !! time to attain the initial foliage using the carbohydrate reserve
558  & (/  undef,   10.,   10.,   10.,   10.,   10.,   10.,  &
559  &       10.,   10.,   10.,   10.,   10.,   10.  /)
560
[720]561  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_fruit_mtc  =  &           !! fruit lifetime (days)
[531]562  & (/  undef,  90.0,    90.0,    90.0,    90.0,   90.0,   90.0,  &
563  &      90.0,  90.0,   undef,   undef,   undef,   undef  /)
[720]564
565  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ecureuil_mtc  =  &            !! fraction of primary leaf and root allocation
566  & (/  undef,   0.0,   1.0,   0.0,   0.0,   1.0,   0.0,  &                !! put into reserve (0-1, unitless)
[531]567  &       1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
[720]568
569  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_min_mtc  =  &           !! NEW - allocation above/below = f(age)
570  & (/  undef,   0.2,     0.2,     0.2,     0.2,    0.2,   0.2,  &         !! - 30/01/04 NV/JO/PF
[531]571  &       0.2,   0.2,   undef,   undef,   undef,   undef  /)
[720]572
573  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_max_mtc  =  &           !! NEW - allocation above/below = f(age)
574  & (/  undef,   0.8,     0.8,     0.8,     0.8,    0.8,   0.8,  &         !! - 30/01/04 NV/JO/PF
[531]575  &       0.8,   0.8,   undef,   undef,   undef,   undef  /)
[720]576
577  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: demi_alloc_mtc  =  &          !! NEW - allocation above/below = f(age)
578  & (/  undef,   5.0,     5.0,     5.0,     5.0,    5.0,   5.0,  &         !! - 30/01/04 NV/JO/PF
[531]579  &       5.0,   5.0,   undef,   undef,   undef,   undef  /)
[720]580
581  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaflife_mtc  =  &            !! leaf longevity, tabulated (??units??)
[531]582  & (/  undef,   0.5,   2.0,   0.33,   1.0,   2.0,   0.33,  &
583  &       2.0,   2.0,   2.0,   2.0,    2.0,   2.0  /)
[511]584  !-
585  ! 3. Senescence
586  !-
[720]587  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaffall_mtc  =  &             !! length of death of leaves, tabulated (days)
[3933]588  & (/  undef,   undef,   10.0,   undef,   undef,   30.0,   undef,  &
589  &       5.0,    10.0,   10.0,    10.0,    10.0,   10.0  /)
[720]590
591  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leafagecrit_mtc  =  &          !! critical leaf age, tabulated (days)
[3933]592  & (/  undef,   730.0,   180.0,   910.0,   730.0,   160.0,   910.0,  &
593  &     220.0,   120.0,    80.0,   120.0,    90.0,    90.0  /)
[720]594
595  CHARACTER(LEN=6), PARAMETER, DIMENSION(nvmc) :: senescence_type_mtc  =  & !! type of senescence, tabulated (unitless)
[531]596  & (/  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ',  &
597  &     'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ',  &
[511]598  &     'mixed ',  'mixed ',   'mixed '            /)
[720]599
600  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_hum_mtc  =  &       !! critical relative moisture availability
601  & (/  undef,   undef,   0.3,   undef,   undef,   undef,   undef,  &       !! for senescence (0-1, unitless)
[531]602  &     undef,   undef,   0.2,     0.2,     0.3,     0.2  /)
[720]603
604  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nosenescence_hum_mtc  =  &     !! relative moisture availability above which
605  & (/  undef,   undef,   0.8,   undef,   undef,   undef,   undef,  &       !! there is no humidity-related senescence
[3933]606  &     undef,   undef,   0.6,     0.3,     0.3,     0.3  /)                !! (0-1, unitless)
[720]607
608  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_turnover_time_mtc  =  &    !! maximum turnover time for grasses (days)
[531]609  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
610  &     undef,   undef,    80.0,    80.0,    80.0,    80.0  /)
[720]611
612  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_turnover_time_mtc  =  &    !! minimum turnover time for grasses (days)
[531]613  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
614  &     undef,   undef,    10.0,    10.0,    10.0,    10.0  /)
[720]615 
616  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_leaf_age_for_senescence_mtc  =  &  !! minimum leaf age to allow
617  & (/  undef,   undef,   90.0,   undef,   undef,   90.0,   undef,  &               !! senescence g (days)
[531]618  &      60.0,    60.0,   30.0,    30.0,    30.0,   30.0  /)
[511]619
[720]620  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_c_mtc  =  &    !! critical temperature for senescence (C)
[3933]621  & (/  undef,   undef,    undef,   undef,   undef,   16.0,   undef,  &     !! constant c of aT^2+bT+c, tabulated
622  &      14.0,    10.0,      5.0,     5.0,     5.0,    10.0  /)             !! (unitless)
[511]623
[720]624  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_b_mtc  =  &    !! critical temperature for senescence (C),
625  & (/  undef,   undef,   undef,   undef,   undef,   0.0,   undef,  &       !! constant b of aT^2+bT+c, tabulated
626  &       0.0,     0.0,     0.1,     0.0,     0.0,   0.0  /)                !! (unitless)
627
628  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_a_mtc  =  &    !! critical temperature for senescence (C),
629  & (/  undef,   undef,     undef,   undef,   undef,   0.0,   undef,  &     !! constant a of aT^2+bT+c, tabulated
630  &       0.0,     0.0,   0.00375,     0.0,     0.0,   0.0  /)              !! (unitless)
631
[1102]632  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gdd_senescence_mtc  =  &       !! minimum gdd to allow senescence of crops (days)
633  & (/  undef,   undef,    undef,   undef,     undef,    undef,    undef,  &
634  &     undef,   undef,    undef,   undef,      950.,    4000.  /)
[720]635
[4902]636  LOGICAL, PARAMETER, DIMENSION(nvmc) :: always_init_mtc  =  &              !! take carbon from atmosphere if carbohydrate reserve too small (true/false)
[4962]637  & (/ .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .TRUE., &!! default is true for all pfts except pft=11 C4 grass
638  &    .TRUE.,   .TRUE.,   .TRUE.,   .FALSE.,   .TRUE.,   .TRUE. /)   
[1102]639
[4902]640
[531]641  !
[511]642  ! DGVM
643  !
[720]644  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: residence_time_mtc  =  &    !! residence time of trees (years)
[531]645  & (/  undef,   30.0,   30.0,   40.0,   40.0,   40.0,   80.0,  &
646  &      80.0,   80.0,    0.0,    0.0,    0.0,    0.0  /) 
[720]647
[531]648  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_crit_mtc  =  &
[720]649  & (/  undef,     0.0,     0.0,   -30.0,   -14.0,   -30.0,   -45.0,  &  !! critical tmin, tabulated (C)
[4480]650  &     -45.0,   -60.0,   undef,   undef,   undef,   undef  /)
[720]651
[531]652  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tcm_crit_mtc  =  &
[720]653  & (/  undef,   undef,   undef,     5.0,    15.5,    15.5,   -8.0,  &   !! critical tcm, tabulated (C)
[531]654  &      -8.0,    -8.0,   undef,   undef,   undef,   undef  /)
[511]655
656
[890]657
658  !
659  ! Biogenic Volatile Organic Compounds
660  !
661  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_isoprene_mtc = &     !! Isoprene emission factor
[1082]662  & (/  0.,    24.,   24.,    8.,   16.,   45.,   8.,  &                    !!
[3221]663  &    18.,    0.5,   12.,   18.,    5.,    5.  /)
[890]664
665  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_monoterpene_mtc = &  !! Monoterpene emission factor
[3221]666  & (/   0.,   2.0,    2.0,   1.8,    1.4,    1.6,    1.8,  &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
667  &    1.4,    1.8,    0.8,   0.8,    0.22,     0.22  /)
[890]668
[3221]669  REAL(r_std), PARAMETER :: LDF_mono_mtc = 0.6                                  !! monoterpenes fraction dependancy to light
670  REAL(r_std), PARAMETER :: LDF_sesq_mtc = 0.5                                  !! sesquiterpenes fraction dependancy to light
671  REAL(r_std), PARAMETER :: LDF_meth_mtc = 0.8                                  !! methanol fraction dependancy to light
672  REAL(r_std), PARAMETER :: LDF_acet_mtc = 0.2                                  !! acetone fraction dependancy to light
673
674  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_apinene_mtc = &      !! Alfa pinene emission factor percentage
675  & (/   0.,   0.395,   0.395,   0.354,   0.463,   0.326,   0.354, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
676  &   0.316,   0.662,   0.231,   0.200,   0.277,   0.277 /)
677
678  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_bpinene_mtc = &      !! Beta pinene emission factor  percentage     
679  & (/   0.,   0.110,   0.110,   0.146,   0.122,   0.087,   0.146, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
680  &   0.063,   0.150,   0.123,   0.080,   0.154,   0.154  /)
681
682  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_limonene_mtc = &     !! Limonene emission factor percentage
683  & (/   0.,   0.092,   0.092,   0.083,   0.122,   0.061,   0.083, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
684  &   0.071,   0.037,   0.146,   0.280,   0.092,   0.092  /)
685
686  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_myrcene_mtc = &      !! Myrcene emission factor percentage
687  & (/   0.,   0.073,   0.073,   0.050,   0.054,   0.028,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
688  &   0.019,   0.025,   0.062,   0.057,   0.046,   0.046  /)
689
690  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sabinene_mtc = &     !! Sabinene emission factor percentage
691  & (/   0.,   0.073,   0.073,   0.050,   0.083,   0.304,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
692  &   0.263,   0.030,   0.065,   0.050,   0.062,   0.062  /)
693
694  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_camphene_mtc = &     !! Camphene emission factor percentage
695  & (/   0.,   0.055,   0.055,   0.042,   0.049,   0.004,   0.042, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
696  &   0.005,   0.023,   0.054,   0.053,   0.031,   0.031  /)
697
698  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_3carene_mtc = &      !! 3-carene emission factor percentage
699  & (/   0.,   0.048,   0.048,   0.175,   0.010,   0.024,   0.175, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
700  &   0.013,   0.042,   0.065,   0.057,   0.200,   0.200  /)
701
702  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_tbocimene_mtc = &    !! T-beta-ocimene emission factor percentage
703  & (/   0.,   0.092,   0.092,   0.054,   0.044,   0.113,   0.054, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
704  &   0.105,   0.028,   0.138,   0.120,   0.031,   0.031  /)
705
706  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_othermonot_mtc = &   !! Other monoterpenes emission factor percentage
707  & (/   0.,   0.062,   0.062,   0.046,   0.054,   0.052,   0.046, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
708  &   0.144,   0.003,   0.115,   0.103,   0.108,   0.108  /)
709
710  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sesquiterp_mtc = &   !! Sesquiterpene emission factor
711  & (/   0.,  0.45,   0.45,   0.13,   0.30,   0.36,   0.15, &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
712  &    0.30,  0.25,   0.60,   0.60,   0.08,   0.08  /)
713
714  REAL(r_std), PARAMETER :: beta_mono_mtc = 0.10                            !! Monoterpenes temperature dependency coefficient
715  REAL(r_std), PARAMETER :: beta_sesq_mtc = 0.17                            !! Sesquiterpenes temperature dependency coefficient
716  REAL(r_std), PARAMETER :: beta_meth_mtc = 0.08                            !! Methanol temperature dependency coefficient
717  REAL(r_std), PARAMETER :: beta_acet_mtc = 0.10                            !! Acetone temperature dependency coefficient
718  REAL(r_std), PARAMETER :: beta_oxyVOC_mtc = 0.13                          !! Other oxygenated BVOC temperature dependency coefficient
719
720
[890]721  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_ORVOC_mtc = &        !! ORVOC emissions factor
[1082]722  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[890]723  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /) 
724
725  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_OVOC_mtc = &         !! OVOC emissions factor
[1082]726  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
[890]727  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /)
728 
729  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_MBO_mtc = &          !! MBO emissions factor
[3221]730  & (/     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
731  &     2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5  /) 
[890]732 
733  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_methanol_mtc = &     !! Methanol emissions factor
[3221]734  & (/  0.,    0.8,   0.8,   1.8,   0.9,   1.9,   1.8,  &                   !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
735  &    1.8,    1.8,   0.7,   0.9,    2.,     2.  /) 
[890]736 
737  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetone_mtc = &      !! Acetone emissions factor
[3221]738  & (/  0.,   0.25,   0.25,   0.30,   0.20,   0.33,   0.30,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
739  &   0.25,   0.25,   0.20,   0.20,   0.08,   0.08  /)
[890]740 
741  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetal_mtc = &       !! Acetaldehyde emissions factor
[3221]742  & (/  0.,   0.2,    0.2,     0.2,   0.2,   0.25,   0.25,   0.16,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
743  &   0.16,   0.12,   0.12,   0.035,   0.020  /) 
[890]744 
745  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formal_mtc = &       !! Formaldehyde emissions factor
[3221]746  & (/  0.,   0.04,   0.04,  0.08,    0.04,    0.04,  0.04,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
747  &   0.04,   0.04,  0.025, 0.025,   0.013,   0.013  /) 
[890]748
749  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetic_mtc = &       !! Acetic Acid emissions factor
[3221]750  & (/   0.,   0.025,   0.025,   0.025,   0.022,   0.08,   0.025,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
751  &   0.022,   0.013,   0.012,   0.012,   0.008,   0.008  /) 
[890]752
753  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formic_mtc = &       !! Formic Acid emissions factor
[3221]754  & (/  0.,  0.015,  0.015,   0.02,    0.02,   0.025,  0.025,  &            !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
755  &  0.015,  0.015,  0.010,  0.010,   0.008,   0.008  /) 
[890]756
757  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_wet_mtc = &        !! NOx emissions factor soil emissions and exponential
[1082]758  & (/  0.,   2.6,   0.06,   0.03,   0.03,   0.03,   0.03,  &               !! dependancy factor for wet soils
759  &  0.03,   0.03,   0.36,   0.36,   0.36,   0.36  /)                       !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
[890]760
761  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_dry_mtc = &        !! NOx emissions factor soil emissions and exponential
[1082]762  & (/  0.,   8.60,   0.40,   0.22,   0.22,   0.22,   0.22,  &              !! dependancy factor for dry soils
763  &   0.22,   0.22,   2.65,   2.65,   2.65,   2.65  /)                      !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
[890]764
765  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Larch_mtc = &                  !! Larcher 1991 SAI/LAI ratio (unitless)
766  & (/   0.,   0.015,   0.015,   0.003,   0.005,   0.005,   0.003,  &
767  &   0.005,   0.003,   0.005,   0.005,   0.008,   0.008  /) 
768
769
770
[511]771END MODULE constantes_mtc
Note: See TracBrowser for help on using the repository browser.