Ignore:
Timestamp:
2011-06-17T14:02:17+02:00 (13 years ago)
Author:
didier.solyga
Message:

Externalized version merged with the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_EXT/ORCHIDEE/src_parameters/constantes_mtc.f90

    r64 r257  
    7575  &    .TRUE.,  .TRUE.,  .TRUE., .TRUE., .FALSE., & 
    7676  &    .FALSE., .FALSE., .FALSE. /) 
    77   !- 
     77  ! used in diffuco 
     78  REAL(r_std), PARAMETER, DIMENSION(nvmc)        :: rveg_mtc = &   
     79  & (/ 1., 1., 1., 1., 1., 1. ,1. ,1. ,1. ,1. ,1. ,1., 1. /) 
     80  ! 
    7881  !- 
    7982  ! 2 .Stomate 
     
    9598  &              .TRUE.,  .TRUE.,  .TRUE.,  .TRUE., .FALSE., .FALSE. /) 
    9699 
     100  !>> DS new for merge in the trunk   ! 15/06/2011  
     101  ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' 
     102  ! is PFT deciduous ? 
     103  LOGICAL, PARAMETER, DIMENSION(nvmc)    :: is_deciduous_mtc  = & 
     104  & (/  .FALSE.,  .FALSE.,  .TRUE.,  .FALSE.,  .FALSE.,  .TRUE.,  .FALSE.,   & 
     105  &              .TRUE.,  .TRUE.,  .FALSE.,  .FALSE., .FALSE., .FALSE. /) 
     106  ! is PFT evergreen ? 
     107  LOGICAL, PARAMETER, DIMENSION(nvmc)    :: is_evergreen_mtc  = & 
     108  & (/  .FALSE.,  .TRUE.,  .FALSE.,  .TRUE.,  .TRUE.,  .FALSE.,  .TRUE.,   & 
     109  &              .FALSE.,  .FALSE.,  .FALSE.,  .FALSE., .FALSE., .FALSE. /)         
     110  ! is PFT C3 ? 
     111  LOGICAL, PARAMETER, DIMENSION(nvmc)    :: is_c3_mtc = &   
     112  & (/.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE.,         & 
     113  &   .FALSE.,.FALSE.,.FALSE.,.TRUE.,.FALSE.,.TRUE.,.FALSE. /) 
     114 
     115  !------------------------------- 
     116  ! Evapotranspiration -  sechiba 
     117  !------------------------------- 
     118  ! 
     119  ! Structural resistance. 
     120  ! Value for rstruct_const : one for each vegetation type 
     121  REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: rstruct_const_mtc = & 
     122  & (/ 0.0, 25.0, 25.0, 25.0, 25.0, 25.0, 25.0,   & 
     123  &   25.0, 25.0,  2.5,  2.0,  2.0,  2.0 /) 
     124  !- 
     125  ! A vegetation dependent constant used in the calculation 
     126  ! of the surface resistance. 
     127  ! Value for kzero one for each vegetation type 
     128  REAL(r_std), PARAMETER, DIMENSION(nvmc)     ::  kzero_mtc  =  & 
     129  & (/0.0, 12.E-5, 12.E-5, 12.e-5, 12.e-5, 25.e-5, 12.e-5,& 
     130  &    25.e-5, 25.e-5, 30.e-5, 30.e-5, 30.e-5, 30.e-5     /) 
     131 
     132 
     133  !------------------- 
     134  ! Water - sechiba 
     135  !------------------- 
     136  ! 
     137  ! Maximum field capacity for each of the vegetations (Temporary). 
     138  ! Value of wmax_veg : max quantity of water : 
     139  ! one for each vegetation type en Kg/M3 
     140  REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: wmax_veg_mtc  = & 
     141  & (/ 150., 150., 150., 150., 150., 150., 150., & 
     142  &    150., 150., 150., 150., 150., 150. /) 
     143  !- 
     144  ! Root profile description for the different vegetation types. 
     145  ! These are the factor in the exponential which gets 
     146  ! the root density as a function of depth 
     147  REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: humcste_mtc  = & 
     148  & (/5., .8, .8, 1., .8, .8, 1., 1., .8, 4., 4., 4., 4./) 
     149  ! used in both hydrology modules 
     150   REAL(r_std), PARAMETER, DIMENSION(nvmc)              :: throughfall_by_mtc = & 
     151  & (/ 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30. /) 
     152 
     153  !------------------ 
     154  ! Albedo - sechiba 
     155  !------------------ 
     156  ! 
     157  ! Initial snow albedo value for each vegetation type 
     158  ! as it will be used in condveg_snow 
     159  ! Values are from the Thesis of S. Chalita (1992) 
     160  REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: snowa_ini_mtc = & 
     161  & (/ 0.35, 0.,   0.,   0.14, 0.14, & 
     162  &    0.14, 0.14, 0.14, 0.14, 0.18, & 
     163  &    0.18, 0.18, 0.18 /) 
     164  !- 
     165  ! Decay rate of snow albedo value for each vegetation type 
     166  ! as it will be used in condveg_snow 
     167  ! Values are from the Thesis of S. Chalita (1992) 
     168  REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: snowa_dec_mtc = & 
     169  & (/ 0.45, 0.,   0.,   0.06, 0.06, & 
     170  &    0.11, 0.06, 0.11, 0.11, 0.52, & 
     171  &    0.52, 0.52, 0.52 /) 
     172  !- 
     173  ! leaf albedo of vegetation type, visible albedo 
     174  REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: alb_leaf_vis_mtc = & 
     175  & (/ .00, .04, .06, .06, .06, & 
     176  &    .06, .06, .06, .06, .10, & 
     177  &    .10, .10, .10 /)  
     178  ! leaf albedo of vegetation type, near infrared albedo 
     179  REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: alb_leaf_nir_mtc = & 
     180  & (/   .00, .20, .22, .22, .22, & 
     181  &      .22, .22, .22, .22, .30, & 
     182  &      .30, .30, .30   /) 
     183 
     184 
     185  !------------------------ 
     186  !   Soil - vegetation 
     187  !------------------------ 
     188  ! 
     189  ! Table which contains the correlation between the soil types 
     190  ! and vegetation type. Two modes exist : 
     191  !  1) pref_soil_veg = 0 then we have an equidistribution 
     192  !     of vegetation on soil types 
     193  !  2) Else for each pft the prefered soil type is given : 
     194  !     1=sand, 2=loan, 3=clay 
     195  ! The variable is initialized in slowproc. 
     196  INTEGER(i_std), PARAMETER, DIMENSION(nvmc)     :: pref_soil_veg_sand_mtc = & 
     197  & (/ 1, 3, 3, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2 /) 
     198 
     199  INTEGER(i_std), PARAMETER, DIMENSION(nvmc)     :: pref_soil_veg_loan_mtc = & 
     200  & (/ 2, 2, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3 /) 
     201 
     202  INTEGER(i_std), PARAMETER, DIMENSION(nvmc)     :: pref_soil_veg_clay_mtc = & 
     203  & (/ 3, 1, 1, 1, 1, 1 ,1 ,1 ,1 ,1 ,1 ,1, 1 /) 
    97204 
    98205  !---------------- 
     
    104211  ! flag for C4 vegetation types 
    105212  LOGICAL,PARAMETER, DIMENSION(nvmc) ::    is_c4_mtc  =        &   
    106   & (/.false.,.false.,.false.,.false.,.false.,.false.,         & 
    107   &   .false.,.false.,.false.,.false.,.true.,.false.,.true. /) 
     213  & (/.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE.,.FALSE.,         & 
     214  &   .FALSE.,.FALSE.,.FALSE.,.FALSE.,.TRUE.,.FALSE.,.TRUE. /) 
    108215  !- 
    109216  ! Slope of the gs/A relation (Ball & al.) 
     
    409516  & (/ undef,    5.,        5.,       5.,        5.,       5.,      5.,   & 
    410517  &              5.,        5.,    undef,     undef,    undef,   undef   /) 
     518 
     519  !>> DS new for merge in the trunk 
     520  ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla 
     521  REAL(r_std) ,PARAMETER , DIMENSION(nvmc)   ::   leaflife_mtc = & 
     522  & (/  undef,      .5,      2.,     .33,      1.,     2.,      .33,   & 
     523  &            2.,      2.,      2.,      2.,     2.,        2. /) 
     524 
    411525  !- 
    412526  ! 3. Senescence 
     
    493607 
    494608 
    495   !------------------------------- 
    496   ! Evapotranspiration -  sechiba 
    497   !------------------------------- 
    498   ! 
    499   ! Structural resistance. 
    500   ! Value for rstruct_const : one for each vegetation type 
    501   REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: rstruct_const_mtc = & 
    502   & (/ 0.0, 25.0, 25.0, 25.0, 25.0, 25.0, 25.0,   & 
    503   &   25.0, 25.0,  2.5,  2.0,  2.0,  2.0 /) 
    504   !- 
    505   ! A vegetation dependent constant used in the calculation 
    506   ! of the surface resistance. 
    507   ! Value for kzero one for each vegetation type 
    508   REAL(r_std), PARAMETER, DIMENSION(nvmc)     ::  kzero_mtc  =  & 
    509   & (/0.0, 12.E-5, 12.E-5, 12.e-5, 12.e-5, 25.e-5, 12.e-5,& 
    510   &    25.e-5, 25.e-5, 30.e-5, 30.e-5, 30.e-5, 30.e-5     /) 
    511  
    512  
    513   !------------------- 
    514   ! Water - sechiba 
    515   !------------------- 
    516   ! 
    517   ! Maximum field capacity for each of the vegetations (Temporary). 
    518   ! Value of wmax_veg : max quantity of water : 
    519   ! one for each vegetation type en Kg/M3 
    520   REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: wmax_veg_mtc  = & 
    521   & (/ 150., 150., 150., 150., 150., 150., 150., & 
    522   &    150., 150., 150., 150., 150., 150. /) 
    523   !- 
    524   ! Root profile description for the different vegetation types. 
    525   ! These are the factor in the exponential which gets 
    526   ! the root density as a function of depth 
    527   REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: humcste_mtc  = & 
    528   & (/5., .8, .8, 1., .8, .8, 1., 1., .8, 4., 4., 4., 4./) 
    529  
    530  
    531   !------------------ 
    532   ! Albedo - sechiba 
    533   !------------------ 
    534   ! 
    535   ! Initial snow albedo value for each vegetation type 
    536   ! as it will be used in condveg_snow 
    537   ! Values are from the Thesis of S. Chalita (1992) 
    538   REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: snowa_ini_mtc = & 
    539   & (/ 0.35, 0.,   0.,   0.14, 0.14, & 
    540   &    0.14, 0.14, 0.14, 0.14, 0.18, & 
    541   &    0.18, 0.18, 0.18 /) 
    542   !- 
    543   ! Decay rate of snow albedo value for each vegetation type 
    544   ! as it will be used in condveg_snow 
    545   ! Values are from the Thesis of S. Chalita (1992) 
    546   REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: snowa_dec_mtc = & 
    547   & (/ 0.45, 0.,   0.,   0.06, 0.06, & 
    548   &    0.11, 0.06, 0.11, 0.11, 0.52, & 
    549   &    0.52, 0.52, 0.52 /) 
    550   !- 
    551   ! leaf albedo of vegetation type, visible albedo 
    552   REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: alb_leaf_vis_mtc = & 
    553   & (/ .00, .04, .06, .06, .06, & 
    554   &    .06, .06, .06, .06, .10, & 
    555   &    .10, .10, .10 /)  
    556   ! leaf albedo of vegetation type, near infrared albedo 
    557   REAL(r_std), PARAMETER, DIMENSION(nvmc)     :: alb_leaf_nir_mtc = & 
    558   & (/   .00, .20, .22, .22, .22, & 
    559   &      .22, .22, .22, .22, .30, & 
    560   &      .30, .30, .30   /) 
    561  
    562  
    563   ! 
    564   !------------------------ 
    565   !   Soil - vegetation 
    566   !------------------------ 
    567  
    568   ! Table which contains the correlation between the soil types 
    569   ! and vegetation type. Two modes exist : 
    570   !  1) pref_soil_veg = 0 then we have an equidistribution 
    571   !     of vegetation on soil types 
    572   !  2) Else for each pft the prefered soil type is given : 
    573   !     1=sand, 2=loan, 3=clay 
    574   ! The variable is initialized in slowproc. 
    575   INTEGER(i_std), PARAMETER, DIMENSION(nvmc)     :: pref_soil_veg_sand_mtc = & 
    576   & (/ 1, 3, 3, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2 /) 
    577  
    578   INTEGER(i_std), PARAMETER, DIMENSION(nvmc)     :: pref_soil_veg_loan_mtc = & 
    579   & (/ 2, 2, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3 /) 
    580  
    581   INTEGER(i_std), PARAMETER, DIMENSION(nvmc)     :: pref_soil_veg_clay_mtc = & 
    582   & (/ 3, 1, 1, 1, 1, 1 ,1 ,1 ,1 ,1 ,1 ,1, 1 /) 
    583  
    584  
    585   ! 
    586   !------------------------------- 
    587   ! Parameters already externalised (from sechiba) 
    588   ! to classify 
    589   !---------------------------------- 
    590   ! 
    591   ! used in hydrolc 
    592    REAL(r_std), PARAMETER, DIMENSION(nvmc)              :: throughfall_by_mtc = & 
    593   & (/ 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30., 30. /) 
    594   ! used in diffuco 
    595    REAL(r_std), PARAMETER, DIMENSION(nvmc)        :: rveg_mtc = &   
    596   & (/ 1., 1., 1., 1., 1., 1. ,1. ,1. ,1. ,1. ,1. ,1., 1. /) 
    597  
    598  
     609!------------------------ 
    599610END MODULE constantes_mtc 
Note: See TracChangeset for help on using the changeset viewer.