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/pft_parameters.f90

    r115 r257  
    1 !    09/2010 
     1! Version 0:   26/06/2010 
    22! This is the module where we define the number of pfts and the values of the  
    33! parameters 
     
    99USE constantes 
    1010USE ioipsl 
     11USE parallel 
    1112USE defprec 
    1213 
     
    5051  ! Is the vegetation type a tree ? 
    5152  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_tree 
     53  !>> DS new for merge in the trunk   ! 15/06/2011  
     54  ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' 
     55  ! is PFT deciduous ? 
     56  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_deciduous 
     57  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_evergreen 
     58  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_c3 
     59  ! used in diffuco   !! Nathalie le 28 mars 2006 - sur proposition de Fred Hourdin, ajout 
     60  !! d'un potentiometre pour regler la resistance de la vegetation 
     61  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      ::  rveg_pft 
     62 
    5263  !- 
    5364  ! 2 .Stomate 
     
    6172  LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:) :: natural 
    6273 
     74  !------------------------------- 
     75  ! Evapotranspiration -  sechiba 
     76  !------------------------------- 
     77  !- 
     78  ! Structural resistance. 
     79  ! Value for rstruct_const : one for each vegetation type 
     80  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: rstruct_const 
     81  ! 
     82  ! A vegetation dependent constant used in the calculation 
     83  ! of the surface resistance. 
     84  ! Value for kzero one for each vegetation type 
     85  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: kzero   
     86 
     87 
     88  !------------------- 
     89  ! Water - sechiba 
     90  !------------------- 
     91  !- 
     92  ! Maximum field capacity for each of the vegetations (Temporary). 
     93  ! Value of wmax_veg : max quantity of water : 
     94  ! one for each vegetation type en Kg/M3 
     95  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: wmax_veg 
     96  ! Root profile description for the different vegetation types. 
     97  ! These are the factor in the exponential which gets 
     98  ! the root density as a function of depth 
     99  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: humcste 
     100  ! used in hydrolc 
     101  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: throughfall_by_pft 
     102 
     103 
     104  !------------------ 
     105  ! Albedo - sechiba 
     106  !------------------ 
     107  !- 
     108  ! Initial snow albedo value for each vegetation type 
     109  ! as it will be used in condveg_snow 
     110  ! Values are from the Thesis of S. Chalita (1992) 
     111  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_ini 
     112  ! 
     113  ! Decay rate of snow albedo value for each vegetation type 
     114  ! as it will be used in condveg_snow 
     115  ! Values are from the Thesis of S. Chalita (1992) 
     116  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_dec 
     117  ! 
     118  ! leaf albedo of vegetation type, visible albedo 
     119  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_vis 
     120  ! leaf albedo of vegetation type, near infrared albedo 
     121  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_nir 
     122  ! leaf albedo of vegetation type, VIS+NIR 
     123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf 
     124 
     125 
     126  !------------------------ 
     127  !   Soil - vegetation 
     128  !------------------------ 
     129  ! 
     130  ! Table which contains the correlation between the soil types 
     131  ! and vegetation type. Two modes exist : 
     132  !  1) pref_soil_veg = 0 then we have an equidistribution 
     133  !     of vegetation on soil types 
     134  !  2) Else for each pft the prefered soil type is given : 
     135  !     1=sand, 2=loan, 3=clay 
     136  ! The variable is initialized in slowproc. 
     137  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: pref_soil_veg 
     138  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_sand 
     139  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_loan 
     140  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_clay 
    63141 
    64142  !---------------- 
     
    163241  ! for carbohydrate reserve, tabulated 
    164242  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::cm_zero_carbres 
     243 
    165244  
    166  
    167  
    168245  !---------------- 
    169246  ! Fire - stomate 
    170247  !---------------- 
    171  
     248  ! 
    172249  ! flamability: critical fraction of water holding capacity 
    173250  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: flam 
    174251  ! fire resistance 
    175252  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: resist 
    176  
    177253 
    178254 
     
    195271  ! 1 .Stomate 
    196272  !- 
    197   ! 
    198273  ! maximum LAI, PFT-specific 
    199274  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: lai_max  
     
    235310  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alloc_max 
    236311  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: demi_alloc 
     312  !>> DS new for merge in the trunk 
     313  ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla 
     314  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaflife_tab 
    237315  !- 
    238316  ! 3. Senescence 
     
    282360 
    283361 
    284   !------------------------------- 
    285   ! Evapotranspiration -  sechiba 
    286   !------------------------------- 
    287   !- 
    288   ! Structural resistance. 
    289   ! Value for rstruct_const : one for each vegetation type 
    290   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: rstruct_const 
    291   ! 
    292   ! A vegetation dependent constant used in the calculation 
    293   ! of the surface resistance. 
    294   ! Value for kzero one for each vegetation type 
    295   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: kzero   
    296  
    297  
    298   !------------------- 
    299   ! Water - sechiba 
    300   !------------------- 
    301   !- 
    302   ! Maximum field capacity for each of the vegetations (Temporary). 
    303   ! Value of wmax_veg : max quantity of water : 
    304   ! one for each vegetation type en Kg/M3 
    305   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: wmax_veg 
    306   ! Root profile description for the different vegetation types. 
    307   ! These are the factor in the exponential which gets 
    308   ! the root density as a function of depth 
    309   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: humcste 
    310  
    311  
    312   !------------------ 
    313   ! Albedo - sechiba 
    314   !------------------ 
    315   !- 
    316   ! Initial snow albedo value for each vegetation type 
    317   ! as it will be used in condveg_snow 
    318   ! Values are from the Thesis of S. Chalita (1992) 
    319   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_ini 
    320   ! 
    321   ! Decay rate of snow albedo value for each vegetation type 
    322   ! as it will be used in condveg_snow 
    323   ! Values are from the Thesis of S. Chalita (1992) 
    324   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_dec 
    325   ! 
    326   ! leaf albedo of vegetation type, visible albedo 
    327   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_vis 
    328   ! leaf albedo of vegetation type, near infrared albedo 
    329   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_nir 
    330   ! leaf albedo of vegetation type, VIS+NIR 
    331   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf 
    332  
    333  
    334   ! 
    335   !------------------------ 
    336   !   Soil - vegetation 
    337   !------------------------ 
    338  
    339   ! Table which contains the correlation between the soil types 
    340   ! and vegetation type. Two modes exist : 
    341   !  1) pref_soil_veg = 0 then we have an equidistribution 
    342   !     of vegetation on soil types 
    343   !  2) Else for each pft the prefered soil type is given : 
    344   !     1=sand, 2=loan, 3=clay 
    345   ! The variable is initialized in slowproc. 
    346   INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: pref_soil_veg 
    347   INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_sand 
    348   INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_loan 
    349   INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_clay 
    350  
    351  
    352   ! 
    353362  !-------------------------------------------- 
    354363  ! Internal parameters used in stomate_data 
     
    370379 
    371380 
    372   !------------------------------- 
    373   ! Parameters already externalised (from sechiba) 
    374   ! to classify 
    375   !---------------------------------- 
    376   ! 
    377   ! used in hydrolc and hydrol 
    378   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: throughfall_by_pft 
    379   ! used in diffuco   !! Nathalie le 28 mars 2006 - sur proposition de Fred Hourdin, ajout 
    380   !! d'un potentiometre pour regler la resistance de la vegetation 
    381   REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      ::  rveg_pft 
    382  
    383381 
    384382CONTAINS 
     
    397395   IF(l_first_define_pft) THEN 
    398396 
     397      ! 1. First time step 
    399398      IF(long_print) THEN 
    400399         WRITE(numout,*) 'l_first_define_pft :we read the parameters from the def files' 
    401400      ENDIF 
    402401 
     402      ! 2. Memory allocation 
    403403      ! Allocation of memory for the pfts-parameters 
    404404      CALL pft_parameters_alloc 
    405405 
     406      ! 3. Correspondance table  
     407       
     408      ! 3.1 Initialisation of the correspondance table 
    406409      ! Initialisation of the correspondance table 
    407410      pft_to_mtc (:) = undef_integer 
    408411       
    409       ! Reading of the conrrespondance table in the .def file 
    410       CALL getin('PFT_TO_MTC',pft_to_mtc) 
    411  
    412       ! Add the standard configuration 
     412      ! 3.2 Reading of the conrrespondance table in the .def file 
     413      CALL getin_p('PFT_TO_MTC',pft_to_mtc) 
     414 
     415      ! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array 
     416      !     If the configuration is wrong, send a error message to the user. 
    413417      IF(nvm .EQ. 13 ) THEN 
    414418         IF(pft_to_mtc(1) .EQ. undef_integer) THEN 
     
    422426      ENDIF 
    423427 
    424      ! What happened if pft_to_mtc(j) > nvmc (if the mtc doesn't exist)? 
     428      ! 3.4 Some error messages 
     429 
     430      ! 3.4.1 What happened if pft_to_mtc(j) > nvmc (if the mtc doesn't exist)? 
    425431       DO i = 1, nvm 
    426432          IF(pft_to_mtc(i) .GT. nvmc) THEN 
     
    431437 
    432438 
    433       ! Verify if pft_to_mtc(1) = 1  
     439      ! 3.4.2 Check if pft_to_mtc(1) = 1  
    434440       IF(pft_to_mtc(1) .NE. 1) THEN 
    435441          WRITE(numout,*) 'the first pft has to be the bare soil' 
     
    445451       
    446452    
    447       ! Initialisation of the pfts-parameters 
     453      ! 4.Initialisation of the pfts-parameters 
    448454      CALL pft_parameters_init 
    449455 
    450       ! Could be useful : correspondance between the number of the pft 
     456      ! 5. A useful message to the user: correspondance between the number of the pft 
    451457      ! and the name of the associated mtc  
    452458      DO i = 1,nvm 
     
    454460      ENDDO 
    455461 
    456  
    457       !------------------------------------------------------! 
    458       ! Initialisation of tables 2D  which are used in the code ! 
    459       !------------------------------------------------------! 
    460       ! 
     462      ! 6. Initialisation of 2D arrays used in the code 
     463 
     464      !-alb_leaf 
     465      alb_leaf(:) = zero 
     466 
     467      !- pref_soil_veg  
     468      pref_soil_veg(:,:) = zero_int 
     469 
    461470      !- pheno_gdd_crit 
    462471      pheno_gdd_crit(:,:) = zero  
     
    470479      !-coeff_maint_zero 
    471480      coeff_maint_zero(:,:) = zero 
    472       ! 
    473       !-alb_leaf 
    474       alb_leaf(:) = zero 
    475       !- pref_soil_veg (see slowproc) 
     481 
     482      ! 7. End message 
     483      IF(long_print) THEN 
     484         WRITE(numout,*) 'pft_parameters_done' 
     485      ENDIF 
    476486 
    477487   ELSE  
    478488 
    479        l_first_define_pft = .FALSE. 
     489      l_first_define_pft = .FALSE. 
    480490        
    481        RETURN 
     491      RETURN 
    482492 
    483493   ENDIF 
     
    496506   !------------ 
    497507 
    498    ! Initialisation !! not all the parameters are initialized  
    499  
    500    !---------------------- 
     508   ! 
     509   ! 1. Initialisation !! not all the parameters are initialized  
     510   ! 
     511 
     512   !- 
    501513   ! Vegetation structure  
    502    !---------------------- 
    503    !- 
     514   !- 
     515   ! 
    504516   ! 1 .Sechiba 
    505    !- 
     517   ! 
    506518   veget_ori_fixed_test_1(:) = zero 
    507519   llaimax(:) = zero 
    508520   llaimin(:) = zero 
    509521   height_presc(:) = zero 
    510    !- 
     522   rveg_pft(:) = zero 
     523   ! 
    511524   ! 2 .Stomate 
    512525   ! 
    513526   leaf_tab(:) = zero_int 
    514527   sla(:) = zero    
    515    !---------------- 
     528   !- 
     529   ! Evapotranspiration -  sechiba 
     530   !- 
     531   rstruct_const(:) = zero 
     532   kzero(:) = zero 
     533   !- 
     534   ! Water - sechiba 
     535   !- 
     536   wmax_veg(:) = zero 
     537   humcste(:) = zero 
     538   throughfall_by_pft(:) = zero 
     539   !- 
     540   ! Albedo - sechiba 
     541   !- 
     542   snowa_ini(:) = zero 
     543   snowa_dec(:) = zero 
     544   alb_leaf_vis(:) = zero 
     545   alb_leaf_nir(:) = zero 
     546   !- 
     547   ! Soil - vegetation 
     548   !- 
     549   pref_soil_veg_sand(:) = zero_int 
     550   pref_soil_veg_loan(:) = zero_int 
     551   pref_soil_veg_clay(:) = zero_int 
     552   !- 
    516553   ! Photosynthesis 
    517    !---------------- 
    518    !- 
     554   !- 
     555   ! 
    519556   ! 1 .CO2 
    520    !- 
     557   ! 
    521558   gsslope(:) = zero 
    522559   gsoffset(:) = zero 
     
    526563   co2_topt_fix(:) = zero 
    527564   co2_tmax_fix(:) = zero 
    528    !- 
     565   ext_coeff(:) = zero 
     566   ! 
    529567   ! 2 .Stomate 
    530    !- 
    531    ext_coeff(:) = zero 
     568   ! 
    532569   vcmax_opt(:) = zero 
    533570   vjmax_opt(:) = zero 
     
    541578   tphoto_max_b(:) = zero 
    542579   tphoto_max_c(:) = zero 
    543    !---------------------- 
     580   !- 
    544581   ! Respiration - stomate 
    545    !---------------------- 
    546    ! 
     582   !- 
    547583   maint_resp_slope_c(:) = zero 
    548584   maint_resp_slope_b(:) = zero 
     
    556592   cm_zero_fruit(:) = zero 
    557593   cm_zero_carbres(:) = zero 
    558    !---------------- 
     594   !- 
    559595   ! Fire - stomate 
    560    !--------------- 
     596   !- 
    561597   !  
    562598   flam(:) = zero 
    563599   resist(:) = zero 
    564    !---------------- 
     600   !- 
    565601   ! Flux - LUC 
    566    !--------------- 
    567    ! 
     602   !- 
    568603   coeff_lcchange_1(:) = zero 
    569604   coeff_lcchange_10(:) = zero 
    570605   coeff_lcchange_100(:) = zero 
    571    ! 
    572    !----------- 
     606   !- 
    573607   ! Phenology 
    574    !----------- 
    575    !- 
     608   !- 
     609   ! 
    576610   ! 1 .Stomate 
    577    !- 
     611   ! 
    578612   lai_max(:) = zero 
    579613   pheno_type(:) = zero_int 
    580    !- 
     614   ! 
    581615   ! 2. Leaf Onset 
    582    !- 
     616   ! 
    583617   pheno_gdd_crit_c(:) = zero 
    584618   pheno_gdd_crit_b(:) = zero 
     
    595629   alloc_max(:) = zero 
    596630   demi_alloc(:) = zero   
    597    !- 
     631  !>> DS new for merge in the trunk 15/06/2011 
     632   leaflife_tab(:) = zero 
     633   ! 
    598634   ! 3. Senescence 
    599    !- 
     635   ! 
    600636   leaffall(:) = zero 
    601637   leafagecrit(:) = zero 
     
    608644   senescence_temp_b(:) = zero  
    609645   senescence_temp_a(:) = zero  
    610    !----------- 
     646   !- 
    611647   ! DGVM 
    612    !----------- 
    613    ! 
     648   !- 
    614649   residence_time(:) = zero 
    615650   tmin_crit(:) = zero 
    616651   tcm_crit(:) = zero 
    617    !------------------------------- 
    618    ! Evapotranspiration -  sechiba 
    619    !------------------------------- 
    620    !- 
    621    rstruct_const(:) = zero 
    622    kzero(:) = zero 
    623    !------------------- 
    624    ! Water - sechiba 
    625    !------------------- 
    626    !- 
    627    wmax_veg(:) = zero 
    628    humcste(:) = zero 
    629    !------------------ 
    630    ! Albedo - sechiba 
    631    !------------------ 
    632    !- 
    633    snowa_ini(:) = zero 
    634    snowa_dec(:) = zero 
    635    alb_leaf_vis(:) = zero 
    636    alb_leaf_nir(:) = zero 
    637    !------------------------ 
    638    !   Soil - vegetation 
    639    !------------------------ 
    640    pref_soil_veg(:,:) = zero_int 
    641  
    642    !------------------------ 
     652   !- 
    643653   !  Internal_parameters 
    644    !------------------------ 
     654   !- 
    645655   lai_initmin(:) = zero 
    646656   bm_sapl(:,:) = zero 
     
    649659   cn_sapl(:) = zero 
    650660   leaf_timecst(:) = zero   
    651    !------------------------------- 
    652    ! Parameters already externalised (from sechiba) 
    653    ! to classify 
    654    !---------------------------------- 
    655    throughfall_by_pft(:) = zero 
    656    rveg_pft(:) = zero 
    657  
    658  
    659    !-------------------------------------------------------------! 
    660    ! Correspondance between the PFTs values and thes MTCs values ! 
    661    !-------------------------------------------------------------!   
     661 
     662 
     663   ! 
     664   ! 2. Correspondance between the PFTs values and thes MTCs values  
     665   ! 
    662666  
    663667   DO j= 1, nvm 
     
    666670      PFT_name(j) = MTC_name(pft_to_mtc(j)) 
    667671 
    668       !---------------------- 
     672      !- 
    669673      ! Vegetation structure  
    670       !---------------------- 
    671       !- 
     674      !- 
     675      ! 
    672676      ! 1 .Sechiba 
    673       !- 
     677      ! 
    674678      veget_ori_fixed_test_1(j) = veget_ori_fixed_mtc(pft_to_mtc(j)) 
    675679      llaimax(j) = llaimax_mtc(pft_to_mtc(j)) 
     
    678682      type_of_lai(j) = type_of_lai_mtc(pft_to_mtc(j)) 
    679683      is_tree(j) = is_tree_mtc(pft_to_mtc(j)) 
    680       !- 
     684      rveg_pft(j) = rveg_mtc(pft_to_mtc(j)) 
     685 
     686      !>> DS new for merge in the trunk   ! 15/06/2011  
     687      ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' 
     688      is_deciduous(j) = is_deciduous_mtc(pft_to_mtc(j)) 
     689      is_evergreen(j) = is_evergreen_mtc(pft_to_mtc(j)) 
     690      is_c3(j) = is_c3(pft_to_mtc(j)) 
     691 
     692      ! 
    681693      ! 2 .Stomate 
    682       !-  
     694      ! 
    683695      leaf_tab(j) = leaf_tab_mtc(pft_to_mtc(j)) 
    684696      sla(j) = sla_mtc(pft_to_mtc(j)) 
    685697      natural(j) = natural_mtc(pft_to_mtc(j)) 
    686       !---------------- 
     698 
     699      !- 
     700      ! Evapotranspiration -  sechiba 
     701      !- 
     702      rstruct_const(j) = rstruct_const_mtc(pft_to_mtc(j)) 
     703      kzero(j) = kzero_mtc(pft_to_mtc(j)) 
     704      !- 
     705      ! Water - sechiba 
     706      !- 
     707      wmax_veg(j) = wmax_veg_mtc(pft_to_mtc(j)) 
     708      humcste(j) = humcste_mtc(pft_to_mtc(j)) 
     709      throughfall_by_pft(j) = throughfall_by_mtc(pft_to_mtc(j)) 
     710      !- 
     711      ! Albedo - sechiba 
     712      !- 
     713      snowa_ini(j) = snowa_ini_mtc(pft_to_mtc(j)) 
     714      snowa_dec(j) = snowa_dec_mtc(pft_to_mtc(j))  
     715      alb_leaf_vis(j) = alb_leaf_vis_mtc(pft_to_mtc(j))   
     716      alb_leaf_nir(j) = alb_leaf_nir_mtc(pft_to_mtc(j)) 
     717      !- 
     718      !   Soil - vegetation 
     719      !- 
     720      pref_soil_veg_sand(j) = pref_soil_veg_sand_mtc(pft_to_mtc(j)) 
     721      pref_soil_veg_loan(j) = pref_soil_veg_loan_mtc(pft_to_mtc(j)) 
     722      pref_soil_veg_clay(j) = pref_soil_veg_clay_mtc(pft_to_mtc(j)) 
     723 
     724      !- 
    687725      ! Photosynthesis 
    688       !---------------- 
    689       !- 
     726      !- 
     727      ! 
    690728      ! 1 .CO2 
    691       !- 
     729      ! 
    692730      is_c4(j) = is_c4_mtc(pft_to_mtc(j)) 
    693731      gsslope(j) = gsslope_mtc(pft_to_mtc(j)) 
     
    698736      co2_topt_fix(j) = co2_topt_fix_mtc(pft_to_mtc(j)) 
    699737      co2_tmax_fix(j) = co2_tmax_fix_mtc(pft_to_mtc(j)) 
    700       !- 
     738      ! 
    701739      ! 2 .Stomate 
    702       !- 
     740      ! 
    703741      ext_coeff(j) = ext_coeff_mtc(pft_to_mtc(j)) 
    704742      vcmax_opt(j) = vcmax_opt_mtc(pft_to_mtc(j)) 
     
    713751      tphoto_max_b(j) = tphoto_max_b_mtc(pft_to_mtc(j)) 
    714752      tphoto_max_c(j) = tphoto_max_c_mtc(pft_to_mtc(j)) 
    715       !---------------------- 
     753      !- 
    716754      ! Respiration - stomate 
    717       !---------------------- 
     755      !- 
    718756      maint_resp_slope_c(j) = maint_resp_slope_c_mtc(pft_to_mtc(j))                
    719757      maint_resp_slope_b(j) = maint_resp_slope_b_mtc(pft_to_mtc(j)) 
     
    727765      cm_zero_fruit(j) = cm_zero_fruit_mtc(pft_to_mtc(j)) 
    728766      cm_zero_carbres(j) = cm_zero_carbres_mtc(pft_to_mtc(j)) 
    729       !---------------- 
     767      !- 
    730768      ! Fire - stomate 
    731       !--------------- 
     769      !- 
    732770      flam(j) = flam_mtc(pft_to_mtc(j)) 
    733771      resist(j) = resist_mtc(pft_to_mtc(j)) 
    734       !---------------- 
     772      !- 
    735773      ! Flux - LUC 
    736       !--------------- 
     774      !- 
    737775      coeff_lcchange_1(j) = coeff_lcchange_1_mtc(pft_to_mtc(j)) 
    738776      coeff_lcchange_10(j) = coeff_lcchange_10_mtc(pft_to_mtc(j)) 
    739777      coeff_lcchange_100(j) = coeff_lcchange_100_mtc(pft_to_mtc(j)) 
    740       !----------- 
     778      !- 
    741779      ! Phenology 
    742       !----------- 
    743       !- 
     780      !- 
     781      ! 
    744782      ! 1 .Stomate 
    745       !- 
     783      ! 
    746784      lai_max(j) = lai_max_mtc(pft_to_mtc(j)) 
    747785      pheno_model(j) = pheno_model_mtc(pft_to_mtc(j)) 
    748786      pheno_type(j) = pheno_type_mtc(pft_to_mtc(j)) 
    749       !- 
     787      ! 
    750788      ! 2. Leaf Onset 
    751       !- 
     789      ! 
    752790      pheno_gdd_crit_c(j) = pheno_gdd_crit_c_mtc(pft_to_mtc(j)) 
    753791      pheno_gdd_crit_b(j) = pheno_gdd_crit_b_mtc(pft_to_mtc(j))          
     
    764802      alloc_max(j) = alloc_max_mtc(pft_to_mtc(j)) 
    765803      demi_alloc(j) = demi_alloc_mtc(pft_to_mtc(j)) 
    766       !- 
     804  !>> DS new for merge in the trunk   ! 15/06/2011  
     805      leaflife_tab(j) = leaflife_mtc(pft_to_mtc(j)) 
     806      ! 
    767807      ! 3. Senescence 
    768       !- 
     808      ! 
    769809      leaffall(j) = leaffall_mtc(pft_to_mtc(j)) 
    770810      leafagecrit(j) = leafagecrit_mtc(pft_to_mtc(j)) 
     
    778818      senescence_temp_b(j) = senescence_temp_b_mtc(pft_to_mtc(j)) 
    779819      senescence_temp_a(j) = senescence_temp_a_mtc(pft_to_mtc(j)) 
    780       !----------- 
     820      !- 
    781821      ! DGVM 
    782       !----------- 
    783822      residence_time(j) = residence_time_mtc(pft_to_mtc(j)) 
    784823      tmin_crit(j) = tmin_crit_mtc(pft_to_mtc(j)) 
    785824      tcm_crit(j) =  tcm_crit_mtc(pft_to_mtc(j)) 
    786825       
    787       !------------------------------- 
    788       ! Evapotranspiration -  sechiba 
    789       !------------------------------- 
    790       !- 
    791       rstruct_const(j) = rstruct_const_mtc(pft_to_mtc(j)) 
    792       kzero(j) = kzero_mtc(pft_to_mtc(j)) 
    793       !------------------- 
    794       ! Water - sechiba 
    795       !------------------- 
    796       !- 
    797       wmax_veg(j) = wmax_veg_mtc(pft_to_mtc(j)) 
    798       humcste(j) = humcste_mtc(pft_to_mtc(j)) 
    799       !------------------ 
    800       ! Albedo - sechiba 
    801       !------------------ 
    802       !- 
    803       snowa_ini(j) = snowa_ini_mtc(pft_to_mtc(j)) 
    804       snowa_dec(j) = snowa_dec_mtc(pft_to_mtc(j))  
    805       alb_leaf_vis(j) = alb_leaf_vis_mtc(pft_to_mtc(j))   
    806       alb_leaf_nir(j) = alb_leaf_nir_mtc(pft_to_mtc(j)) 
    807       !------------------------ 
    808       !   Soil - vegetation 
    809       !------------------------ 
    810       pref_soil_veg_sand(j) = pref_soil_veg_sand_mtc(pft_to_mtc(j)) 
    811       pref_soil_veg_loan(j) = pref_soil_veg_loan_mtc(pft_to_mtc(j)) 
    812       pref_soil_veg_clay(j) = pref_soil_veg_clay_mtc(pft_to_mtc(j)) 
    813       !------------------------------- 
    814       ! Parameters already externalised (from sechiba) 
    815       ! to classify 
    816       !----------------------------------  
    817       throughfall_by_pft(j) = throughfall_by_mtc(pft_to_mtc(j)) 
    818       rveg_pft(j) = rveg_mtc(pft_to_mtc(j)) 
    819  
    820   ! end loop over nvm     
    821    ENDDO 
     826   ENDDO ! end loop over nvm  
    822827 
    823828 END SUBROUTINE pft_parameters_init 
     
    840845   l_error = l_error .OR. (ier .NE. 0) 
    841846   !- 
     847   !>> DS new for merge in the trunk   ! 15/06/2011  
     848   ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' 
     849   ALLOCATE(is_deciduous(nvm),stat=ier)    
     850   l_error = l_error .OR. (ier .NE. 0) 
     851   ALLOCATE(is_evergreen(nvm),stat=ier)   
     852   l_error = l_error .OR. (ier .NE. 0) 
     853   ALLOCATE(is_c3(nvm),stat=ier)   
     854   l_error = l_error .OR. (ier .NE. 0) 
     855   ALLOCATE(leaflife_tab(nvm),stat=ier)    
     856   l_error = l_error .OR. (ier .NE. 0) 
     857   ! >> END 
     858 
    842859   ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier) 
    843860   l_error = l_error .OR. (ier .NE. 0) 
     
    10661083 
    10671084 END SUBROUTINE pft_parameters_alloc 
     1085! 
     1086!= 
     1087! 
     1088 SUBROUTINE getin_sechiba_pft_parameters 
     1089 
     1090   IMPLICIT NONE 
     1091   
     1092   LOGICAL, SAVE ::  first_call = .TRUE. 
     1093 
     1094  IF(first_call) THEN 
     1095 
     1096     ! No calling to getin for veget_ori_fixed_test_1, llaimax and height_presc 
     1097     ! use of setvar in slowproc.f90 
     1098 
     1099     !- 
     1100     ! Vegetation structure 
     1101     !- 
     1102     CALL getin_p('LLAIMIN',llaimin) 
     1103     CALL getin('TYPE_OF_LAI',type_of_lai) 
     1104     CALL getin_p('IS_TREE',is_tree) 
     1105     CALL getin_p('NATURAL',natural) 
     1106 
     1107     !>> DS new for merge in the trunk   ! 15/06/2011  
     1108     ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' 
     1109     CALL getin('IS_DECIDUOUS',is_deciduous) 
     1110     CALL getin('IS_EVERGREEN',is_evergreen)   
     1111     CALL getin_p('IS_C3',is_c3)    
     1112 
     1113     !- 
     1114     ! Photosynthesis 
     1115     !- 
     1116     CALL getin_p('IS_C4',is_c4) 
     1117     CALL getin_p('GSSLOPE',gsslope) 
     1118     CALL getin_p('GSOFFSET',gsoffset) 
     1119     CALL getin_p('VCMAX_FIX',vcmax_fix) 
     1120     CALL getin_p('VJMAX_FIX',vjmax_fix) 
     1121     CALL getin_p('CO2_TMIN_FIX',co2_tmin_fix) 
     1122     CALL getin_p('CO2_TOPT_FIX',co2_topt_fix) 
     1123     CALL getin_p('CO2_TMAX_FIX',co2_tmax_fix) 
     1124     CALL getin_p('EXT_COEFF',ext_coeff) 
     1125     !- 
     1126     ! Evapotranspiration -  sechiba 
     1127     !- 
     1128     CALL getin_p('RSTRUCT_CONST',rstruct_const) 
     1129     CALL getin_p('KZERO',kzero) 
     1130     CALL getin_p('RVEG_PFT', rveg_pft)     
     1131     !- 
     1132     ! Water-hydrology - sechiba 
     1133     !- 
     1134     CALL getin_p('WMAX_VEG',wmax_veg) 
     1135     CALL getin_p('HYDROL_HUMCSTE', humcste) 
     1136     CALL getin_p('PERCENT_TROUGHFALL_PFT',throughfall_by_pft) 
     1137     !- 
     1138     ! Albedo - sechiba 
     1139     !- 
     1140     CALL getin_p('SNOWA_INI',snowa_ini) 
     1141     CALL getin_p('SNOWA_DEC',snowa_dec) 
     1142     CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis) 
     1143     CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir) 
     1144     !- 
     1145     ! Soil - vegetation 
     1146     !- 
     1147     CALL getin_p('PREF_SOIL_VEG_SAND',pref_soil_veg_sand) 
     1148     CALL getin_p('PREF_SOIL_VEG_LOAN',pref_soil_veg_loan)          
     1149     CALL getin_p('PREF_SOIL_VEG_CLAY',pref_soil_veg_clay) 
     1150 
     1151     first_call = .FALSE. 
     1152 
     1153  ENDIF 
     1154 
     1155END SUBROUTINE getin_sechiba_pft_parameters 
     1156! 
     1157!= 
     1158! 
     1159SUBROUTINE getin_stomate_pft_parameters 
     1160 
     1161  IMPLICIT NONE 
     1162 
     1163  LOGICAL, SAVE ::  first_call = .TRUE. 
     1164 
     1165  IF(first_call) THEN 
     1166 
     1167      !- 
     1168      ! Vegetation structure 
     1169      !- 
     1170      CALL getin_p('LEAF_TAB',leaf_tab) 
     1171      CALL getin_p('SLA',sla) 
     1172      !- 
     1173      ! Photosynthesis 
     1174      !- 
     1175      CALL getin_p('VCMAX_OPT',vcmax_opt) 
     1176      CALL getin_p('VJMAX_OPT',vjmax_opt) 
     1177      CALL getin_p('TPHOTO_MIN_A',tphoto_min_a) 
     1178      CALL getin_p('TPHOTO_MIN_B',tphoto_min_b) 
     1179      CALL getin_p('TPHOTO_MIN_C',tphoto_min_c) 
     1180      CALL getin_p('TPHOTO_OPT_A',tphoto_opt_a) 
     1181      CALL getin_p('TPHOTO_OPT_B',tphoto_opt_b) 
     1182      CALL getin_p('TPHOTO_OPT_C',tphoto_opt_c) 
     1183      CALL getin_p('TPHOTO_MAX_A',tphoto_max_a) 
     1184      CALL getin_p('TPHOTO_MAX_B',tphoto_max_b) 
     1185      CALL getin_p('TPHOTO_MAX_C',tphoto_max_c) 
     1186      !- 
     1187      ! Respiration - stomate 
     1188      !- 
     1189      CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c)  
     1190      CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b) 
     1191      CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a) 
     1192      CALL getin_p('CM_ZERO_LEAF',cm_zero_leaf) 
     1193      CALL getin_p('CM_ZERO_SAPABOVE',cm_zero_sapabove) 
     1194      CALL getin_p('CM_ZERO_SAPBELOW',cm_zero_sapbelow) 
     1195      CALL getin_p('CM_ZERO_HEARTABOVE',cm_zero_heartabove) 
     1196      CALL getin_p('CM_ZERO_HEARTBELOW',cm_zero_heartbelow) 
     1197      CALL getin_p('CM_ZERO_ROOT',cm_zero_root) 
     1198      CALL getin_p('CM_ZERO_FRUIT',cm_zero_fruit) 
     1199      CALL getin_p('CM_ZERO_CARBRES',cm_zero_carbres) 
     1200      !- 
     1201      ! Fire - stomate 
     1202      !- 
     1203      CALL getin_p('FLAM',flam) 
     1204      CALL getin_p('RESIST',resist) 
     1205      !- 
     1206      ! Flux - LUC 
     1207      !- 
     1208      CALL getin_p('COEFF_LCCHANGE_1',coeff_lcchange_1) 
     1209      CALL getin_p('COEFF_LCCHANGE_10',coeff_lcchange_10) 
     1210      CALL getin_p('COEFF_LCCHANGE_100',coeff_lcchange_100) 
     1211      !- 
     1212      ! Phenology 
     1213      !- 
     1214      CALL getin_p('LAI_MAX',lai_max) 
     1215      CALL getin('PHENO_MODEL',pheno_model) 
     1216      CALL getin_p('PHENO_TYPE',pheno_type) 
     1217      !- 
     1218      ! Phenology : Leaf Onset 
     1219      !- 
     1220      CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c) 
     1221      CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b) 
     1222      CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a) 
     1223      CALL getin_p('NGD_CRIT',ngd_crit) 
     1224      CALL getin_p('NCDGDD_TEMP', ncdgdd_temp) 
     1225      CALL getin_p('HUM_FRAC', hum_frac) 
     1226      CALL getin_p('LOWGPP_TIME', lowgpp_time) 
     1227      CALL getin_p('HUM_MIN_TIME', hum_min_time) 
     1228      CALL getin_p('TAU_SAP',tau_sap) 
     1229      CALL getin_p('TAU_FRUIT',tau_fruit) 
     1230      CALL getin_p('ECUREUIL',ecureuil) 
     1231      CALL getin_p('ALLOC_MIN',alloc_min) 
     1232      CALL getin_p('ALLOC_MAX',alloc_max) 
     1233      CALL getin_p('DEMI_ALLOC',demi_alloc) 
     1234 
     1235      !>> DS new for merge in the trunk 
     1236      ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla 
     1237      CALL getin_p('LEAFLIFE_TAB',leaflife_tab) 
     1238 
     1239      !- 
     1240      ! Phenology : Senescence 
     1241      !- 
     1242      CALL getin_p('LEAFFALL',leaffall) 
     1243      CALL getin_p('LEAFAGECRIT',leafagecrit)   
     1244      CALL getin('SENESCENCE_TYPE', senescence_type)  
     1245      CALL getin_p('SENESCENCE_HUM', senescence_hum) 
     1246      CALL getin_p('NOSENESCENCE_HUM', nosenescence_hum)  
     1247      CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time) 
     1248      CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time) 
     1249      CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE', min_leaf_age_for_senescence) 
     1250      CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c) 
     1251      CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b) 
     1252      CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a) 
     1253      !- 
     1254      ! DGVM 
     1255      !- 
     1256      CALL getin_p('RESIDENCE_TIME',residence_time) 
     1257      CALL getin_p('TMIN_CRIT',tmin_crit) 
     1258      CALL getin_p('TCM_CRIT',tcm_crit) 
     1259       
     1260     first_call = .FALSE. 
     1261        
     1262  ENDIF 
     1263   
     1264END SUBROUTINE getin_stomate_pft_parameters 
    10681265 ! 
    10691266 != 
    10701267 ! 
    10711268 SUBROUTINE pft_parameters_clear 
    1072  
     1269    
    10731270   l_first_define_pft = .TRUE. 
    1074  
     1271    
    10751272   IF(ALLOCATED(pft_to_mtc))DEALLOCATE(pft_to_mtc) 
    10761273   IF(ALLOCATED(PFT_name))DEALLOCATE(PFT_name) 
     1274   !- 
     1275   !>> DS new for merge in the trunk   ! 15/06/2011  
     1276   ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' 
     1277   IF(ALLOCATED(is_deciduous))DEALLOCATE(is_deciduous) 
     1278   IF(ALLOCATED(is_evergreen))DEALLOCATE(is_evergreen) 
     1279   IF(ALLOCATED(leaflife_tab))DEALLOCATE(leaflife_tab) 
     1280   IF(ALLOCATED(is_c3))DEALLOCATE(is_c3)   
    10771281   !- 
    10781282   IF(ALLOCATED(veget_ori_fixed_test_1))DEALLOCATE(veget_ori_fixed_test_1)    
     
    11941398   !- 
    11951399   IF(ALLOCATED(throughfall_by_pft))DEALLOCATE(throughfall_by_pft) 
    1196    IF (ALLOCATED(rveg_pft))DEALLOCATE(rveg_pft) 
    1197  
     1400   IF(ALLOCATED(rveg_pft))DEALLOCATE(rveg_pft) 
     1401    
    11981402 END SUBROUTINE pft_parameters_clear 
    1199 ! 
    1200 != 
    1201 ! 
    1202  SUBROUTINE getin_sechiba_pft_parameters 
    1203  
    1204    IMPLICIT NONE 
    1205    
    1206    LOGICAL, SAVE ::  first_call = .TRUE. 
    1207  
    1208   IF(first_call) THEN 
    1209  
    1210      !---------------------- 
    1211      ! Vegetation structure 
    1212      !--------------------- 
    1213      !       
    1214      CALL getin('LLAIMIN',llaimin) 
    1215      CALL getin('TYPE_OF_LAI',type_of_lai) 
    1216      CALL getin('IS_TREE',is_tree) 
    1217      ! No calling to getin for 
    1218      ! veget_ori_fixed_test_1, llaimax and height_presc 
    1219      ! use of setvar in slowproc.f90 
    1220       
    1221      !----------------- 
    1222      ! Photosynthesis 
    1223      !----------------- 
    1224      !- 
    1225      CALL getin('IS_C4',is_c4) 
    1226      CALL getin('GSSLOPE',gsslope) 
    1227      CALL getin('GSOFFSET',gsoffset) 
    1228      CALL getin('VCMAX_FIX',vcmax_fix) 
    1229      CALL getin('VJMAX_FIX',vjmax_fix) 
    1230      CALL getin('CO2_TMIN_FIX',co2_tmin_fix) 
    1231      CALL getin('CO2_TOPT_FIX',co2_topt_fix) 
    1232      CALL getin('CO2_TMAX_FIX',co2_tmax_fix) 
    1233      CALL getin('EXT_COEFF',ext_coeff) 
    1234      !------------------------------- 
    1235      ! Evapotranspiration -  sechiba 
    1236      !------------------------------- 
    1237      ! 
    1238      CALL getin('RSTRUCT_CONST',rstruct_const) 
    1239      CALL getin('KZERO',kzero) 
    1240      CALL getin('RVEG_PFT', rveg_pft)     
    1241      !--------------------------- 
    1242      ! Water-hydrology - sechiba 
    1243      !--------------------------- 
    1244      ! 
    1245      CALL getin('WMAX_VEG',wmax_veg) 
    1246      CALL getin('HYDROL_HUMCSTE', humcste) 
    1247      CALL getin('PERCENT_TROUGHFALL_PFT',throughfall_by_pft) 
    1248      !------------------ 
    1249      ! Albedo - sechiba 
    1250      !------------------ 
    1251      ! 
    1252      CALL getin('SNOWA_INI',snowa_ini) 
    1253      CALL getin('SNOWA_DEC',snowa_dec) 
    1254      CALL getin('ALB_LEAF_VIS',alb_leaf_vis) 
    1255      CALL getin('ALB_LEAF_NIR',alb_leaf_nir) 
    1256  
    1257      !------------------------ 
    1258      !   Soil - vegetation 
    1259      !------------------------  
    1260      ! 
    1261      CALL getin('PREF_SOIL_VEG_SAND',pref_soil_veg_sand) 
    1262      CALL getin('PREF_SOIL_VEG_LOAN',pref_soil_veg_loan)          
    1263      CALL getin('PREF_SOIL_VEG_CLAY',pref_soil_veg_clay) 
    1264  
    1265      first_call = .FALSE. 
    1266  
    1267   ENDIF 
    1268  
    1269 END SUBROUTINE getin_sechiba_pft_parameters 
    1270 ! 
    1271 != 
    1272 ! 
    1273 SUBROUTINE getin_stomate_pft_parameters 
    1274  
    1275   IMPLICIT NONE 
    1276  
    1277   LOGICAL, SAVE ::  first_call = .TRUE. 
    1278  
    1279   IF(first_call) THEN 
    1280  
    1281      !---------------------- 
    1282      ! Vegetation structure 
    1283      !--------------------- 
    1284      ! 
    1285      CALL getin('LEAF_TAB',leaf_tab) 
    1286      CALL getin('SLA',sla) 
    1287      CALL getin('NATURAL',natural) 
    1288      !----------------- 
    1289      ! Photosynthesis 
    1290      !----------------- 
    1291      ! 
    1292      CALL getin('VCMAX_OPT',vcmax_opt) 
    1293      CALL getin('VJMAX_OPT',vjmax_opt) 
    1294      CALL getin('TPHOTO_MIN_A',tphoto_min_a) 
    1295      CALL getin('TPHOTO_MIN_B',tphoto_min_b) 
    1296      CALL getin('TPHOTO_MIN_C',tphoto_min_c) 
    1297      CALL getin('TPHOTO_OPT_A',tphoto_opt_a) 
    1298      CALL getin('TPHOTO_OPT_B',tphoto_opt_b) 
    1299      CALL getin('TPHOTO_OPT_C',tphoto_opt_c) 
    1300      CALL getin('TPHOTO_MAX_A',tphoto_max_a) 
    1301      CALL getin('TPHOTO_MAX_B',tphoto_max_b) 
    1302      CALL getin('TPHOTO_MAX_C',tphoto_max_c) 
    1303      !---------------------- 
    1304      ! Respiration - stomate 
    1305      !---------------------- 
    1306      ! 
    1307      CALL getin('MAINT_RESP_SLOPE_C',maint_resp_slope_c)  
    1308      CALL getin('MAINT_RESP_SLOPE_B',maint_resp_slope_b) 
    1309      CALL getin('MAINT_RESP_SLOPE_A',maint_resp_slope_a) 
    1310      CALL getin('CM_ZERO_LEAF',cm_zero_leaf) 
    1311      CALL getin('CM_ZERO_SAPABOVE',cm_zero_sapabove) 
    1312      CALL getin('CM_ZERO_SAPBELOW',cm_zero_sapbelow) 
    1313      CALL getin('CM_ZERO_HEARTABOVE',cm_zero_heartabove) 
    1314      CALL getin('CM_ZERO_HEARTBELOW',cm_zero_heartbelow) 
    1315      CALL getin('CM_ZERO_ROOT',cm_zero_root) 
    1316      CALL getin('CM_ZERO_FRUIT',cm_zero_fruit) 
    1317      CALL getin('CM_ZERO_CARBRES',cm_zero_carbres) 
    1318       
    1319      !---------------- 
    1320      ! Fire - stomate 
    1321      !--------------- 
    1322      ! 
    1323      CALL getin('FLAM',flam) 
    1324      CALL getin('RESIST',resist) 
    1325      !---------------- 
    1326      ! Flux - LUC 
    1327      !--------------- 
    1328      ! 
    1329      CALL getin('COEFF_LCCHANGE_1',coeff_lcchange_1) 
    1330      CALL getin('COEFF_LCCHANGE_10',coeff_lcchange_10) 
    1331      CALL getin('COEFF_LCCHANGE_100',coeff_lcchange_100) 
    1332  
    1333      !----------- 
    1334      ! Phenology 
    1335      !----------- 
    1336      !- 
    1337      ! 1 .Stomate 
    1338      !- 
    1339      CALL getin('LAI_MAX',lai_max) 
    1340      CALL getin('PHENO_MODEL',pheno_model) 
    1341      CALL getin('PHENO_TYPE',pheno_type) 
    1342      !- 
    1343      ! 2. Leaf Onset 
    1344      !- 
    1345      CALL getin('PHENO_GDD_CRIT_C',pheno_gdd_crit_c) 
    1346      CALL getin('PHENO_GDD_CRIT_B',pheno_gdd_crit_b) 
    1347      CALL getin('PHENO_GDD_CRIT_A',pheno_gdd_crit_a) 
    1348      CALL getin('NGD_CRIT',ngd_crit) 
    1349      CALL getin('NCDGDD_TEMP', ncdgdd_temp) 
    1350      CALL getin('HUM_FRAC', hum_frac) 
    1351      CALL getin('LOWGPP_TIME', lowgpp_time) 
    1352      CALL getin('HUM_MIN_TIME', hum_min_time) 
    1353      CALL getin('TAU_SAP',tau_sap) 
    1354      CALL getin('TAU_FRUIT',tau_fruit) 
    1355      CALL getin('ECUREUIL',ecureuil) 
    1356      CALL getin('ALLOC_MIN',alloc_min) 
    1357      CALL getin('ALLOC_MAX',alloc_max) 
    1358      CALL getin('DEMI_ALLOC',demi_alloc) 
    1359      !- 
    1360      ! 3. Senescence 
    1361      !- 
    1362      CALL getin('LEAFFALL',leaffall) 
    1363      CALL getin('LEAFAGECRIT',leafagecrit)   
    1364      CALL getin('SENESCENCE_TYPE', senescence_type)  
    1365      CALL getin('SENESCENCE_HUM', senescence_hum) 
    1366      CALL getin('NOSENESCENCE_HUM', nosenescence_hum)  
    1367      CALL getin('MAX_TURNOVER_TIME',max_turnover_time) 
    1368      CALL getin('MIN_TURNOVER_TIME',min_turnover_time) 
    1369      CALL getin('MIN_LEAF_AGE_FOR_SENESCENCE', min_leaf_age_for_senescence) 
    1370      CALL getin('SENESCENCE_TEMP_C',senescence_temp_c) 
    1371      CALL getin('SENESCENCE_TEMP_B',senescence_temp_b) 
    1372      CALL getin('SENESCENCE_TEMP_A',senescence_temp_a) 
    1373      !----------- 
    1374      ! DGVM 
    1375      !----------- 
    1376      CALL getin('RESIDENCE_TIME',residence_time) 
    1377      CALL getin('TMIN_CRIT',tmin_crit) 
    1378      CALL getin('TCM_CRIT',tcm_crit) 
    1379  
    1380      first_call = .FALSE. 
    1381         
    1382   ENDIF 
    1383    
    1384 END SUBROUTINE getin_stomate_pft_parameters 
    13851403 
    13861404END MODULE pft_parameters 
Note: See TracChangeset for help on using the changeset viewer.