Ignore:
Timestamp:
2024-02-12T19:49:09+01:00 (11 months ago)
Author:
bertrand.guenet
Message:

The Moyano function describing the soil moisture effect on OM decomposition is added

Location:
branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate.f90

    r7326 r8418  
    644644         rest_id_stom,   hist_id_stom,      hist_id_stom_IPCC,               & 
    645645         index,          lalo,              neighbours,   resolution,        & 
    646          contfrac,       totfrac_nobio,     clay,         temp_air,          & 
    647          lai,            veget,             veget_max,                       & 
     646         contfrac,       totfrac_nobio,     clay,         bulk,              & 
     647         temp_air,       lai,               veget,        veget_max,         & 
    648648         deadleaf_cover,    assim_param,  temp_growth ) 
    649649 
     
    665665    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: totfrac_nobio     !! Fraction of grid cell covered by lakes, land ice, cities, ... (unitless)  
    666666    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless) 
     667    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: bulk              !! Bulk density (kg/m**3)   
    667668    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: temp_air          !! Air temperature at first atmospheric model layer (K) 
    668669    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: lai               !! Leaf area inex @tex $(m^2 m^{-2})$ @endtex 
     
    11881189       & (kjit, kjpij, kjpindex, & 
    11891190       &  index, lalo, neighbours, resolution, contfrac, totfrac_nobio, clay, & 
    1190        &  temp_air, temp_sol, stempdiag, & 
    1191        &  humrel, shumdiag, litterhumdiag, precip_rain, precip_snow, & 
     1191       &  bulk, temp_air, temp_sol, stempdiag, & 
     1192       &  humrel, shumdiag,shumdiagSAT, litterhumdiag,litterhumdiagSAT, precip_rain, precip_snow, & 
    11921193       &  gpp, deadleaf_cover, assim_param, & 
    11931194       &  lai, frac_age, height, veget, veget_max, & 
     
    12251226                                                                         !! ice, cities, ... (unitless)  
    12261227    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless) 
     1228    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: bulk              !! Bulk density (kg/m**3)   
    12271229    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: humrel            !! Relative humidity ("moisture availability")  
    12281230                                                                         !! (0-1, unitless)  
     
    12311233    REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: stempdiag         !! Soil temperature (K) 
    12321234    REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: shumdiag          !! Relative soil moisture (0-1, unitless) 
     1235    REAL(r_std),DIMENSION(kjpindex,nslm),INTENT(in) :: shumdiagSAT       !! Relative soil moisture (0-1, unitless) 
     1236                                                                         !! with respect to(mcs-mcw) 
    12331237    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: litterhumdiag     !! Litter humidity (0-1, unitless) 
     1238    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: litterhumdiagSAT  !! Litter humidity (0-1, unitless) 
     1239                                                                         !! with respect to(tmc_litter_sat-tmc_litter_wilt) 
    12341240    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: precip_rain       !! Rain precipitation   
    12351241                                                                         !! @tex $(mm dt_stomate^{-1})$ @endtex  
     
    13691375 
    13701376!_ ================================================================================================================================ 
    1371      
     1377    
     1378  
    13721379  !! 1. Initialize variables 
    13731380 
     
    14871494    CALL littercalc (kjpindex, & 
    14881495         turnover_littercalc, bm_to_littercalc, & 
    1489          veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag, & 
     1496         veget_cov_max, temp_sol, stempdiag, shumdiag, litterhumdiag,shumdiagSAT,litterhumdiagSAT, & 
    14901497         litterpart, litter, dead_leaves, lignin_struc, & 
    14911498         deadleaf_cover, resp_hetero_litter, & 
    14921499         soilcarbon_input_inst, control_temp_inst, control_moist_inst, & 
    1493          matrixA, vectorB) 
     1500         matrixA, vectorB, bulk, clay, carbon) 
    14941501     
    14951502    ! Heterothropic litter respiration during time step ::dt_sechiba @tex $(gC m^{-2})$ @endtex 
     
    15511558            &          (kjpindex, dt_days, & 
    15521559            &           veget_cov, veget_cov_max, & 
    1553             &           humrel_daily, t2m_daily, tsoil_daily, soilhum_daily, lalo, & 
     1560            &           humrel_daily, t2m_daily, tsoil_daily, & 
     1561            &           soilhum_daily, lalo, & 
    15541562            &           precip_daily, npp_daily, biomass, & 
    15551563            &           turnover_daily, gpp_daily, when_growthinit, & 
     
    15621570            &           maxfpc_lastyear, maxfpc_thisyear, & 
    15631571            &           humrel_month, humrel_week, t2m_longterm, tau_longterm, & 
    1564             &           t2m_month, t2m_week, tsoil_month, soilhum_month, & 
     1572            &           t2m_month, t2m_week, tsoil_month,soilhum_month, & 
    15651573            &           npp_longterm, turnover_longterm, gpp_week, & 
    15661574            &           gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, & 
     
    15841592            &             clay, herbivores, & 
    15851593            &             tsurf_daily, tsoil_daily, t2m_daily, t2m_min_daily, & 
    1586             &             litterhum_daily, soilhum_daily, & 
     1594            &             litterhum_daily, soilhum_daily,  & 
    15871595            &             maxhumrel_lastyear, minhumrel_lastyear, & 
    15881596            &             gdd0_lastyear, precip_lastyear, & 
     
    20132021!_ ================================================================================================================================ 
    20142022 
    2015   SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, assim_param)  
     2023  SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, bulk, assim_param)  
    20162024     
    20172025    IMPLICIT NONE 
     
    20232031    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! Indices of the terrestrial pixels only (unitless) 
    20242032    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless) 
     2033    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: bulk              !! Bulk density (kg/m**3) 
    20252034    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(in) :: assim_param  !! min+max+opt temperatures (K) & vmax for photosynthesis   
    20262035 
     
    21092118         dt_days, days_since_beg, & 
    21102119         ind, adapted, regenerate, & 
    2111          humrel_daily, gdd_init_date, litterhum_daily, & 
     2120         humrel_daily, gdd_init_date, litterhum_daily,& 
    21122121         t2m_daily, t2m_min_daily, tsurf_daily, tsoil_daily, & 
    21132122         soilhum_daily, precip_daily, & 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_io.f90

    r7326 r8418  
    440440         &              .TRUE., litterhum_daily, 'gather', nbp_glo, index_g) 
    441441    IF (ALL(litterhum_daily(:) == val_exp)) litterhum_daily(:) = zero 
     442 
    442443    !- 
    443444    t2m_daily(:) = val_exp 
     
    471472         &                .TRUE., soilhum_daily, 'gather', nbp_glo, index_g) 
    472473    IF (ALL(soilhum_daily(:,:) == val_exp)) soilhum_daily(:,:) = zero 
     474 
    473475    !- 
    474476    precip_daily(:) = val_exp 
     
    604606         &              .TRUE., soilhum_month, 'gather', nbp_glo, index_g) 
    605607    IF (ALL(soilhum_month(:,:) == val_exp)) soilhum_month(:,:) = zero 
     608 
     609 
    606610    !- 
    607611    ! 6 fire probability 
     
    993997             CALL restget_p (rest_id_stomate, var_name, nbp_glo, nlitt , 1, itime, & 
    994998                  &                     .TRUE., litter(:,:,m,l,k), 'gather', nbp_glo, index_g) 
    995              IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = zero 
     999             IF (ok_moyano_soilhumsat)THEN 
     1000               IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = Litterini_Moyano 
     1001             ELSE 
     1002               IF (ALL(litter(:,:,m,l,k) == val_exp)) litter(:,:,m,l,k) = zero 
     1003             ENDIF 
    9961004          ENDDO 
    9971005       ENDDO 
     
    10131021       CALL restget_p (rest_id_stomate, var_name, nbp_glo, ncarb , 1, itime, & 
    10141022            &                   .TRUE., carbon(:,:,m), 'gather', nbp_glo, index_g) 
    1015        IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = zero 
     1023       IF (ok_moyano_soilhumsat)THEN  
     1024          IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = Cini_Moyano 
     1025       ELSE 
     1026          IF (ALL(carbon(:,:,m) == val_exp)) carbon(:,:,m) = zero 
     1027       ENDIF 
    10161028    ENDDO 
    10171029    !- 
     
    16891701    var_name = 't2m_daily' 
    16901702    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, & 
    1691          &                t2m_daily, 'scatter', nbp_glo, index_g) 
     1703                    &                t2m_daily, 'scatter', nbp_glo, index_g) 
    16921704    !- 
    16931705    var_name = 't2m_min_daily' 
    16941706    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, & 
    1695          &                t2m_min_daily, 'scatter', nbp_glo, index_g) 
     1707                    &                t2m_min_daily, 'scatter', nbp_glo, index_g) 
    16961708    !- 
    16971709    var_name = 'tsurf_daily' 
    16981710    CALL restput_p (rest_id_stomate, var_name, nbp_glo,    1, 1, itime, & 
    1699          &                tsurf_daily, 'scatter', nbp_glo, index_g) 
     1711                    &                tsurf_daily, 'scatter', nbp_glo, index_g) 
    17001712    !- 
    17011713    var_name = 'tsoil_daily' 
    17021714    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nslm, 1, itime, & 
    1703          &                tsoil_daily, 'scatter', nbp_glo, index_g) 
     1715                    &                tsoil_daily, 'scatter', nbp_glo, index_g) 
    17041716    !- 
    17051717    var_name = 'soilhum_daily' 
Note: See TracChangeset for help on using the changeset viewer.