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

    r251 r257  
    88!!-------------------------------------------------------------------- 
    99  USE defprec 
    10   USE ioipsl 
     10  USE parallel 
    1111!- 
    1212  IMPLICIT NONE 
     
    2121  !---------------- 
    2222 
    23   ! Unit for output messages 
    24   INTEGER(i_std), SAVE :: numout = 6 
    2523  !- 
    2624  ! To set for more printing 
     
    185183  INTEGER(i_std),PARAMETER :: ipassive = 3 
    186184  INTEGER(i_std),PARAMETER :: ncarb = 3 
     185  ! 
     186  ! transformation between types of surface (DS : not used in the code?) 
     187  INTEGER(i_std),PARAMETER :: ito_natagri = 1 
     188  INTEGER(i_std),PARAMETER :: ito_total = 2 
     189 
    187190 
    188191 
     
    197200  REAL(r_std), PARAMETER :: pi = 4.*ATAN(1.) 
    198201  ! e 
    199   REAL(r_std),PARAMETER :: euler = 2.71828182846 
     202  REAL(r_std),PARAMETER :: euler = 2.71828182846 !or euler = EXP(1.) 
    200203  !- 
    201204  ! Integer constant set to zero 
     
    230233  ! 
    231234  ! radius of the Earth (m) 
     235  ! comment : 
     236  ! Earth radius ~= Equatorial radius 
     237  ! The Earth's equatorial radius a, or semi-major axis, is the distance from its center to the equator and equals 6,378.1370 km. 
     238  ! The equatorial radius is often used to compare Earth with other planets. 
    232239  REAL(r_std), PARAMETER :: R_Earth = 6378000. 
     240  !The meridional mean is well approximated by the semicubic mean of the two axe yielding 6367.4491 km 
     241  ! or less accurately by the quadratic mean of the two axes about 6,367.454 km 
     242  ! or even just the mean of the two axes about 6,367.445 km. 
     243  !- 
    233244  ! standard pressure 
    234245  REAL(r_std), PARAMETER :: pb_std = 1013.  
     
    333344 
    334345 
    335 !----------------------------------------------- 
    336 !---------------------------------------------- 
    337 ! SCALAR PARAMETERS EXTERNALIZED 
    338 !---------------------------------------------- 
    339 !----------------------------------------------- 
    340 !------------------------------------------ 
    341 !  SECHIBA, SOIL AND VEGETATION parameters 
    342 !----------------------------------------- 
    343  
    344   !!--------------------------------------- 
    345   !! Parameters for soil type distribution 
    346   !!--------------------------------------- 
    347   ! 
    348   ! Default soil texture distribution in the following order : 
    349   !    sand, loam and clay 
    350   REAL(r_std),SAVE, DIMENSION(nstm) :: soiltype_default = (/ 0.0, 1.0, 0.0 /) 
    351  
    352   !!---------------------------------------- 
    353   !! Constantes from the Choisnel hydrology 
    354   !!---------------------------------------- 
     346 
     347                           !------------------------! 
     348                           !  SECHIBA PARAMETERS    ! 
     349                           !------------------------! 
     350 
     351! DS Maybe should I move these constants in the modules they belong 
     352!- 
     353! Specific parameters for the CWRR hydrology module 
     354!- 
     355! 
     356! CWRR linearisation 
     357INTEGER(i_std),PARAMETER :: imin = 1 
     358! number of interval for CWRR 
     359INTEGER(i_std),PARAMETER :: nbint = 100 
     360! number of points for CWRR 
     361INTEGER(i_std),PARAMETER :: imax = nbint+1 
     362 
     363!- 
     364! diffuco 
     365!- 
     366REAL(r_std),PARAMETER :: Tetens_1 = 0.622    
     367REAL(r_std),PARAMETER :: Tetens_2 = 0.378 
     368REAL(r_std),PARAMETER :: std_ci_frac = 0.667 
     369REAL(r_std),PARAMETER :: alpha_j = 0.8855 
     370REAL(r_std),PARAMETER :: curve_assim = 0.7 
     371REAL(r_std),PARAMETER :: WJ_coeff1 = 4.5 
     372REAL(r_std),PARAMETER :: WJ_coeff2 = 10.5 
     373REAL(r_std),PARAMETER :: Vc_to_Rd_ratio = 0.011 
     374REAL(r_std),PARAMETER :: O2toCO2_stoechio = 1.6 
     375REAL(r_std),PARAMETER :: mmol_to_m_1 = 0.0244 
     376REAL(r_std),PARAMETER  :: RG_to_PAR = 0.5  
     377REAL(r_std),PARAMETER  :: W_to_mmol = 4.6 ! W_to_mmol * RG_to_PAR = 2.3 
     378 
     379 
     380 
     381                               !-----------! 
     382                               ! Global    ! 
     383                               !-----------! 
     384  ! The minimum wind 
     385  REAL(r_std),SAVE :: min_wind = 0.1 
     386  ! Sets the amount above which only sublimation occures [Kg/m^2] 
     387  REAL(r_std),SAVE :: snowcri=1.5 
     388  ! Transforms leaf area index into size of interception reservoir 
     389  REAL(r_std),SAVE      :: qsintcst = 0.1 
     390  ! Total depth of soil reservoir (for hydrolc) 
     391  REAL(r_std),SAVE :: dpu_cste =  deux 
     392  ! Total depth of soil reservoir (m) 
     393  REAL(r_std),SAVE,DIMENSION(nstm) :: dpu =  (/ 2.0_r_std, 2.0_r_std, 2.0_r_std /) 
     394 
     395  ! FLAGS 
     396 
     397  ! allow agricultural PFTs 
     398  LOGICAL,SAVE :: agriculture = .TRUE. !(read in slowproc) 
     399  ! Do we treat PFT expansion across a grid point after introduction? 
     400  ! default = .FALSE. 
     401  LOGICAL,SAVE :: treat_expansion = .FALSE. 
     402  ! herbivores? 
     403  LOGICAL,SAVE :: ok_herbivores = .FALSE. 
     404  ! harvesting ? 
     405  LOGICAL,SAVE :: harvest_agri = .TRUE. 
     406  ! constant moratlity 
     407  LOGICAL,SAVE :: lpj_gap_const_mort=.TRUE. 
     408 
     409  ! Parameters used by both hydrology models 
     410 
     411  ! Maximum period of snow aging 
     412  REAL(r_std),SAVE :: max_snow_age = 50._r_std 
     413  ! Transformation time constant for snow (m) 
     414  REAL(r_std),SAVE :: snow_trans = 0.3_r_std 
     415  ! Lower limit of snow amount 
     416  REAL(r_std),SAVE :: sneige 
     417  ! The maximum mass (kg/m^2) of a glacier. 
     418  REAL(r_std),SAVE :: maxmass_glacier = 3000. 
     419  ! Maximum quantity of water (Kg/M3) 
     420  REAL(r_std),SAVE :: mx_eau_eau = 150. 
     421 
     422  ! UNKNOW 
     423 
     424  ! Is veget_ori array stored in restart file 
     425!!$! DS: Where is it used ? 
     426  !  LOGICAL,PARAMETER :: ldveget_ori_on_restart = .TRUE. 
     427  !- 
     428!!$! DS not used in the code ?  
     429  ! Limit of air temperature for snow 
     430  REAL(r_std),SAVE :: tsnow=273. 
     431 
     432 
     433 
     434 
     435                               !-------------! 
     436                               ! condveg.f90 ! 
     437                               !-------------! 
     438 
     439  ! 1. Scalar 
     440 
     441  ! to get z0 from height 
     442  REAL(r_std), SAVE  :: z0_over_height = un/16. 
     443  ! Magic number which relates the height to the displacement height. 
     444  REAL(r_std), SAVE  :: height_displacement = 0.75 
     445  ! bare soil roughness length (m) 
     446  REAL(r_std),SAVE :: z0_bare = 0.01 
     447  ! ice roughness length (m) 
     448  REAL(r_std),SAVE :: z0_ice = 0.001 
     449  ! Time constant of the albedo decay of snow 
     450  REAL(r_std),SAVE :: tcst_snowa = 5.0 
     451  ! Critical value for computation of snow albedo [Kg/m^2] 
     452  REAL(r_std),SAVE :: snowcri_alb=10. 
     453 
     454  ! 2. Arrays 
     455 
     456  ! albedo of dead leaves, VIS+NIR 
     457  REAL(r_std),DIMENSION(2),SAVE :: alb_deadleaf = (/ .12, .35/) 
     458  ! albedo of ice, VIS+NIR 
     459  REAL(r_std),DIMENSION(2),SAVE :: alb_ice = (/ .60, .20/) 
     460  !   The correspondance table for the soil color numbers and their albedo 
     461  ! 
     462  REAL(r_std), DIMENSION(classnb) :: vis_dry = (/0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/) 
     463  REAL(r_std), DIMENSION(classnb) :: nir_dry = (/0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)   
     464  REAL(r_std), DIMENSION(classnb) :: vis_wet = (/0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)   
     465  REAL(r_std), DIMENSION(classnb) :: nir_wet = (/0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/) 
     466  !    
     467  ! Nathalie, introduction d'un albedo moyen, VIS+NIR 
     468  ! Les valeurs suivantes correspondent a la moyenne des valeurs initiales 
     469  !  REAL(stnd), DIMENSION(classnb) :: albsoil_vis = (/0.18, 0.165, 0.15, 0.135, 0.12, 0.105, 0.09, 0.075, 0.21/) 
     470  !  REAL(stnd), DIMENSION(classnb) :: albsoil_nir = (/0.36, 0.33, 0.30, 0.27, 0.24, 0.21, 0.18, 0.15, 0.43/) 
     471  ! les valeurs retenues accentuent le contraste entre equateur et Sahara.  
     472  ! On diminue aussi l'albedo des deserts (tous sauf Sahara) 
     473  REAL(r_std), DIMENSION(classnb) :: albsoil_vis = (/0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25/) 
     474  REAL(r_std), DIMENSION(classnb) :: albsoil_nir = (/0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45/)  
     475 
     476 
     477                               !-------------! 
     478                               ! diffuco.f90 ! 
     479                               !-------------! 
     480 
     481  ! 1. Scalar 
     482 
     483  INTEGER(i_std), SAVE        :: nlai = 20 ! dimension de tableau 
     484  ! used in diffuco_trans 
     485  REAL(r_std), SAVE                :: laimax = 12. 
     486  REAL(r_std), SAVE                :: xc4_1 = .83 
     487  REAL(r_std), SAVE                :: xc4_2 = .93 
     488  ! Set to .TRUE. if you want q_cdrag coming from GCM 
     489  LOGICAL,SAVE :: ldq_cdrag_from_gcm = .FALSE. 
     490 
     491  ! 2; Arrays 
     492 
     493  ! 3. Coefficients of equations 
     494 
     495  REAL(r_std), SAVE      :: lai_level_depth = .15 
     496  REAL(r_std), SAVE      :: x1_coef =  0.177 
     497  REAL(r_std), SAVE      :: x1_Q10 =  0.069 
     498  REAL(r_std), SAVE      :: quantum_yield =  0.092 
     499  REAL(r_std), SAVE      :: kt_coef = 0.7      
     500  REAL(r_std), SAVE      :: kc_coef = 39.09 
     501  REAL(r_std), SAVE      :: Ko_Q10 = .085 
     502  REAL(r_std), SAVE      :: Oa = 210000. 
     503  REAL(r_std), SAVE      :: Ko_coef =  2.412 
     504  REAL(r_std), SAVE      :: CP_0 = 42. 
     505  REAL(r_std), SAVE      :: CP_temp_coef = 9.46  
     506  REAL(r_std), SAVE      :: CP_temp_ref = 25. 
     507  ! 
     508  REAL(r_std), SAVE, DIMENSION(2)  :: rt_coef = (/ 0.8, 1.3 /)  
     509  REAL(r_std), SAVE, DIMENSION(2)  :: vc_coef = (/ 0.39, 0.3 /) 
     510  ! 
     511  ! coefficients of the polynome of degree 5 used inthe equation of coeff_dew_veg 
     512  REAL(r_std), SAVE, DIMENSION(6)     :: dew_veg_poly_coeff = & 
     513  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /)  
     514 
     515 
     516 
     517                              !-------------! 
     518                              ! hydrolc.f90 ! 
     519                              !-------------! 
     520 
     521  ! 1. Scalar 
     522 
    355523  ! 
    356524  ! Wilting point (Has a numerical role for the moment) 
    357525  REAL(r_std),SAVE :: qwilt = 5.0 
    358   ! Total depth of soil reservoir (for hydrolc) 
    359   REAL(r_std),SAVE :: dpu_cste =  deux 
    360526  ! The minimal size we allow for the upper reservoir (m) 
    361527  REAL(r_std),SAVE :: min_resdis = 2.e-5 
     
    369535  REAL(r_std),SAVE :: exp_drain = 1.5 
    370536  !- 
    371   ! Transforms leaf area index into size of interception reservoir 
    372   REAL(r_std),SAVE      :: qsintcst = 0.1 
    373   ! Maximum quantity of water (Kg/M3) 
    374   REAL(r_std),SAVE :: mx_eau_eau = 150. 
    375   !- 
    376537  ! Constant in the computation of resistance for bare  soil evaporation 
    377538  REAL(r_std),SAVE :: rsol_cste = 33.E3 
     
    380541  REAL(r_std),SAVE :: hcrit_litter=0.08_r_std 
    381542 
    382   !!--------------------------------------------------- 
    383   !! Specific parameters for the CWRR hydrology module 
    384   !!---------------------------------------------------  
    385   ! 
    386 !!$ DS To externalise ?  
    387 !!$ advice of MM : to put in hydrol 
    388   ! CWRR linearisation 
    389   INTEGER(i_std),PARAMETER :: imin = 1 
    390   ! number of interval for CWRR 
    391   INTEGER(i_std),PARAMETER :: nbint = 100 
    392   ! number of points for CWRR 
    393   INTEGER(i_std),PARAMETER :: imax = nbint+1 
     543 
     544 
     545 
     546                              !-------------! 
     547                              ! hydrol.f90  ! 
     548                              !-------------! 
     549 
     550 
     551  ! 1. Scalar 
     552 
     553  ! Allowed moisture above mcs (boundary conditions) 
     554  REAL(r_std), SAVE                :: dmcs = 0.002      
     555  ! Allowed moisture below mcr (boundary conditions) 
     556  REAL(r_std), SAVE                :: dmcr = 0.002   
     557 
     558  ! 2. Arrays 
     559  
    394560  !- 
    395561  ! externalise w_time (some bug in hydrol) 
     
    406572  ! Saturated soil water content 
    407573  REAL(r_std),SAVE,DIMENSION(nstm) :: mcs = (/ 0.41_r_std, 0.43_r_std, 0.41_r_std /) 
    408   ! Total depth of soil reservoir (m) 
    409   REAL(r_std),SAVE,DIMENSION(nstm) :: dpu =  (/ 2.0_r_std, 2.0_r_std, 2.0_r_std /) 
    410574  !- 
    411575  ! dpu must be constant over the different soil types 
     
    427591 
    428592 
    429   !!----------------------------------------------------- 
    430   !! Vegetation parameters (previously in constantes_veg) 
    431   !!-----------------------------------------------------  
    432   ! 
    433   ! Value for frac_nobio for tests in 0-dim simulations 
     593   
     594                              !-------------! 
     595                              ! routing.f90 ! 
     596                              !-------------! 
     597 
     598  ! 1. Scalar 
     599 
     600  ! Parameter for the Kassel irrigation parametrization linked to the crops 
     601  REAL(r_std), SAVE          :: crop_coef = 1.5 
     602 
     603 
     604 
     605                              !--------------! 
     606                              ! slowproc.f90 ! 
     607                              !--------------! 
     608 
     609 
     610  ! 1. Scalar 
     611 
     612  REAL(r_std), SAVE          :: clayfraction_default = 0.2 
     613  ! Minimal fraction of mesh a vegetation type can occupy 
     614  REAL(r_std),SAVE :: min_vegfrac=0.001 
     615 ! Value for frac_nobio for tests in 0-dim simulations 
    434616  ! laisser ca tant qu'il n'y a que de la glace (pas de lacs) 
    435617  !DS : used in slowproc 
    436618  REAL(r_std),SAVE :: frac_nobio_fixed_test_1 = 0.0 
    437   !- 
    438   ! Is veget_ori array stored in restart file 
    439 !!$ DS: Where is it used ? 
    440   !  LOGICAL,PARAMETER :: ldveget_ori_on_restart = .TRUE. 
    441   !- 
    442   ! Set to .TRUE. if you want q_cdrag coming from GCM 
    443   ! used in diffuco 
    444   LOGICAL,SAVE :: ldq_cdrag_from_gcm = .FALSE. 
    445   !- 
    446   ! allow agricultural PFTs 
    447   LOGICAL,SAVE :: agriculture = .TRUE. 
    448   !- 
    449   ! The maximum mass (kg/m^2) of a glacier. 
    450   REAL(r_std),SAVE :: maxmass_glacier = 3000. 
    451   !- 
    452   ! Minimal fraction of mesh a vegetation type can occupy 
    453   REAL(r_std),SAVE :: min_vegfrac=0.001 
    454   !- 
    455 !!$ DS not used in the code ?  
    456   ! Limit of air temperature for snow 
    457   REAL(r_std),SAVE :: tsnow=273. 
    458   !- 
    459   ! Sets the amount above which only sublimation occures [Kg/m^2] 
    460   REAL(r_std),SAVE :: snowcri=1.5 
    461   ! Critical value for computation of snow albedo [Kg/m^2] 
    462   REAL(r_std),SAVE :: snowcri_alb=10. 
    463   ! Lower limit of snow amount 
    464   REAL(r_std),SAVE :: sneige 
    465   !- 
    466   ! The minimum wind 
    467   REAL(r_std),SAVE :: min_wind = 0.1 
    468   ! bare soil roughness length (m) 
    469   REAL(r_std),SAVE :: z0_bare = 0.01 
    470   ! ice roughness length (m) 
    471   REAL(r_std),SAVE :: z0_ice = 0.001 
    472   !- 
    473   ! Time constant of the albedo decay of snow 
    474   REAL(r_std),SAVE :: tcst_snowa = cinq 
    475   ! Maximum period of snow aging 
    476   REAL(r_std),SAVE :: max_snow_age = 50._r_std 
    477   ! Transformation time constant for snow (m) 
    478   REAL(r_std),SAVE :: snow_trans = 0.3_r_std 
    479   !- 
    480   ! albedo of dead leaves, VIS+NIR 
    481   REAL(r_std),DIMENSION(2),SAVE :: alb_deadleaf = (/ .12, .35/) 
    482   ! albedo of ice, VIS+NIR 
    483   REAL(r_std),DIMENSION(2),SAVE :: alb_ice = (/ .60, .20/) 
    484  
    485   !!-------------------------------- 
    486   !!  SECHIBA specific parameters 
    487   !!-------------------------------- 
    488   ! 
    489   !- 
    490   ! condveg 
     619 
     620  ! 2. Arrays 
     621 
     622  ! Default soil texture distribution in the following order : 
     623  !    sand, loam and clay 
     624  REAL(r_std),SAVE, DIMENSION(nstm) :: soiltype_default = (/ 0.0, 1.0, 0.0 /) 
     625 
     626 
     627 
     628 
     629                           !-----------------------------! 
     630                           !  STOMATE AND LPJ PARAMETERS ! 
     631                           !-----------------------------! 
     632 
     633  !- 
     634  ! stomate_alloc 
    491635  !-  
    492   ! to get z0 from height 
    493   REAL(r_std), SAVE  :: z0_over_height = un/16. 
    494   ! Magic number which relates the height to the displacement height. 
    495   REAL(r_std), SAVE  :: height_displacement = 0.75 
    496   !- 
    497   ! diffuco 
    498   !- 
    499   INTEGER(i_std), SAVE        :: nlai = 20 ! dimension de tableau 
    500   ! used in diffuco_trans 
    501   REAL(r_std), SAVE                :: laimax = 12. 
    502   REAL(r_std), SAVE                :: xc4_1 = .83 
    503   REAL(r_std), SAVE                :: xc4_2 = .93 
    504   !- 
    505   ! hydrol. 
    506   !- 
    507   ! Allowed moisture above mcs (boundary conditions) 
    508   REAL(r_std), SAVE                :: dmcs = 0.002      
    509   ! Allowed moisture below mcr (boundary conditions) 
    510   REAL(r_std), SAVE                :: dmcr = 0.002   
    511   !- 
    512   ! routing 
    513   !-  
    514   ! Parameter for the Kassel irrigation parametrization linked to the crops 
    515   REAL(r_std), SAVE          :: crop_coef = 1.5 
    516   !- 
    517   ! slowproc 
    518   !-  
    519   REAL(r_std), SAVE          :: clayfraction_default = 0.2 
     636  REAL(r_std), PARAMETER  ::  max_possible_lai = 10.  
     637  REAL(r_std), PARAMETER  ::  Nlim_Q10 = 10.  
     638  !- 
     639  ! stomate_litter 
     640  !- 
     641  REAL(r_std), PARAMETER    :: Q10 = 10. 
     642  ! 
     643 
     644! DS 31/03/2011 test new organization 
     645! List of Externalized Parameters by modules 
     646 
     647 
     648                              !----------------------! 
     649                              ! lpj_constraints.f90  ! 
     650                              !----------------------! 
     651 
    520652   
    521 !----------------------------- 
    522 !  STOMATE AND LPJ PARAMETERS 
    523 !----------------------------- 
    524   ! 
    525   !- 
    526   ! lpj_constraints 
    527   !- 
     653  ! 1. Scalar 
     654 
    528655  ! longest sustainable time without regeneration (vernalization) 
    529656  REAL(r_std), SAVE  :: too_long = 5. 
    530   ! 
    531   !- 
    532   ! lpj_fire 
    533   !- 
     657 
     658 
     659                              !--------------------! 
     660                              ! lpj_establish.f90  ! 
     661                              !--------------------! 
     662 
     663  ! 1. Scalar 
     664  ! Maximum tree establishment rate 
     665  REAL(r_std),SAVE :: estab_max_tree = 0.12 
     666  ! Maximum grass establishment rate 
     667  REAL(r_std),SAVE :: estab_max_grass = 0.12  
     668   
     669  ! 3. Coefficients of equations 
     670 
     671  REAL(r_std), SAVE      :: establish_scal_fact = 15. 
     672  REAL(r_std), SAVE      :: fpc_crit_max = .075 
     673  REAL(r_std), SAVE      :: fpc_crit_min= .05  
     674 
     675 
     676                              !---------------! 
     677                              ! lpj_fire.f90  ! 
     678                              !---------------! 
     679 
     680  ! 1. Scalar 
     681 
    534682  ! Time scale for memory of the fire index (days). Validated for one year in the DGVM. 
    535683  REAL(r_std), SAVE  :: tau_fire = 30.  
    536684  ! Critical litter quantity for fire 
    537685  REAL(r_std), SAVE  :: litter_crit = 200. 
    538   ! 
    539   !- 
    540   ! lpj_light 
    541   !- 
     686 
     687  ! 2. Arrays 
     688 
     689  ! What fraction of a burned plant compartment goes into the atmosphere 
     690  !   (rest into litter) 
     691  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /) 
     692 
     693 
     694  ! 3. Coefficients of equations 
     695 
     696  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)  
     697  REAL(r_std), SAVE, DIMENSION(4)  :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /) 
     698 
     699 
     700                              !--------------! 
     701                              ! lpj_gap.f90  ! 
     702                              !--------------! 
     703 
     704  ! 1. Scalar 
     705! DS 15/06/2011 : the name of the parameter constant_mortality was replaced by its keyword   
     706!!$  ! which kind of mortality 
     707!!$  LOGICAL, SAVE          :: constant_mortality = .TRUE. 
     708 
     709  ! 3. Coefficients of equations 
     710 
     711  REAL(r_std), SAVE      ::  availability_fact = 0.02 
     712  REAL(r_std), SAVE      ::  vigour_ref = 0.17 
     713  REAL(r_std), SAVE      ::  vigour_coeff = 70. 
     714 
     715 
     716                              !----------------! 
     717                              ! lpj_light.f90  ! 
     718                              !----------------! 
     719 
     720  ! 1. Scalar 
     721   
    542722  ! maximum total number of grass individuals in a closed canopy 
    543723  REAL(r_std), SAVE  :: grass_mercy = 0.01 
     
    547727  ! to fpc of last time step (F)? 
    548728  LOGICAL, SAVE     :: annual_increase = .TRUE. 
    549   ! 
    550   !- 
    551   ! lpj_pftinout 
    552   !- 
     729  ! For trees, minimum fraction of crown area occupied 
     730  ! (due to its branches etc.) 
     731  ! This means that only a small fraction of its crown area 
     732  ! can be invaded by other trees. 
     733  REAL(r_std),SAVE :: min_cover = 0.05   
     734 
     735 
     736                              !------------------! 
     737                              ! lpj_pftinout.f90 ! 
     738                              !------------------! 
     739 
     740  ! 1. Scalar 
     741 
    553742  ! minimum availability 
    554743  REAL(r_std), SAVE  :: min_avail = 0.01 
    555   ! 
    556   !- 
    557   ! stomate_alloc 
    558   !- 
     744  ! initial density of individuals 
     745  REAL(r_std),SAVE :: ind_0 = 0.02 
     746 
     747  ! 2. Arrays 
     748 
     749  ! 3. Coefficients of equations 
     750   
     751  REAL(r_std), SAVE      :: RIP_time_min = 1.25 
     752  REAL(r_std), SAVE      :: npp_longterm_init = 10.  
     753  REAL(r_std), SAVE      :: everywhere_init = 0.05 
     754 
     755 
     756 
     757                              !-------------------! 
     758                              ! stomate_alloc.f90 ! 
     759                              !-------------------! 
     760 
     761  ! 1. Scalar 
     762 
    559763  ! Do we try to reach a minimum reservoir even if we are severely stressed? 
    560764  LOGICAL, SAVE                                        :: ok_minres = .TRUE. 
     
    582786  ! scaling depth for nitrogen limitation (m) 
    583787  REAL(r_std), SAVE                                     :: z_nitrogen = 0.2 
    584   ! 
    585   !- 
    586   ! stomate_data 
    587   !- 
    588   !!------------------------------- 
    589   !! Parameters for the pipe model 
    590   !!------------------------------ 
    591   !- 
     788 
     789 
     790  ! 2. Arrays 
     791   
     792 
     793  ! 3. Coefficients of equations 
     794 
     795  REAL(r_std), SAVE  :: lai_max_to_happy = 0.5   
     796  REAL(r_std), SAVE  ::  Nlim_tref = 25. 
     797 
     798 
     799                              !------------------! 
     800                              ! stomate_data.f90 ! 
     801                              !------------------! 
     802  ! 1. Scalar  
     803 
     804  ! 
     805  ! 1.1 Parameters for the pipe model 
     806  ! 
    592807  ! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory) 
    593808  REAL(r_std),SAVE :: pipe_tune1 = 100.0 
     
    601816  ! one more SAVE 
    602817  REAL(r_std),SAVE :: pipe_k1 = 8.e3 
    603   ! 
    604   !- 
    605   ! Maximum tree establishment rate 
    606   REAL(r_std),SAVE :: estab_max_tree = 0.12 
    607   ! Maximum grass establishment rate 
    608   REAL(r_std),SAVE :: estab_max_grass = 0.12 
    609   ! initial density of individuals 
    610   REAL(r_std),SAVE :: ind_0 = 0.02 
    611   ! For trees, minimum fraction of crown area occupied 
    612   ! (due to its branches etc.) 
    613   ! This means that only a small fraction of its crown area 
    614   ! can be invaded by other trees. 
    615   REAL(r_std),SAVE :: min_cover = 0.05   
    616   !- 
    617   ! alpha's : ? 
    618   REAL(r_std),SAVE :: alpha_grass = .5 
    619   REAL(r_std),SAVE :: alpha_tree = 1. 
    620   !- 
    621   ! maximum reference long term temperature (K) 
    622   REAL(r_std),SAVE :: tlong_ref_max = 303.1 
    623   ! minimum reference long term temperature (K) 
    624   REAL(r_std),SAVE :: tlong_ref_min = 253.1 
    625   ! 
    626   !! LOGICAL 
    627   !- 
    628   ! Do we treat PFT expansion across a grid point after introduction? 
    629   ! default = .FALSE. 
    630   LOGICAL,SAVE :: treat_expansion = .FALSE. 
    631   ! 
    632   ! herbivores? 
    633   LOGICAL,SAVE :: ok_herbivores = .FALSE. 
    634   ! 
    635   ! harvesting ? 
    636   LOGICAL,SAVE :: harvest_agri = .TRUE. 
    637   !!---------------------- 
    638   !! climatic parameters  
    639   !!--------------------- 
     818  ! pipe tune exponential coeff 
     819  REAL(r_std), SAVE      :: pipe_tune_exp_coeff = 1.6  
     820 
     821  ! 
     822  !  1.2 climatic parameters  
    640823  ! 
    641824  ! minimum precip, in mm/year 
     
    645828  ! critical fpc, needed for light competition and establishment 
    646829  REAL(r_std),SAVE :: fpc_crit = 0.95 
    647   !- 
    648   ! fraction of GPP which is lost as growth respiration 
    649   REAL(r_std),SAVE :: frac_growthresp = 0.28 
    650   ! 
    651   !- 
     830 
     831  ! 
     832  ! 1.3 sapling characteristics 
     833  ! 
     834  ! alpha's : ? 
     835  REAL(r_std),SAVE :: alpha_grass = .5 
     836  REAL(r_std),SAVE :: alpha_tree = 1. 
    652837  ! mass ratio (heartwood+sapwood)/sapwood 
    653838  REAL(r_std), SAVE  :: mass_ratio_heart_sap = 3. 
    654   ! 
    655   !!--------------------------------------------------------- 
    656   ! time scales for phenology and other processes (in days) 
    657   !!--------------------------------------------------------- 
     839  ! fraction of GPP which is lost as growth respiration 
     840  REAL(r_std),SAVE :: frac_growthresp = 0.28   
     841 
     842  ! 
     843  ! 1.4  time scales for phenology and other processes (in days) 
    658844  ! 
    659845  REAL(r_std), SAVE    ::  tau_hum_month = 20.             
     
    667853  REAL(r_std), SAVE    ::  tau_ngd = 50. 
    668854  REAL(r_std), SAVE    ::  coeff_tau_longterm = 3. 
    669   ! used in stomate_data and in stomate_season 
    670855  REAL(r_std), SAVE    ::  tau_longterm  
    671   ! 
    672   !- 
    673   ! stomate_litter 
    674   !- 
    675   ! scaling depth for soil activity (m) 
    676   REAL(r_std), SAVE    :: z_decomp = 0.2 
    677   ! 
    678   !- 
    679   ! stomate_lpj 
    680   !- 
    681   REAL(r_std), SAVE    :: frac_turnover_daily = 0.55 
    682   ! 
    683   !- 
    684   ! stomate_npp 
    685   !- 
    686   ! maximum fraction of allocatable biomass used for maintenance respiration 
    687   REAL(r_std), SAVE   :: tax_max = 0.8 
    688   ! 
    689   !- 
    690   ! stomate_phenology 
    691   !-  
    692   ! take carbon from atmosphere if carbohydrate reserve too small? 
    693   LOGICAL, SAVE                                         :: always_init = .FALSE. 
    694   ! minimum time (d) since last beginning of a growing season 
    695   REAL(r_std), SAVE                                      :: min_growthinit_time = 300. 
    696   ! moisture availability above which moisture tendency doesn't matter 
    697   REAL(r_std), SAVE                                   :: moiavail_always_tree = 1.0 
    698   REAL(r_std), SAVE                                   :: moiavail_always_grass = 0.6 
    699   ! monthly temp. above which temp. tendency doesn't matter 
    700   REAL(r_std), SAVE                                   ::  t_always 
    701   REAL(r_std), SAVE                                   ::  t_always_add = 10. 
    702   ! 
    703   !- 
    704   ! stomate_season 
    705   !- 
    706   ! rapport maximal GPP/GGP_max pour dormance 
    707   REAL(r_std), SAVE                                  :: gppfrac_dormance = 0.2 
    708   ! minimum gpp considered as not "lowgpp" 
    709   REAL(r_std), SAVE                                  :: min_gpp_allowed = 0.3 
    710   ! tau (year) for "climatologic variables 
    711   REAL(r_std), SAVE                                  :: tau_climatology = 20 
    712   ! parameters for herbivore activity 
    713   REAL(r_std), SAVE                                  :: hvc1 = 0.019 
    714   REAL(r_std), SAVE                                  :: hvc2 = 1.38 
    715   REAL(r_std), SAVE                                  :: leaf_frac_hvc =.33 
    716   ! 
    717   !- 
    718   ! stomate_vmax 
    719   !- 
    720   ! offset (minimum relative vcmax) 
    721   REAL(r_std), SAVE                                      :: vmax_offset = 0.3 
    722   ! leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age) 
    723   REAL(r_std), SAVE                                      :: leafage_firstmax = 0.03 
    724   ! leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age) 
    725   REAL(r_std), SAVE                                      :: leafage_lastmax = 0.5 
    726   ! leaf age at which vmax attains its minimum (in fraction of critical leaf age) 
    727   REAL(r_std), SAVE                                      :: leafage_old = 1. 
    728  
    729  
    730 !-------------------------- 
    731 !-------------------------- 
    732 ! ARRAYS-PARAMETERS 
    733 !-------------------------- 
    734 !-------------------------- 
    735   !- 
    736   ! condveg 
    737   !- 
    738   !   The correspondance table for the soil color numbers and their albedo 
    739   ! 
    740   REAL(r_std), DIMENSION(classnb) :: vis_dry = (/0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/) 
    741   REAL(r_std), DIMENSION(classnb) :: nir_dry = (/0.48, 0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)   
    742   REAL(r_std), DIMENSION(classnb) :: vis_wet = (/0.12, 0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)   
    743   REAL(r_std), DIMENSION(classnb) :: nir_wet = (/0.24, 0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/) 
    744   !    
    745   ! Nathalie, introduction d'un albedo moyen, VIS+NIR 
    746   ! Les valeurs suivantes correspondent a la moyenne des valeurs initiales 
    747   !  REAL(stnd), DIMENSION(classnb) :: albsoil_vis = (/0.18, 0.165, 0.15, 0.135, 0.12, 0.105, 0.09, 0.075, 0.21/) 
    748   !  REAL(stnd), DIMENSION(classnb) :: albsoil_nir = (/0.36, 0.33, 0.30, 0.27, 0.24, 0.21, 0.18, 0.15, 0.43/) 
    749   ! les valeurs retenues accentuent le contraste entre equateur et Sahara.  
    750   ! On diminue aussi l'albedo des deserts (tous sauf Sahara) 
    751   REAL(r_std), DIMENSION(classnb) :: albsoil_vis = (/0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25/) 
    752   REAL(r_std), DIMENSION(classnb) :: albsoil_nir = (/0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45/) 
    753  
    754   !- 
    755   ! lpj_fire 
    756   !- 
    757  
    758   ! What fraction of a burned plant compartment goes into the atmosphere 
    759   !   (rest into litter) 
    760   REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /) 
    761  
    762   !- 
    763   ! stomate_litter  
    764   !- 
    765  
    766   ! C/N ratio 
    767   REAL(r_std), SAVE, DIMENSION(nparts) :: CN = 40.0  
    768   ! Lignine/C ratio of the different plant parts 
    769   REAL(r_std), SAVE, DIMENSION(nparts) :: LC = (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /) 
    770   ! corresponding to frac_soil(istructural,iactive,iabove)  
    771   REAL(r_std), SAVE      ::  frac_soil_struct_aa = .55 
    772   ! corresponding to frac_soil(istructural,iactive,ibelow) 
    773   REAL(r_std), SAVE      :: frac_soil_struct_ab = .45 
    774   ! corresponding to frac_soil(istructural,islow,iabove) 
    775   REAL(r_std), SAVE      ::  frac_soil_struct_sa = .7 
    776   ! corresponding to frac_soil(istructural,islow,ibelow)  
    777   REAL(r_std), SAVE      ::  frac_soil_struct_sb = .7 
    778   ! corresponding to frac_soil(imetabolic,iactive,iabove) 
    779   REAL(r_std), SAVE      ::  frac_soil_metab_aa = .45 
    780   ! corresponding to frac_soil(imetabolic,iactive,ibelow) 
    781   REAL(r_std), SAVE      ::  frac_soil_metab_ab = .45 
    782   !- 
    783   ! stomate_soilcarbon 
    784   !- 
    785   ! frac_carb_coefficients 
    786   ! from active pool: depends on clay content 
    787   ! correspnding to  frac_carb(:,iactive,iactive) 
    788   REAL(r_std), SAVE      :: frac_carb_aa = 0.0 
    789   ! correspnding to  frac_carb(:,iactive,ipassive) 
    790   REAL(r_std), SAVE      :: frac_carb_ap = 0.004 
    791   !frac_carb(;;iactive,islow) is computed in stomate_soilcarbon.f90 
    792   !- 
    793   ! from slow pool 
    794   ! correspnding to  frac_carb(:,islow,islow) 
    795   REAL(r_std), SAVE      :: frac_carb_ss = 0.0   
    796   ! correspnding to  frac_carb(:,islow,iactive) 
    797   REAL(r_std), SAVE      :: frac_carb_sa = .42 
    798   ! correspnding to  frac_carb(:,islow,ipassive) 
    799   REAL(r_std), SAVE      :: frac_carb_sp = .03 
    800   !- 
    801   ! from passive pool 
    802   ! correspnding to  frac_carb(:,ipassive,ipassive) 
    803   REAL(r_std), SAVE      :: frac_carb_pp = .0 
    804   ! correspnding to  frac_carb(:,ipassive,iactive) 
    805   REAL(r_std), SAVE      :: frac_carb_pa = .45 
    806   ! correspnding to  frac_carb(:,ipassive,islow) 
    807   REAL(r_std), SAVE      :: frac_carb_ps = .0 
    808   
    809  
    810 !---------------------------------------- 
    811 !--------------------------------------- 
    812 ! COEFFICIENTS OF EQUATIONS 
    813 !------------------------------------- 
    814 !--------------------------------------- 
    815  
    816   !--------- 
    817   ! SECHIBA 
    818   !--------- 
    819   !- 
    820   ! diffuco 
    821   !- 
    822   REAL(r_std),PARAMETER :: Tetens_1 = 0.622    
    823   REAL(r_std),PARAMETER :: Tetens_2 = 0.378 
    824   REAL(r_std),PARAMETER :: std_ci_frac = 0.667 
    825   REAL(r_std),PARAMETER :: alpha_j = 0.8855 
    826   REAL(r_std),PARAMETER :: curve_assim = 0.7 
    827   REAL(r_std),PARAMETER :: WJ_coeff1 = 4.5 
    828   REAL(r_std),PARAMETER :: WJ_coeff2 = 10.5 
    829   REAL(r_std),PARAMETER :: Vc_to_Rd_ratio = 0.011 
    830   REAL(r_std),PARAMETER :: O2toCO2_stoechio = 1.6 
    831   REAL(r_std),PARAMETER :: mmol_to_m_1 = 0.0244 
    832   REAL(r_std),PARAMETER  :: RG_to_PAR = 0.5  
    833   REAL(r_std),PARAMETER  :: W_to_mmol = 4.6 ! W_to_mmol * RG_to_PAR = 2.3 
    834   ! 
    835   REAL(r_std), SAVE      :: lai_level_depth = .15 
    836   REAL(r_std), SAVE      :: x1_coef =  0.177 
    837   REAL(r_std), SAVE      :: x1_Q10 =  0.069 
    838   REAL(r_std), SAVE      :: quantum_yield =  0.092 
    839   REAL(r_std), SAVE      :: kt_coef = 0.7      
    840   REAL(r_std), SAVE      :: kc_coef = 39.09 
    841   REAL(r_std), SAVE      :: Ko_Q10 = .085 
    842   REAL(r_std), SAVE      :: Oa = 210000. 
    843   REAL(r_std), SAVE      :: Ko_coef =  2.412 
    844   REAL(r_std), SAVE      :: CP_0 = 42. 
    845   REAL(r_std), SAVE      :: CP_temp_coef = 9.46  
    846   REAL(r_std), SAVE      :: CP_temp_ref = 25. 
    847   ! 
    848   REAL(r_std), SAVE, DIMENSION(2)  :: rt_coef = (/ 0.8, 1.3 /)  
    849   REAL(r_std), SAVE, DIMENSION(2)  :: vc_coef = (/ 0.39, 0.3 /) 
    850   ! 
    851   ! coefficients of the polynome of degree 5 used inthe equation of coeff_dew_veg 
    852   REAL(r_std), SAVE, DIMENSION(6)     :: dew_veg_poly_coeff = & 
    853   & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /)  
    854   
    855   !--------- 
    856   ! LPJ 
    857   !--------- 
    858   !- 
    859   ! lpj_crown 
    860   !- 
    861   REAL(r_std), SAVE      :: pipe_tune_exp_coeff = 1.6  
    862   ! 
    863   !- 
    864   ! lpj_establish 
    865   !- 
    866   REAL(r_std), SAVE      :: establish_scal_fact = 15. 
    867   REAL(r_std), SAVE      :: fpc_crit_max = .075 
    868   REAL(r_std), SAVE      :: fpc_crit_min= .05  
    869   ! 
    870   !- 
    871   ! lpj_fire 
    872   !- 
    873   REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)  
    874   REAL(r_std), SAVE, DIMENSION(4)  :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /) 
    875   ! 
    876   !- 
    877   ! lpj_gap 
    878   !-  
    879   REAL(r_std), SAVE      ::  availability_fact = 0.02 
    880   REAL(r_std), SAVE      ::  vigour_ref = 0.17 
    881   REAL(r_std), SAVE      ::  vigour_coeff = 70.  
    882   !- 
    883   ! lpj_pftinout 
    884   !- 
    885   REAL(r_std), SAVE      :: RIP_time_min = 1.25 
    886   REAL(r_std), SAVE      :: npp_longterm_init = 10.  
    887   REAL(r_std), SAVE      :: everywhere_init = 0.05 
    888   ! 
    889  
    890   !--------- 
    891   ! STOMATE 
    892   !--------- 
    893   !- 
    894   ! stomate_alloc 
    895   !-  
    896   REAL(r_std), PARAMETER  ::  max_possible_lai = 10.  
    897   REAL(r_std), PARAMETER  ::  Nlim_Q10 = 10.  
    898   ! 
    899   REAL(r_std), SAVE      :: lai_max_to_happy = 0.5   
    900   REAL(r_std), SAVE  ::  Nlim_tref = 25. 
    901   ! 
    902   !- 
    903   ! stomate_data 
    904   !- 
     856 
     857  ! 3. Coefficients of equations 
     858 
    905859  REAL(r_std), SAVE  :: bm_sapl_carbres = 5. 
    906860  REAL(r_std), SAVE  :: bm_sapl_sapabove = 0.5 
     
    920874  REAL(r_std), SAVE, DIMENSION(2)  :: maxdia_coeff =(/ 100., 0.01/) 
    921875  REAL(r_std), SAVE, DIMENSION(4)  :: bm_sapl_leaf = (/ 4., 4., .8, 5./) 
    922   ! 
    923   !- 
    924   ! stomate_litter 
    925   !- 
    926   REAL(r_std), PARAMETER    :: Q10 = 10. 
    927   ! 
    928   REAL(r_std), SAVE      :: metabolic_ref_frac = 0.85 
     876 
     877 
     878 
     879                              !--------------------! 
     880                              ! stomate_litter.f90 ! 
     881                              !--------------------! 
     882 
     883 
     884  ! 1. Scalar 
     885 
     886  ! scaling depth for soil activity (m) 
     887  REAL(r_std), SAVE    :: z_decomp = 0.2 
     888 
     889  ! 2. Arrays 
     890 
     891  ! C/N ratio 
     892  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = 40.0  
     893  ! Lignine/C ratio of the different plant parts 
     894  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /) 
     895  ! corresponding to frac_soil(istructural,iactive,iabove)  
     896  REAL(r_std), SAVE      ::  frac_soil_struct_aa = .55 
     897  ! corresponding to frac_soil(istructural,iactive,ibelow) 
     898  REAL(r_std), SAVE      :: frac_soil_struct_ab = .45 
     899  ! corresponding to frac_soil(istructural,islow,iabove) 
     900  REAL(r_std), SAVE      ::  frac_soil_struct_sa = .7 
     901  ! corresponding to frac_soil(istructural,islow,ibelow)  
     902  REAL(r_std), SAVE      ::  frac_soil_struct_sb = .7 
     903  ! corresponding to frac_soil(imetabolic,iactive,iabove) 
     904  REAL(r_std), SAVE      ::  frac_soil_metab_aa = .45 
     905  ! corresponding to frac_soil(imetabolic,iactive,ibelow) 
     906  REAL(r_std), SAVE      ::  frac_soil_metab_ab = .45 
     907 
     908  ! 3. Coefficients of equations 
     909 
     910  REAL(r_std), SAVE      :: metabolic_ref_frac = 0.85  ! used by litter and soilcarbon 
    929911  REAL(r_std), SAVE      :: metabolic_LN_ratio = 0.018     
    930912  REAL(r_std), SAVE      :: tau_metabolic = .066 
     
    934916  REAL(r_std), SAVE      :: litter_struct_coef = 3. 
    935917  REAL(r_std), SAVE, DIMENSION(3)   :: moist_coeff = (/ 1.1,  2.4,  0.29 /) 
    936   ! 
    937   !- 
    938   ! stomate_phenology 
    939   !- 
     918 
     919 
     920 
     921                             !-----------------! 
     922                             ! stomate_lpj.f90 ! 
     923                             !-----------------! 
     924 
     925  ! 1. Scalar 
     926 
     927  REAL(r_std), SAVE    :: frac_turnover_daily = 0.55 
     928 
     929 
     930                             !-----------------! 
     931                             ! stomate_npp.f90 ! 
     932                             !-----------------! 
     933 
     934  ! 1. Scalar 
     935 
     936  ! maximum fraction of allocatable biomass used for maintenance respiration 
     937  REAL(r_std), SAVE   :: tax_max = 0.8 
     938 
     939 
     940                             !-----------------------! 
     941                             ! stomate_phenology.f90 ! 
     942                             !-----------------------! 
     943 
     944 
     945 
     946  ! 1. Scalar 
     947 
     948  ! take carbon from atmosphere if carbohydrate reserve too small? 
     949  LOGICAL, SAVE                                         :: always_init = .FALSE. 
     950  ! minimum time (d) since last beginning of a growing season 
     951  REAL(r_std), SAVE                                      :: min_growthinit_time = 300. 
     952  ! moisture availability above which moisture tendency doesn't matter 
     953  REAL(r_std), SAVE                                   :: moiavail_always_tree = 1.0 
     954  REAL(r_std), SAVE                                   :: moiavail_always_grass = 0.6 
     955  ! monthly temp. above which temp. tendency doesn't matter 
     956  REAL(r_std), SAVE                                   ::  t_always 
     957  REAL(r_std), SAVE                                   ::  t_always_add = 10. 
     958 
     959  ! 3. Coefficients of equations 
     960   
    940961  REAL(r_std), SAVE      :: gddncd_ref = 603. 
    941962  REAL(r_std), SAVE      :: gddncd_curve = 0.0091 
    942963  REAL(r_std), SAVE      :: gddncd_offset = 64. 
    943   ! 
    944   !- 
    945   ! stomate_prescribe 
    946   !- 
     964 
     965 
     966 
     967 
     968                             !-----------------------! 
     969                             ! stomate_prescribe.f90 ! 
     970                             !-----------------------! 
     971 
     972  ! 3. Coefficients of equations 
     973 
    947974  REAL(r_std), SAVE      :: cn_tree = 4. 
    948975  REAL(r_std), SAVE      :: bm_sapl_rescale = 40. 
    949   ! 
    950   !- 
    951   ! stomate_resp 
    952   !- 
     976 
     977 
     978 
     979                             !------------------! 
     980                             ! stomate_resp.f90 ! 
     981                             !------------------! 
     982 
     983  ! 3. Coefficients of equations 
     984 
    953985  REAL(r_std), SAVE      :: maint_resp_min_vmax = 0.3   
    954986  REAL(r_std), SAVE      :: maint_resp_coeff = 1.4 
    955   ! 
    956   !- 
    957   ! stomate_season 
    958   !- 
    959   REAL(r_std), SAVE  :: ncd_max_year = 3. 
    960   REAL(r_std), SAVE  :: gdd_threshold = 5. 
    961   REAL(r_std), SAVE  :: green_age_ever = 2. 
    962   REAL(r_std), SAVE  :: green_age_dec = 0.5 
    963   !- 
    964   ! stomate_soilcarbon 
    965   !- 
     987 
     988 
     989 
     990                             !------------------------! 
     991                             ! stomate_soilcarbon.f90 ! 
     992                             !------------------------! 
     993 
     994  ! 2. Arrays  
     995 
     996  ! frac_carb_coefficients 
     997  ! from active pool: depends on clay content 
     998  ! correspnding to  frac_carb(:,iactive,iactive) 
     999  REAL(r_std), SAVE      :: frac_carb_aa = 0.0 
     1000  ! correspnding to  frac_carb(:,iactive,ipassive) 
     1001  REAL(r_std), SAVE      :: frac_carb_ap = 0.004 
     1002  !frac_carb(;;iactive,islow) is computed in stomate_soilcarbon.f90 
     1003  !- 
     1004  ! from slow pool 
     1005  ! correspnding to  frac_carb(:,islow,islow) 
     1006  REAL(r_std), SAVE      :: frac_carb_ss = 0.0   
     1007  ! correspnding to  frac_carb(:,islow,iactive) 
     1008  REAL(r_std), SAVE      :: frac_carb_sa = .42 
     1009  ! correspnding to  frac_carb(:,islow,ipassive) 
     1010  REAL(r_std), SAVE      :: frac_carb_sp = .03 
     1011  !- 
     1012  ! from passive pool 
     1013  ! correspnding to  frac_carb(:,ipassive,ipassive) 
     1014  REAL(r_std), SAVE      :: frac_carb_pp = .0 
     1015  ! correspnding to  frac_carb(:,ipassive,iactive) 
     1016  REAL(r_std), SAVE      :: frac_carb_pa = .45 
     1017  ! correspnding to  frac_carb(:,ipassive,islow) 
     1018  REAL(r_std), SAVE      :: frac_carb_ps = .0 
     1019 
     1020 
     1021  ! 3. Coefficients of equations 
     1022 
    9661023  REAL(r_std), SAVE      :: active_to_pass_clay_frac = .68   
    9671024  !residence times in carbon pools (days) 
     
    9711028  ! 
    9721029  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/) 
    973   ! 
    974   !- 
    975   ! stomate_turnover 
    976   !- 
     1030 
     1031 
     1032 
     1033                             !----------------------! 
     1034                             ! stomate_turnover.f90 ! 
     1035                             !----------------------! 
     1036 
     1037  ! 3.Coefficients of equations 
     1038 
    9771039  REAL(r_std), SAVE      ::  new_turnover_time_ref = 20. 
    9781040  REAL(r_std), SAVE      ::  dt_turnover_time = 10.  
     
    9801042  REAL(r_std), SAVE, DIMENSION(3)   :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) 
    9811043 
    982 !************************************************************** 
     1044 
     1045 
     1046 
     1047                             !------------------! 
     1048                             ! stomate_vmax.f90 ! 
     1049                             !------------------! 
     1050 
     1051  ! 1. Scalar 
     1052 
     1053  ! offset (minimum relative vcmax) 
     1054  REAL(r_std), SAVE                                      :: vmax_offset = 0.3 
     1055  ! leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age) 
     1056  REAL(r_std), SAVE                                      :: leafage_firstmax = 0.03 
     1057  ! leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age) 
     1058  REAL(r_std), SAVE                                      :: leafage_lastmax = 0.5 
     1059  ! leaf age at which vmax attains its minimum (in fraction of critical leaf age) 
     1060  REAL(r_std), SAVE                                      :: leafage_old = 1. 
     1061 
     1062 
     1063 
     1064                             !--------------------! 
     1065                             ! stomate_season.f90 ! 
     1066                             !--------------------! 
     1067 
     1068 
     1069  ! 1. Scalar 
     1070 
     1071  ! rapport maximal GPP/GGP_max pour dormance 
     1072  REAL(r_std), SAVE                                  :: gppfrac_dormance = 0.2 
     1073  ! minimum gpp considered as not "lowgpp" 
     1074  REAL(r_std), SAVE                                  :: min_gpp_allowed = 0.3 
     1075  ! tau (year) for "climatologic variables 
     1076  REAL(r_std), SAVE                                  :: tau_climatology = 20 
     1077  ! parameters for herbivore activity 
     1078  REAL(r_std), SAVE                                  :: hvc1 = 0.019 
     1079  REAL(r_std), SAVE                                  :: hvc2 = 1.38 
     1080  REAL(r_std), SAVE                                  :: leaf_frac_hvc =.33 
     1081  ! maximum reference long term temperature (K) 
     1082  REAL(r_std),SAVE :: tlong_ref_max = 303.1 
     1083  ! minimum reference long term temperature (K) 
     1084  REAL(r_std),SAVE :: tlong_ref_min = 253.1 
     1085 
     1086  ! 3. Coefficients of equations 
     1087 
     1088  REAL(r_std), SAVE  :: ncd_max_year = 3. 
     1089  REAL(r_std), SAVE  :: gdd_threshold = 5. 
     1090  REAL(r_std), SAVE  :: green_age_ever = 2. 
     1091  REAL(r_std), SAVE  :: green_age_dec = 0.5 
     1092 
     1093 
    9831094 
    9841095 CONTAINS 
    9851096 
    986  ! Subroutine called for getin the new parameters values used in sechiba 
    987  ! 
    988  SUBROUTINE getin_sechiba_parameters 
    989  
    990   IMPLICIT NONE 
    991   ! first call 
    992   LOGICAL, SAVE ::  first_call = .TRUE. 
    993  
    994   IF(first_call) THEN  
    995  
    996 !!$   CALL getin('DIAG_QSAT',diag_qsat) 
    997    !   
    998    CALL getin('QWILT',qwilt) 
    999    CALL getin('MIN_RESDIS',min_resdis) 
    1000    CALL getin('MIN_DRAIN',min_drain) 
    1001    CALL getin('MAX_DRAIN',max_drain) 
    1002    CALL getin('EXP_DRAIN',exp_drain) 
    1003    CALL getin('MX_EAU_EAU',mx_eau_eau) 
    1004    CALL getin('RSOL_CSTE',rsol_cste) 
    1005    CALL getin('HCRIT_LITTER',hcrit_litter) 
    1006    !- 
    1007    CALL getin('SOILTYPE_DEFAULT',soiltype_default) 
    1008    !- 
    1009    CALL getin('MAXMASS_GLACIER',maxmass_glacier) 
    1010    CALL getin('MIN_VEGFRAC',min_vegfrac) 
    1011    !- 
    1012    CALL getin('SNOWCRI',snowcri) 
    1013    !- 
    1014    CALL getin('SNOWCRI_ALB',snowcri_alb) 
    1015    CALL getin('MIN_WIND',min_wind) 
    1016    CALL getin('Z0_BARE',z0_bare) 
    1017    CALL getin('Z0_ICE',z0_ice) 
    1018    CALL getin('TCST_SNOWA',tcst_snowa) 
    1019    CALL getin('MAX_SNOW_AGE',max_snow_age) 
    1020    CALL getin('SNOW_TRANS',snow_trans) 
    1021    CALL getin('ALB_DEADLEAF',alb_deadleaf) 
    1022    CALL getin('ALB_ICE',alb_ice) 
    1023    !- 
    1024    CALL getin('Z0_OVER_HEIGHT',z0_over_height) 
    1025    CALL getin('HEIGHT_DISPLACEMENT',height_displacement) 
    1026    !- 
    1027    CALL getin('NLAI',nlai) 
    1028    CALL getin('LAIMAX',laimax) 
    1029    CALL getin('XC4_1',xc4_1) 
    1030    CALL getin('XC4_2',xc4_2) 
    1031    !- 
    1032    CALL getin('DMCS',dmcs) 
    1033    CALL getin('DMCR',dmcr) 
    1034    !- 
    1035    CALL getin('VIS_DRY',vis_dry) 
    1036    CALL getin('NIR_DRY',nir_dry) 
    1037    CALL getin('VIS_WET',vis_wet) 
    1038    CALL getin('NIR_WET',nir_wet) 
    1039    CALL getin('ALBSOIL_VIS',albsoil_vis) 
    1040    CALL getin('ALBSOIL_NIR',albsoil_nir) 
    1041    !- 
    1042    CALL getin('CLAYFRACTION_DEFAULT',clayfraction_default) 
    1043    ! 
    1044    CALL getin('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff) 
    1045  
    1046    first_call =.FALSE. 
    1047  
    1048   ENDIF 
    1049  
    1050   END SUBROUTINE getin_sechiba_parameters 
    1051  
    1052 !********************************************************* 
    1053  
    1054   ! Subroutine called only if river_routing is activated 
    1055  
    1056   SUBROUTINE getin_routing_parameters 
    1057  
    1058   IMPLICIT NONE 
    1059  
    1060   LOGICAL, SAVE ::  first_call = .TRUE. 
    1061  
    1062   IF(first_call) THEN 
    1063  
    1064      CALL getin('CROP_COEF',crop_coef) 
    1065  
    1066      first_call =.FALSE. 
    1067  
    1068   ENDIF    
    1069  
    1070   END SUBROUTINE getin_routing_parameters   
    1071  
    1072 !******************************************************* 
    1073  
    1074   ! Subroutine called only if hydrol_cwrr is activated 
    1075  
    1076   SUBROUTINE getin_hydrol_cwrr_parameters 
    1077  
    1078   IMPLICIT NONE 
    1079  
    1080   LOGICAL, SAVE ::  first_call = .TRUE. 
    1081  
     1097   SUBROUTINE getin_sechiba_parameters 
     1098 
     1099     IMPLICIT NONE 
     1100     ! first call 
     1101     LOGICAL, SAVE ::  first_call = .TRUE. 
     1102      
     1103     IF(first_call) THEN  
     1104         
     1105        ! Global 
     1106        ! DS by global I mean the parameters used by two or more modules 
     1107        ! Example : the common parameters for both hydrology models 
     1108        CALL getin_p('MAXMASS_GLACIER',maxmass_glacier) 
     1109        CALL getin_p('SNOWCRI',snowcri) 
     1110        CALL getin_p('SECHIBA_QSINT', qsintcst) 
     1111        WRITE(numout, *)' SECHIBA_QSINT, qsintcst = ', qsintcst 
     1112        CALL getin_p("HYDROL_SOIL_DEPTH", dpu_cste) 
     1113        ! 
     1114        CALL getin_p('MIN_WIND',min_wind) 
     1115        CALL getin_p('MAX_SNOW_AGE',max_snow_age) 
     1116        CALL getin_p('SNOW_TRANS',snow_trans) 
     1117        CALL getin_p('MX_EAU_EAU',mx_eau_eau) 
     1118        !- 
     1119        ! condveg 
     1120        CALL getin_p('Z0_OVER_HEIGHT',z0_over_height) 
     1121        CALL getin_p('HEIGHT_DISPLACEMENT',height_displacement) 
     1122        CALL getin_p('Z0_BARE',z0_bare) 
     1123        CALL getin_p('Z0_ICE',z0_ice) 
     1124        CALL getin_p('TCST_SNOWA',tcst_snowa) 
     1125        CALL getin_p('SNOWCRI_ALB',snowcri_alb) 
     1126        ! 
     1127        CALL getin_p('VIS_DRY',vis_dry) 
     1128        CALL getin_p('NIR_DRY',nir_dry) 
     1129        CALL getin_p('VIS_WET',vis_wet) 
     1130        CALL getin_p('NIR_WET',nir_wet) 
     1131        CALL getin_p('ALBSOIL_VIS',albsoil_vis) 
     1132        CALL getin_p('ALBSOIL_NIR',albsoil_nir) 
     1133        !- 
     1134        CALL getin_p('ALB_DEADLEAF',alb_deadleaf) 
     1135        CALL getin_p('ALB_ICE',alb_ice) 
     1136        !- 
     1137        ! diffuco  
     1138        ! DS the rest of diffuco parameters are only read when ok_co2 is set to TRUE 
     1139        CALL getin_p('NLAI',nlai) 
     1140        CALL getin_p('LAIMAX',laimax) 
     1141        CALL getin_p('XC4_1',xc4_1) 
     1142        CALL getin_p('XC4_2',xc4_2) 
     1143        CALL getin_p('DEW_VEG_POLY_COEFF',dew_veg_poly_coeff) 
     1144        !- 
     1145        ! slowproc 
     1146        CALL getin_p('CLAYFRACTION_DEFAULT',clayfraction_default) 
     1147        CALL getin_p('MIN_VEGFRAC',min_vegfrac) 
     1148        CALL getin_p('SOILTYPE_DEFAULT',soiltype_default) 
     1149         
     1150         
     1151        first_call =.FALSE. 
     1152         
     1153     ENDIF 
     1154      
     1155   END SUBROUTINE getin_sechiba_parameters 
     1156! 
     1157!= 
     1158! 
     1159   ! Subroutine called only if ok_co2 is activated 
     1160   ! only for diffuco_trans_co2 
     1161    
     1162   SUBROUTINE getin_co2_parameters 
     1163      
     1164     IMPLICIT NONE 
     1165      
     1166     LOGICAL, SAVE ::  first_call = .TRUE. 
     1167      
     1168     IF(first_call) THEN 
     1169         
     1170        CALL getin_p('LAI_LEVEL_DEPTH',lai_level_depth) 
     1171        CALL getin_p('X1_COEF',x1_coef) 
     1172        CALL getin_p('X1_Q10',x1_Q10) 
     1173        CALL getin_p('QUANTUM_YIELD',quantum_yield) 
     1174        CALL getin_p('KT_COEF',kt_coef) 
     1175        CALL getin_p('KC_COEF',kc_coef) 
     1176        CALL getin_p('KO_Q10',Ko_Q10) 
     1177        CALL getin_p('OA',Oa) 
     1178        CALL getin_p('KO_COEF',Ko_coef) 
     1179        CALL getin_p('CP_0',CP_0) 
     1180        CALL getin_p('CP_TEMP_COEF',cp_temp_coef) 
     1181        CALL getin_p('CP_TEMP_REF',cp_temp_ref) 
     1182        CALL getin_p('RT_COEF',rt_coef) 
     1183        CALL getin_p('VC_COEF',vc_coef) 
     1184         
     1185        first_call =.FALSE. 
     1186         
     1187     ENDIF 
     1188      
     1189   END SUBROUTINE getin_co2_parameters 
     1190! 
     1191!= 
     1192! 
     1193   SUBROUTINE getin_hydrolc_parameters 
     1194      
     1195     LOGICAL, SAVE ::  first_call = .TRUE. 
     1196      
     1197     IF(first_call) THEN  
     1198         
     1199        CALL getin_p('QWILT',qwilt) 
     1200        CALL getin_p('MIN_RESDIS',min_resdis) 
     1201        CALL getin_p('MIN_DRAIN',min_drain) 
     1202        CALL getin_p('MAX_DRAIN',max_drain) 
     1203        CALL getin_p('EXP_DRAIN',exp_drain) 
     1204        CALL getin_p('RSOL_CSTE',rsol_cste) 
     1205        CALL getin_p('HCRIT_LITTER',hcrit_litter) 
     1206         
     1207        first_call =.FALSE. 
     1208         
     1209     ENDIF 
     1210      
     1211   END SUBROUTINE getin_hydrolc_parameters 
     1212    
     1213! 
     1214!= 
     1215! 
     1216   ! Subroutine called only if hydrol_cwrr is activated 
     1217    
     1218   SUBROUTINE getin_hydrol_cwrr_parameters 
     1219      
     1220     IMPLICIT NONE 
     1221      
     1222     LOGICAL, SAVE ::  first_call = .TRUE. 
     1223      
     1224     IF(first_call) THEN 
     1225         
     1226        CALL getin_p('W_TIME',w_time) 
     1227        CALL getin_p('NVAN',nvan)    
     1228        CALL getin_p('AVAN',avan) 
     1229        CALL getin_p('MCR',mcr) 
     1230        CALL getin_p('MCS',mcs) 
     1231        CALL getin_p('KS',ks) 
     1232        CALL getin_p('PCENT',pcent) 
     1233        CALL getin_p('FREE_DRAIN_MAX',free_drain_max) 
     1234        CALL getin_p('MCF',mcf) 
     1235        CALL getin_p('MCW',mcw) 
     1236        CALL getin_p('MC_AWET',mc_awet) 
     1237         
     1238        first_call =.FALSE. 
     1239         
     1240     ENDIF 
     1241 
     1242   END SUBROUTINE getin_hydrol_cwrr_parameters 
     1243! 
     1244!= 
     1245! 
     1246   SUBROUTINE getin_routing_parameters 
     1247      
     1248     IMPLICIT NONE 
     1249      
     1250     LOGICAL, SAVE ::  first_call = .TRUE. 
     1251      
     1252     IF(first_call) THEN 
     1253         
     1254        CALL getin_p('CROP_COEF',crop_coef) 
     1255         
     1256        first_call =.FALSE. 
     1257         
     1258     ENDIF 
     1259      
     1260   END SUBROUTINE getin_routing_parameters 
     1261! 
     1262!= 
     1263! 
     1264   SUBROUTINE getin_stomate_parameters 
     1265      
     1266    IMPLICIT NONE 
     1267     
     1268    LOGICAL, SAVE ::  first_call = .TRUE. 
     1269     
    10821270    IF(first_call) THEN 
    1083  
    1084        CALL getin('W_TIME',w_time) 
    1085        CALL getin('NVAN',nvan)    
    1086        CALL getin('AVAN',avan) 
    1087        CALL getin('MCR',mcr) 
    1088        CALL getin('MCS',mcs) 
    1089        CALL getin('KS',ks) 
    1090        CALL getin('PCENT',pcent) 
    1091        CALL getin('FREE_DRAIN_MAX',free_drain_max) 
    1092        CALL getin('MCF',mcf) 
    1093        CALL getin('MCW',mcw) 
    1094        CALL getin('MC_AWET',mc_awet) 
    1095  
    1096        first_call =.FALSE. 
    1097    
     1271        
     1272       ! constraints_parameters 
     1273       CALL getin_p('TOO_LONG',too_long) 
     1274       !- 
     1275       ! fire parameters 
     1276       CALL getin_p('TAU_FIRE',tau_fire) 
     1277       CALL getin_p('LITTER_CRIT',litter_crit) 
     1278       CALL getin_p('CO2FRAC',co2frac) 
     1279       CALL getin_p('BCFRAC_COEFF',bcfrac_coeff) 
     1280       CALL getin_p('FIREFRAC_COEFF',firefrac_coeff) 
     1281       !- 
     1282       ! gap parameters (+ lpj_const_mort) 
     1283       CALL getin_p('AVAILABILITY_FACT', availability_fact)   
     1284       CALL getin_p('VIGOUR_REF',vigour_ref) 
     1285       CALL getin_p('VIGOUR_COEFF',vigour_coeff)  
     1286       !- 
     1287       ! allocation parameters 
     1288       CALL getin_p('OK_MINRES',ok_minres) 
     1289       CALL getin_p('TAU_LEAFINIT', tau_leafinit) 
     1290       CALL getin_p('RESERVE_TIME_TREE',reserve_time_tree) 
     1291       CALL getin_p('RESERVE_TIME_GRASS',reserve_time_grass) 
     1292       CALL getin_p('R0',R0) 
     1293       CALL getin_p('S0',S0) 
     1294       CALL getin_p('F_FRUIT',f_fruit) 
     1295       CALL getin_p('ALLOC_SAP_ABOVE_TREE',alloc_sap_above_tree) 
     1296       CALL getin_p('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass) 
     1297       CALL getin_p('MIN_LTOLSR',min_LtoLSR) 
     1298       CALL getin_p('MAX_LTOLSR',max_LtoLSR) 
     1299       CALL getin_p('Z_NITROGEN',z_nitrogen) 
     1300       CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy) 
     1301       CALL getin_p('NLIM_TREF',Nlim_tref)    
     1302       !- 
     1303       ! data parameters 
     1304       CALL getin_p('PIPE_TUNE1',pipe_tune1) 
     1305       CALL getin_p('PIPE_TUNE2',pipe_tune2)    
     1306       CALL getin_p('PIPE_TUNE3',pipe_tune3) 
     1307       CALL getin_p('PIPE_TUNE4',pipe_tune4) 
     1308       CALL getin_p('PIPE_DENSITY',pipe_density) 
     1309       CALL getin_p('PIPE_K1',pipe_k1) 
     1310       CALL getin_p('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff) 
     1311       ! 
     1312       CALL getin_p('PRECIP_CRIT',precip_crit) 
     1313       CALL getin_p('GDD_CRIT_ESTAB',gdd_crit_estab)  
     1314       CALL getin_p('FPC_CRIT',fpc_crit) 
     1315       CALL getin_p('ALPHA_GRASS',alpha_grass) 
     1316       CALL getin_p('ALPHA_TREE',alpha_tree) 
     1317       !- 
     1318       CALL getin_p('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap) 
     1319       CALL getin_p('FRAC_GROWTHRESP',frac_growthresp) 
     1320       CALL getin_p('TAU_HUM_MONTH',tau_hum_month) 
     1321       CALL getin_p('TAU_HUM_WEEK',tau_hum_week) 
     1322       CALL getin_p('TAU_T2M_MONTH',tau_t2m_month) 
     1323       CALL getin_p('TAU_T2M_WEEK',tau_t2m_week) 
     1324       CALL getin_p('TAU_TSOIL_MONTH',tau_tsoil_month) 
     1325       CALL getin_p('TAU_SOILHUM_MONTH',tau_soilhum_month) 
     1326       CALL getin_p('TAU_GPP_WEEK',tau_gpp_week) 
     1327       CALL getin_p('TAU_GDD',tau_gdd) 
     1328       CALL getin_p('TAU_NGD',tau_ngd) 
     1329       CALL getin_p('COEFF_TAU_LONGTERM',coeff_tau_longterm) 
     1330       !- 
     1331       CALL getin_p('BM_SAPL_CARBRES',bm_sapl_carbres) 
     1332       CALL getin_p('BM_SAPL_SAPABOVE',bm_sapl_sapabove) 
     1333       CALL getin_p('BM_SAPL_HEARTABOVE',bm_sapl_heartabove) 
     1334       CALL getin_p('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow) 
     1335       CALL getin_p('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat) 
     1336       CALL getin_p('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri) 
     1337       CALL getin_p('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres) 
     1338       CALL getin_p('INIT_SAPL_MASS_ROOT',init_sapl_mass_root) 
     1339       CALL getin_p('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit) 
     1340       CALL getin_p('CN_SAPL_INIT',cn_sapl_init) 
     1341       CALL getin_p('MIGRATE_TREE',migrate_tree) 
     1342       CALL getin_p('MIGRATE_GRASS',migrate_grass) 
     1343       CALL getin_p('MAXDIA_COEFF',maxdia_coeff) 
     1344       CALL getin_p('LAI_INITMIN_TREE',lai_initmin_tree) 
     1345       CALL getin_p('LAI_INITMIN_GRASS',lai_initmin_grass) 
     1346       CALL getin_p('DIA_COEFF',dia_coeff) 
     1347       CALL getin_p('MAXDIA_COEFF',maxdia_coeff) 
     1348       CALL getin_p('BM_SAPL_LEAF',bm_sapl_leaf) 
     1349       !- 
     1350       ! litter parameters 
     1351       CALL getin_p('METABOLIC_REF_FRAC',metabolic_ref_frac) 
     1352       CALL getin_p('Z_DECOMP',z_decomp) 
     1353       CALL getin_p('CN',CN) 
     1354       CALL getin_p('LC',LC) 
     1355       CALL getin_p('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa) 
     1356       CALL getin_p('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab) 
     1357       CALL getin_p('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa) 
     1358       CALL getin_p('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb) 
     1359       CALL getin_p('FRAC_SOIL_METAB_AA',frac_soil_metab_aa) 
     1360       CALL getin_p('FRAC_SOIL_METAB_AB',frac_soil_metab_ab) 
     1361       ! 
     1362       CALL getin_p('METABOLIC_LN_RATIO',metabolic_LN_ratio)    
     1363       CALL getin_p('TAU_METABOLIC',tau_metabolic) 
     1364       CALL getin_p('TAU_STRUCT',tau_struct) 
     1365       CALL getin_p('SOIL_Q10',soil_Q10) 
     1366       CALL getin_p('TSOIL_REF',tsoil_ref) 
     1367       CALL getin_p('LITTER_STRUCT_COEF',litter_struct_coef) 
     1368       CALL getin_p('MOIST_COEFF',moist_coeff) 
     1369       !- 
     1370       ! lpj parameters 
     1371       CALL getin_p('FRAC_TURNOVER_DAILY',frac_turnover_daily)    
     1372       !- 
     1373       ! npp parameters 
     1374       CALL getin_p('TAX_MAX',tax_max)  
     1375       !- 
     1376       ! phenology parameters 
     1377       CALL getin_p('ALWAYS_INIT',always_init) 
     1378       CALL getin_p('MIN_GROWTHINIT_TIME',min_growthinit_time) 
     1379       CALL getin_p('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree) 
     1380       CALL getin_p('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass) 
     1381       CALL getin_p('T_ALWAYS_ADD',t_always_add) 
     1382       ! 
     1383       CALL getin_p('GDDNCD_REF',gddncd_ref) 
     1384       CALL getin_p('GDDNCD_CURVE',gddncd_curve) 
     1385       CALL getin_p('GDDNCD_OFFSET',gddncd_offset) 
     1386       !- 
     1387       ! prescribe parameters 
     1388       CALL getin_p('CN_TREE',cn_tree) 
     1389       CALL getin_p('BM_SAPL_RESCALE',bm_sapl_rescale) 
     1390       !- 
     1391       ! respiration parameters 
     1392       CALL getin_p('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax)   
     1393       CALL getin_p('MAINT_RESP_COEFF',maint_resp_coeff) 
     1394       !- 
     1395       ! soilcarbon parameters 
     1396       CALL getin_p('FRAC_CARB_AA',frac_carb_aa) 
     1397       CALL getin_p('FRAC_CARB_AP',frac_carb_ap)    
     1398       CALL getin_p('FRAC_CARB_SS',frac_carb_ss) 
     1399       CALL getin_p('FRAC_CARB_SA',frac_carb_sa) 
     1400       CALL getin_p('FRAC_CARB_SP',frac_carb_sp) 
     1401       CALL getin_p('FRAC_CARB_PP',frac_carb_pp) 
     1402       CALL getin_p('FRAC_CARB_PA',frac_carb_pa) 
     1403       CALL getin_p('FRAC_CARB_PS',frac_carb_ps) 
     1404       ! 
     1405       CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac) 
     1406       CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive) 
     1407       CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow) 
     1408       CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive) 
     1409       CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff) 
     1410       !- 
     1411       ! turnover parameters 
     1412       CALL getin_p('NEW_TURNOVER_TIME_REF',new_turnover_time_ref) 
     1413       CALL getin_p('DT_TURNOVER_TIME',dt_turnover_time) 
     1414       CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref) 
     1415       CALL getin_p('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff) 
     1416       !- 
     1417       ! vmax parameters 
     1418       CALL getin_p('VMAX_OFFSET',vmax_offset) 
     1419       CALL getin_p('LEAFAGE_FIRSTMAX',leafage_firstmax) 
     1420       CALL getin_p('LEAFAGE_LASTMAX',leafage_lastmax) 
     1421       CALL getin_p('LEAFAGE_OLD',leafage_old) 
     1422       !- 
     1423       ! season parameters 
     1424       CALL getin_p('GPPFRAC_DORMANCE',gppfrac_dormance) 
     1425       CALL getin_p('MIN_GPP_ALLOWED',min_gpp_allowed) 
     1426       CALL getin_p('TAU_CLIMATOLOGY',tau_climatology) 
     1427       CALL getin_p('HVC1',hvc1) 
     1428       CALL getin_p('HVC2',hvc2) 
     1429       CALL getin_p('LEAF_FRAC_HVC',leaf_frac_hvc) 
     1430       ! 
     1431       CALL getin_p('TLONG_REF_MAX',tlong_ref_max) 
     1432       CALL getin_p('TLONG_REF_MIN',tlong_ref_min) 
     1433       ! 
     1434       CALL getin_p('NCD_MAX_YEAR',ncd_max_year) 
     1435       CALL getin_p('GDD_THRESHOLD',gdd_threshold) 
     1436       CALL getin_p('GREEN_AGE_EVER',green_age_ever) 
     1437       CALL getin_p('GREEN_AGE_DEC',green_age_dec) 
     1438        
     1439       first_call = .FALSE. 
     1440        
    10981441    ENDIF 
    1099  
    1100   END SUBROUTINE getin_hydrol_cwrr_parameters 
    1101 !-------------------------------------------- 
    1102  
    1103   ! Subroutine called only if ok_co2 is activated 
    1104   ! only for diffuco_trans_co2 
    1105  
    1106   SUBROUTINE getin_co2_parameters 
    1107  
    1108   IMPLICIT NONE 
    1109  
    1110   LOGICAL, SAVE ::  first_call = .TRUE. 
    1111  
     1442     
     1443  END SUBROUTINE getin_stomate_parameters 
     1444! 
     1445!= 
     1446! 
     1447  SUBROUTINE getin_dgvm_parameters    
     1448     
     1449    IMPLICIT NONE 
     1450     
     1451    LOGICAL, SAVE ::  first_call = .TRUE. 
     1452     
    11121453    IF(first_call) THEN 
    1113  
    1114        CALL getin('LAI_LEVEL_DEPTH',lai_level_depth) 
    1115        CALL getin('X1_COEF',x1_coef) 
    1116        CALL getin('X1_Q10',x1_Q10) 
    1117        CALL getin('QUANTUM_YIELD',quantum_yield) 
    1118        CALL getin('KT_COEF',kt_coef) 
    1119        CALL getin('KC_COEF',kc_coef) 
    1120        CALL getin('KO_Q10',Ko_Q10) 
    1121        CALL getin('OA',Oa) 
    1122        CALL getin('KO_COEF',Ko_coef) 
    1123        CALL getin('CP_0',CP_0) 
    1124        CALL getin('CP_TEMP_COEF',cp_temp_coef) 
    1125        CALL getin('CP_TEMP_REF',cp_temp_ref) 
    1126        CALL getin('RT_COEF',rt_coef) 
    1127        CALL getin('VC_COEF',vc_coef) 
    1128  
    1129        first_call =.FALSE. 
    1130  
    1131    ENDIF 
    1132  
    1133   END SUBROUTINE getin_co2_parameters 
    1134  
    1135 !********************************************************** 
    1136  
    1137   ! Subroutine called only if stomate is activated 
    1138  
    1139   SUBROUTINE getin_stomate_parameters 
    1140  
    1141     IMPLICIT NONE 
    1142  
    1143     LOGICAL, SAVE ::  first_call = .TRUE. 
    1144  
    1145     IF(first_call) THEN 
     1454        
     1455       ! establish parameters 
     1456       CALL getin_p('ESTAB_MAX_TREE',estab_max_tree) 
     1457       CALL getin_p('ESTAB_MAX_GRASS',estab_max_grass) 
     1458       CALL getin_p('ESTABLISH_SCAL_FACT',establish_scal_fact) 
     1459       CALL getin_p('FPC_CRIT_MAX',fpc_crit_max) 
     1460       CALL getin_p('FPC_CRIT_MIN',fpc_crit_min) 
     1461       !- 
     1462       ! light parameters 
     1463       CALL getin_p('GRASS_MERCY',grass_mercy) 
     1464       CALL getin_p('TREE_MERCY',tree_mercy) 
     1465       CALL getin_p('ANNUAL_INCREASE',annual_increase) 
     1466       CALL getin_p('MIN_COVER',min_cover) 
     1467       !- 
     1468       ! pftinout parameters 
     1469       CALL getin_p('IND_0',ind_0) 
     1470       CALL getin_p('MIN_AVAIL',min_avail) 
     1471       CALL getin_p('RIP_TIME_MIN',RIP_time_min) 
     1472       CALL getin_p('NPP_LONGTERM_INIT',npp_longterm_init) 
     1473       CALL getin_p('EVERYWHERE_INIT',everywhere_init) 
     1474        
     1475       first_call = .FALSE. 
     1476        
     1477    ENDIF 
    11461478     
    1147        CALL getin('TOO_LONG',too_long) 
    1148        !- 
    1149        CALL getin('TAU_FIRE',tau_fire) 
    1150        CALL getin('LITTER_CRIT',litter_crit) 
    1151        !- 
    1152        CALL getin('OK_MINRES',ok_minres) 
    1153        CALL getin('TAU_LEAFINIT', tau_leafinit) 
    1154        CALL getin('RESERVE_TIME_TREE',reserve_time_tree) 
    1155        CALL getin('RESERVE_TIME_GRASS',reserve_time_grass) 
    1156        CALL getin('R0',R0) 
    1157        CALL getin('S0',S0) 
    1158        CALL getin('F_FRUIT',f_fruit) 
    1159        CALL getin('ALLOC_SAP_ABOVE_TREE',alloc_sap_above_tree) 
    1160        CALL getin('ALLOC_SAP_ABOVE_GRASS',alloc_sap_above_grass) 
    1161        CALL getin('MIN_LTOLSR',min_LtoLSR) 
    1162        CALL getin('MAX_LTOLSR',max_LtoLSR) 
    1163        CALL getin('Z_NITROGEN',z_nitrogen) 
    1164        !- 
    1165        CALL getin('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff) 
    1166        CALL getin('PIPE_TUNE1',pipe_tune1) 
    1167        CALL getin('PIPE_TUNE2',pipe_tune2)    
    1168        CALL getin('PIPE_TUNE3',pipe_tune3) 
    1169        CALL getin('PIPE_TUNE4',pipe_tune4) 
    1170        CALL getin('PIPE_DENSITY',pipe_density) 
    1171        CALL getin('PIPE_K1',pipe_k1) 
    1172        CALL getin('ESTAB_MAX_TREE',estab_max_tree) 
    1173        CALL getin('ESTAB_MAX_GRASS',estab_max_grass) 
    1174        CALL getin('IND_0',ind_0) 
    1175        CALL getin('MIN_COVER',min_cover) 
    1176        CALL getin('PRECIP_CRIT',precip_crit) 
    1177        CALL getin('GDD_CRIT_ESTAB',gdd_crit_estab)  
    1178        CALL getin('FPC_CRIT',fpc_crit) 
    1179        CALL getin('FRAC_GROWTHRESP',frac_growthresp) 
    1180        CALL getin('ALPHA_GRASS',alpha_grass) 
    1181        CALL getin('ALPHA_TREE',alpha_tree) 
    1182        CALL getin('TLONG_REF_MAX',tlong_ref_max) 
    1183        CALL getin('TLONG_REF_MIN',tlong_ref_min) 
    1184        !- 
    1185        CALL getin('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap) 
    1186        CALL getin('TAU_HUM_MONTH',tau_hum_month) 
    1187        CALL getin('TAU_HUM_WEEK',tau_hum_week) 
    1188        CALL getin('TAU_T2M_MONTH',tau_t2m_month) 
    1189        CALL getin('TAU_T2M_WEEK',tau_t2m_week) 
    1190        CALL getin('TAU_TSOIL_MONTH',tau_tsoil_month) 
    1191        CALL getin('TAU_SOILHUM_MONTH',tau_soilhum_month) 
    1192        CALL getin('TAU_GPP_WEEK',tau_gpp_week) 
    1193        CALL getin('TAU_GDD',tau_gdd) 
    1194        CALL getin('TAU_NGD',tau_ngd) 
    1195        CALL getin('COEFF_TAU_LONGTERM',coeff_tau_longterm) 
    1196        ! 
    1197        CALL getin('FRAC_TURNOVER_DAILY',frac_turnover_daily) 
    1198        !- 
    1199        CALL getin('Z_DECOMP',z_decomp) 
    1200        !- 
    1201        CALL getin('TAX_MAX',tax_max) 
    1202        !- 
    1203        CALL getin('ALWAYS_INIT',always_init) 
    1204        CALL getin('MIN_GROWTHINIT_TIME',min_growthinit_time) 
    1205        CALL getin('MOIAVAIL_ALWAYS_TREE',moiavail_always_tree) 
    1206        CALL getin('MOIAVAIL_ALWAYS_GRASS',moiavail_always_grass) 
    1207        CALL getin('T_ALWAYS_ADD',t_always_add) 
    1208        !- 
    1209        CALL getin('VMAX_OFFSET',vmax_offset) 
    1210        CALL getin('LEAFAGE_FIRSTMAX',leafage_firstmax) 
    1211        CALL getin('LEAFAGE_LASTMAX',leafage_lastmax) 
    1212        CALL getin('LEAFAGE_OLD',leafage_old) 
    1213        !- 
    1214        CALL getin('GPPFRAC_DORMANCE',gppfrac_dormance) 
    1215        CALL getin('MIN_GPP_ALLOWED',min_gpp_allowed) 
    1216        CALL getin('TAU_CLIMATOLOGY',tau_climatology) 
    1217        CALL getin('HVC1',hvc1) 
    1218        CALL getin('HVC2',hvc2) 
    1219        CALL getin('LEAF_FRAC_HVC',leaf_frac_hvc) 
    1220        !- 
    1221        CALL getin('CO2FRAC',co2frac) 
    1222        CALL getin('CN',CN) 
    1223        CALL getin('LC',LC) 
    1224        !- 
    1225        CALL getin('FRAC_SOIL_STRUCT_AA',frac_soil_struct_aa) 
    1226        CALL getin('FRAC_SOIL_STRUCT_AB',frac_soil_struct_ab) 
    1227        CALL getin('FRAC_SOIL_STRUCT_SA',frac_soil_struct_sa) 
    1228        CALL getin('FRAC_SOIL_STRUCT_SB',frac_soil_struct_sb) 
    1229        CALL getin('FRAC_SOIL_METAB_AA',frac_soil_metab_aa) 
    1230        CALL getin('FRAC_SOIL_METAB_AB',frac_soil_metab_ab) 
    1231        !- 
    1232        CALL getin('FRAC_CARB_AA',frac_carb_aa) 
    1233        CALL getin('FRAC_CARB_AP',frac_carb_ap)    
    1234        CALL getin('FRAC_CARB_SS',frac_carb_ss) 
    1235        CALL getin('FRAC_CARB_SA',frac_carb_sa) 
    1236        CALL getin('FRAC_CARB_SP',frac_carb_sp) 
    1237        CALL getin('FRAC_CARB_PP',frac_carb_pp) 
    1238        CALL getin('FRAC_CARB_PA',frac_carb_pa) 
    1239        CALL getin('FRAC_CARB_PS',frac_carb_ps) 
    1240  
    1241        !--------------------------------------- 
    1242        ! COEFFICIENTS OF EQUATIONS 
    1243        !------------------------------------- 
    1244        ! 
    1245        !- 
    1246        CALL getin('BCFRAC_COEFF',bcfrac_coeff) 
    1247        CALL getin('FIREFRAC_COEFF',firefrac_coeff) 
    1248        !- 
    1249        CALL getin('AVAILABILITY_FACT', availability_fact)   
    1250        CALL getin('VIGOUR_REF',vigour_ref) 
    1251        CALL getin('VIGOUR_COEFF',vigour_coeff) 
    1252        !- 
    1253        CALL getin('RIP_TIME_MIN',RIP_time_min) 
    1254        CALL getin('NPP_LONGTERM_INIT',npp_longterm_init) 
    1255        CALL getin('EVERYWHERE_INIT',everywhere_init) 
    1256        ! 
    1257        !- 
    1258        CALL getin('LAI_MAX_TO_HAPPY',lai_max_to_happy) 
    1259        CALL getin('NLIM_TREF',Nlim_tref)    
    1260        !- 
    1261        CALL getin('BM_SAPL_CARBRES',bm_sapl_carbres) 
    1262        CALL getin('BM_SAPL_SAPABOVE',bm_sapl_sapabove) 
    1263        CALL getin('BM_SAPL_HEARTABOVE',bm_sapl_heartabove) 
    1264        CALL getin('BM_SAPL_HEARTBELOW',bm_sapl_heartbelow) 
    1265        CALL getin('INIT_SAPL_MASS_LEAF_NAT',init_sapl_mass_leaf_nat) 
    1266        CALL getin('INIT_SAPL_MASS_LEAF_AGRI',init_sapl_mass_leaf_agri) 
    1267        CALL getin('INIT_SAPL_MASS_CARBRES',init_sapl_mass_carbres) 
    1268        CALL getin('INIT_SAPL_MASS_ROOT',init_sapl_mass_root) 
    1269        CALL getin('INIT_SAPL_MASS_FRUIT',init_sapl_mass_fruit) 
    1270        CALL getin('CN_SAPL_INIT',cn_sapl_init) 
    1271        CALL getin('MIGRATE_TREE',migrate_tree) 
    1272        CALL getin('MIGRATE_GRASS',migrate_grass) 
    1273        CALL getin('MAXDIA_COEFF',maxdia_coeff) 
    1274        CALL getin('LAI_INITMIN_TREE',lai_initmin_tree) 
    1275        CALL getin('LAI_INITMIN_GRASS',lai_initmin_grass) 
    1276        CALL getin('DIA_COEFF',dia_coeff) 
    1277        CALL getin('MAXDIA_COEFF',maxdia_coeff) 
    1278        CALL getin('BM_SAPL_LEAF',bm_sapl_leaf) 
    1279        !- 
    1280        CALL getin('METABOLIC_REF_FRAC',metabolic_ref_frac) 
    1281        CALL getin('METABOLIC_LN_RATIO',metabolic_LN_ratio)    
    1282        CALL getin('TAU_METABOLIC',tau_metabolic) 
    1283        CALL getin('TAU_STRUCT',tau_struct) 
    1284        CALL getin('SOIL_Q10',soil_Q10) 
    1285        CALL getin('TSOIL_REF',tsoil_ref) 
    1286        CALL getin('LITTER_STRUCT_COEF',litter_struct_coef) 
    1287        CALL getin('MOIST_COEFF',moist_coeff) 
    1288        !- 
    1289        CALL getin('GDDNCD_REF',gddncd_ref) 
    1290        CALL getin('GDDNCD_CURVE',gddncd_curve) 
    1291        CALL getin('GDDNCD_OFFSET',gddncd_offset) 
    1292        !- 
    1293        CALL getin('CN_TREE',cn_tree) 
    1294        CALL getin('BM_SAPL_RESCALE',bm_sapl_rescale) 
    1295        !- 
    1296        CALL getin('MAINT_RESP_MIN_VMAX',maint_resp_min_vmax)   
    1297        CALL getin('MAINT_RESP_COEFF',maint_resp_coeff) 
    1298        !- 
    1299        CALL getin('NCD_MAX_YEAR',ncd_max_year) 
    1300        CALL getin('GDD_THRESHOLD',gdd_threshold) 
    1301        CALL getin('GREEN_AGE_EVER',green_age_ever) 
    1302        CALL getin('GREEN_AGE_DEC',green_age_dec) 
    1303        !- 
    1304        CALL getin('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac) 
    1305        CALL getin('CARBON_TAU_IACTIVE',carbon_tau_iactive) 
    1306        CALL getin('CARBON_TAU_ISLOW',carbon_tau_islow) 
    1307        CALL getin('CARBON_TAU_IPASSIVE',carbon_tau_ipassive) 
    1308        CALL getin('FLUX_TOT_COEFF',flux_tot_coeff) 
    1309        !- 
    1310        CALL getin('NEW_TURNOVER_TIME_REF',new_turnover_time_ref) 
    1311        CALL getin('DT_TURNOVER_TIME',dt_turnover_time) 
    1312        CALL getin('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref) 
    1313        CALL getin('LEAF_AGE_CRIT_COEFF',leaf_age_crit_coeff) 
    1314  
    1315        first_call = .FALSE. 
    1316  
    1317     ENDIF 
    1318  
    1319  END SUBROUTINE getin_stomate_parameters 
    1320  
    1321 !****************************************** 
    1322  
    1323  SUBROUTINE getin_dgvm_parameters    
    1324     
    1325    IMPLICIT NONE 
    1326  
    1327     LOGICAL, SAVE ::  first_call = .TRUE. 
    1328  
    1329     IF(first_call) THEN 
    1330  
    1331           CALL getin('ESTABLISH_SCAL_FACT',establish_scal_fact) 
    1332           CALL getin('FPC_CRIT_MAX',fpc_crit_max) 
    1333           CALL getin('FPC_CRIT_MIN',fpc_crit_min) 
    1334           ! 
    1335           CALL getin('GRASS_MERCY',grass_mercy) 
    1336           CALL getin('TREE_MERCY',tree_mercy) 
    1337           CALL getin('ANNUAL_INCREASE',annual_increase) 
    1338           ! 
    1339           CALL getin('MIN_AVAIL',min_avail) 
    1340           CALL getin('RIP_TIME_MIN',RIP_time_min) 
    1341           CALL getin('NPP_LONGTERM_INIT',npp_longterm_init) 
    1342           CALL getin('EVERYWHERE_INIT',everywhere_init) 
    1343  
    1344           first_call = .FALSE. 
    1345         
    1346      ENDIF 
    1347  
    1348  
    1349    END SUBROUTINE getin_dgvm_parameters 
     1479     
     1480  END SUBROUTINE getin_dgvm_parameters 
     1481 
    13501482 
    13511483!-------------------- 
Note: See TracChangeset for help on using the changeset viewer.