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

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/slowproc.f90

    r7709 r8418  
    7272  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: siltfraction        !! Siltfraction (0-1, unitless) 
    7373!$OMP THREADPRIVATE(siltfraction)   
     74  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      :: bulk                !!Bulk density (kg/m**3)  
     75!$OMP THREADPRIVATE(bulk)    
    7476  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:,:)  :: laimap              !! LAI map when the LAI is prescribed and not calculated by STOMATE 
    7577!$OMP THREADPRIVATE(laimap) 
     
    137139     
    138140    !! 2. Prepare for reading of PFTmap file 
     141         !!  
     142         !! 2.1 Prepare for reading of bulk variable  
     143         !!  
     144     IF (ok_moyano_soilhumsat) THEN  
     145         ! Get the file name from run.def file and set file attributes accordingly  
     146         filename = 'soil_bulk_and_ph.nc'   
     147         CALL getin_p('SOIL_BULK_FILE',filename)   
     148         name = filename(1:LEN_TRIM(FILENAME)-3)  
     149         CALL xios_orchidee_set_file_attr("soilbulk_file",name=name)  
     150       
     151         ! Set variables that can be used in the xml files  
     152         lerr=xios_orchidee_setvar('bulk_default',bulk_default)  
     153           
     154         ! Determine if the file will be read by XIOS. If not,deactivate reading of the file.      
     155         IF (xios_interpolation .AND. restname_in=='NONE' .AND. .NOT. impsoilt) THEN  
     156            ! Reading will be done with XIOS later  
     157            IF (printlev>=2) WRITE(numout,*) 'Reading of soilbulk file will be done later using XIOS. The filename is ', filename  
     158        ELSE  
     159            ! No reading by XIOS, deactivate soilbulk file and related variables declared in context_input_orchidee.xml.  
     160            ! If this is not done, the model will crash if the file is not available in the run directory.  
     161            IF (printlev>=2) WRITE(numout,*) 'Reading of soil_bulk file will not be done with XIOS.'  
     162            CALL xios_orchidee_set_file_attr("soilbulk_file",enabled=.FALSE.)  
     163            CALL xios_orchidee_set_field_attr("soilbulk",enabled=.FALSE.)  
     164            CALL xios_orchidee_set_field_attr("soilbulk_mask",enabled=.FALSE.)  
     165         END IF  
     166     ELSE 
     167         ! Not needed if the flag is not activated, deactivate soilbulk file and related variables 
     168         ! declared in context_input_orchidee.xml.  
     169         ! If this is not done, the model will crash if the file is not 
     170         ! available in the run directory.  
     171         IF (printlev>=2) WRITE(numout,*) 'Reading of soil_bulk file will not be done with XIOS.' 
     172         CALL xios_orchidee_set_file_attr("soilbulk_file",enabled=.FALSE.) 
     173         CALL xios_orchidee_set_field_attr("soilbulk",enabled=.FALSE.) 
     174         CALL xios_orchidee_set_field_attr("soilbulk_mask",enabled=.FALSE.) 
     175      END IF 
     176           
     177    !!  
     178    !! 2.2 Prepare for reading of PFTmap file  
     179    !!  
     180 
    139181    filename = 'PFTmap.nc' 
    140182    CALL getin_p('VEGETATION_FILE',filename) 
     
    377419             rest_id_stom,   hist_id_stom,           hist_id_stom_IPCC,               & 
    378420             indexLand,      lalo,                   neighbours,   resolution,        & 
    379              contfrac,       totfrac_nobio,          clayfraction, temp_air,          & 
    380              lai,            veget,                  veget_max,                       & 
     421             contfrac,       totfrac_nobio,          clayfraction, bulk,              & 
     422             temp_air,       lai,                    veget,        veget_max,         & 
    381423             deadleaf_cover,         assim_param,  temp_growth ) 
    382424    ENDIF 
     
    478520  SUBROUTINE slowproc_main (kjit, kjpij, kjpindex, & 
    479521       IndexLand, indexveg, lalo, neighbours, resolution, contfrac, soiltile, fraclut, nwdFraclut, & 
    480        temp_air, temp_sol, stempdiag, & 
     522       temp_air, temp_sol, stempdiag, shumdiagSAT,litterhumdiagSAT, & 
    481523       humrel, shumdiag, litterhumdiag, precip_rain, precip_snow, gpp, & 
    482524       deadleaf_cover, & 
     
    511553    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in)  :: stempdiag           !! Soil temperature (K) 
    512554    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in)  :: shumdiag            !! Relative soil moisture (0-1, unitless) 
     555    REAL(r_std),DIMENSION (kjpindex,nslm), INTENT (in)  :: shumdiagSAT         !! Relative soil moisture (0-1, unitless) 
     556                                                                               !! with respect to(mcs-mcw) 
    513557    REAL(r_std),DIMENSION (kjpindex), INTENT (in)       :: litterhumdiag       !! Litter humidity  (0-1, unitless) 
     558    REAL(r_std),DIMENSION (kjpindex), INTENT (in)       :: litterhumdiagSAT    !! Litter humidity  (0-1, unitless)  
     559                                                                               !!with respect to(tmc_litter_sat-tmc_litter_wilt) 
    514560    REAL(r_std),DIMENSION (kjpindex), INTENT (in)       :: precip_rain         !! Rain precipitation (mm dt_stomate^{-1}) 
    515561    REAL(r_std),DIMENSION (kjpindex), INTENT (in)       :: precip_snow         !! Snow precipitation (mm dt_stomate^{-1}) 
     
    627673 
    628674       !! 4.1 Call stomate main routine that will call all c-cycle routines       ! 
     675 
    629676       CALL stomate_main (kjit, kjpij, kjpindex, & 
    630677            IndexLand, lalo, neighbours, resolution, contfrac, totfrac_nobio, clayfraction, & 
    631             temp_air, temp_sol, stempdiag, & 
    632             humrel, shumdiag, litterhumdiag, precip_rain, precip_snow, gpp, & 
     678            bulk, temp_air, temp_sol, stempdiag, humrel, shumdiag, shumdiagSAT, litterhumdiag, & 
     679            litterhumdiagSAT, precip_rain, precip_snow, gpp, & 
    633680            deadleaf_cover, & 
    634681            assim_param, & 
     
    638685            co2_flux, fco2_lu, fco2_wh, fco2_ha, & 
    639686            resp_maint, resp_hetero, resp_growth, temp_growth) 
    640  
    641687 
    642688       !! 4.2 Output the respiration terms and the net primary 
     
    865911    ! counter, vegetation fraction, max vegetation fraction, LAI 
    866912    ! variable from stomate, fraction of bare soil, soiltype 
    867     ! fraction, clay fraction, height of vegetation, map of LAI 
     913    ! fraction, clay fraction,bulk density, height of vegetation, map of LAI 
    868914     
    869915    CALL restput_p (rest_id, 'veget', nbp_glo, nvm, 1, kjit, veget, 'scatter',  nbp_glo, index_g) 
     
    904950    CALL restput_p (rest_id, 'clay_frac', nbp_glo, 1, 1, kjit, clayfraction, 'scatter',  nbp_glo, index_g) 
    905951    CALL restput_p (rest_id, 'sand_frac', nbp_glo, 1, 1, kjit, sandfraction, 'scatter',  nbp_glo, index_g) 
     952    CALL restput_p (rest_id, 'bulk', nbp_glo, 1, 1, kjit, bulk, 'scatter',  nbp_glo,index_g)  
    906953    !salma: added the following lines for restput of the soil parameters 
    907954    CALL restput_p (rest_id, 'ks', nbp_glo, 1, 1, kjit, ks, 'scatter',  nbp_glo, index_g) 
     
    929976    ! 2.2 Write restart variables managed by STOMATE 
    930977    IF ( ok_stomate ) THEN 
    931        CALL stomate_finalize (kjit, kjpindex, indexLand, clayfraction, assim_param)  
     978       CALL stomate_finalize (kjit, kjpindex, indexLand, clayfraction, bulk, assim_param)  
    932979    ENDIF 
    933980     
     
    10571104    siltfraction(:)=undef_sechiba 
    10581105 
     1106    ALLOCATE (bulk(kjpindex),stat=ier) 
     1107    IF (ier /= 0) CALL ipslerr_p(3,'slowproc_init','Problem in allocation of variable bulk','','') 
     1108    bulk(:)=undef_sechiba 
     1109 
    10591110    ! Allocation of last year vegetation fraction in case of land use change 
    10601111    ALLOCATE(veget_max_new(kjpindex, nvm), STAT=ier) 
     
    13571408          CALL slowproc_soilt(njsc, ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, & 
    13581409               lalo, neighbours, resolution, contfrac, soilclass, & 
    1359                clayfraction, sandfraction, siltfraction) 
     1410               clayfraction, sandfraction, siltfraction, bulk) 
    13601411           
    13611412          call_slowproc_soilt=.FALSE. 
     
    15361587    ENDIF 
    15371588 
     1589    var_name= 'bulk'  
     1590    CALL ioconf_setatt_p('UNITS', '-') 
     1591    CALL ioconf_setatt_p('LONG_NAME','Bulk density in each mesh') 
     1592    CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., bulk, "gather", nbp_glo, index_g)  
     1593 
    15381594    var_name= 'lai' 
    15391595    CALL ioconf_setatt_p('UNITS', '-') 
     
    16111667       !Config Units = [-] 
    16121668       CALL setvar_p (lai, val_exp, 'SECHIBA_LAI', llaimax) 
     1669 
     1670       !Config Key   = BULK   
     1671       !Config Desc  = Bulk density (0-dim mode)  
     1672       !Config Def   = XXX  
     1673       !Config If    = IMPOSE_VEG and IMPOSE_SOIL  
     1674       !Config Help  = Determines the bulk density in the grid box.  The bulk density  
     1675       !Config         is the weight of soil in a given volume.  
     1676       !Config Units = [-]   
     1677       CALL setvar_p (bulk, val_exp, 'BULK', bulk_default)  
    16131678 
    16141679       !Config Key   = SLOWPROC_HEIGHT 
     
    17231788    ENDIF 
    17241789     
    1725  
    17261790    !! 4.3 Dynamic irrigation map 
    17271791    !  If do_irrigation, it will look to the dynamical irrig. map in restart 
     
    18431907    IF (ALLOCATED (sandfraction)) DEALLOCATE (sandfraction) 
    18441908    IF (ALLOCATED (siltfraction)) DEALLOCATE (siltfraction) 
     1909    IF (ALLOCATED (bulk)) DEALLOCATE (bulk)  
    18451910    IF (ALLOCATED (laimap)) DEALLOCATE (laimap) 
    18461911    IF (ALLOCATED (veget_max_new)) DEALLOCATE (veget_max_new) 
     
    25312596    END IF  
    25322597 
    2533     ! Assigning the right values and giving a value where information was not found 
     2598    ! Assiggning the right values and giving a value where information was not found 
    25342599    DO ib=1,nbpt 
    25352600      IF (alaimap(ib) < min_sechiba) THEN 
     
    29312996!>\BRIEF         looks for nearest grid point on the fine map 
    29322997!! 
    2933 !! DESCRIPTION  : (definitions, functional, design, flags):  
    2934 !! 
     2998!! DESCRIPTION  : (definitions, functional, design, flags): 
     2999!!            
    29353000!! RECENT CHANGE(S): None 
    29363001!! 
     
    30033068!! 
    30043069!>\BRIEF         Interpolate the Zobler or Reynolds/USDA soil type map 
     3070!!               Read and interpolate soil bulk from file.  
    30053071!! 
    30063072!! DESCRIPTION  : (definitions, functional, design, flags):  
     
    30103076!!                             and everything needed to read all maps and assign parameter values.   
    30113077!! 
    3012 !! MAIN OUTPUT VARIABLE(S): ::soiltype, ::clayfraction, sandfraction, siltfraction 
     3078!! MAIN OUTPUT VARIABLE(S): ::soiltype, ::clayfraction, sandfraction, siltfraction, bulk 
    30133079!! 
    30143080!! REFERENCE(S) : Reynold, Jackson, and Rawls (2000). Estimating soil water-holding capacities  
     
    30193085!! \n 
    30203086!_ ================================================================================================================================ 
    3021   SUBROUTINE slowproc_soilt(njsc,  ks,  nvan, avan, mcr, mcs, mcfc, mcw, nbpt, lalo, neighbours, resolution, contfrac, soilclass, clayfraction, sandfraction, siltfraction) 
     3087  SUBROUTINE slowproc_soilt(njsc,  ks,  nvan, avan, mcr, mcs, mcfc, mcw, nbpt, lalo, neighbours, resolution, contfrac, soilclass, clayfraction, sandfraction, siltfraction, bulk) 
    30223088 
    30233089    USE interpweight 
     
    30613127    REAL(r_std), INTENT(out)      :: sandfraction(nbpt)     !! The fraction of sand (for SP-MIP) 
    30623128    REAL(r_std), INTENT(out)      :: siltfraction(nbpt)     !! The fraction of silt (for SP-MIP) 
     3129    REAL(r_std), INTENT(out)      :: bulk(nbpt)             !! Bulk density  as used by STOMATE  
    30633130    ! 
    30643131    ! 
     
    30883155    CHARACTER(LEN=80)                                    :: spmipexp          !! designing the number of sp-mip experiment 
    30893156    CHARACTER(LEN=80)                                    :: unif_case               !! designing the model of experiment 4 (sp_mip) 
    3090  
     3157    REAL(r_std), DIMENSION(nbpt)                         :: abulkph          !!Availability of the bulk and ph interpolation  
    30913158    REAL(r_std)                                          :: vmin, vmax       !! min/max values to use for the  
    30923159 
     
    31133180                                                                             !!   `maskingtype')  
    31143181    CHARACTER(LEN=250)                                   :: namemaskvar      !! name of the variable to use to mask  
     3182    CHARACTER(LEN=80)                                    :: fieldname        !!name of the field read for the bulk density map 
    31153183    INTEGER(i_std), DIMENSION(:), ALLOCATABLE            :: vecpos 
    31163184    REAL(r_std)                                          :: sgn              !! sum of fractions excluding glaciers and ocean 
     
    36373705                      IF ( (solt(ilf) .LE. nscm) .AND. (solt(ilf) .GT. 0) ) THEN 
    36383706                         soilclass(ib,solt(ilf)) = textrefrac(ib,solt(ilf)) 
    3639                          clayfraction(ib) = clayfraction(ib) + textfrac_table(solt(ilf),3) *                & 
     3707                         clayfraction(ib) = clayfraction(ib) + textfrac_table(solt(ilf),3) * & 
    36403708                              textrefrac(ib,solt(ilf)) 
    36413709                         sandfraction(ib) = sandfraction(ib) + textfrac_table(solt(ilf),2) * & 
     
    36883756 
    36893757       ENDIF        !      xios_interpolation 
     3758 
     3759    !!  
     3760    !! Read and interpolate soil bulk and soil ph using IOIPSL or XIOS  
     3761    !! 
     3762    IF (ok_moyano_soilhumsat) THEN 
     3763       IF (xios_interpolation) THEN  
     3764         ! Read and interpolate using XIOS  
     3765     
     3766           ! Check if the restart file for sechiba is read.  
     3767           ! Reading of soilbulk and soilph with XIOS is only activated if restname==NONE.  
     3768           IF (restname_in /= 'NONE') THEN  
     3769              CALL ipslerr_p(3,'slowproc_soilt','soilbulk and soilph can not be read with XIOS if sechiba restart file exist', & 
     3770              'Remove sechiba restart file and start again','')  
     3771           END IF  
     3772      
     3773           IF (printlev_loc>=3) WRITE (numout,*) 'slowproc_soilt:Read soilbulk and soilph with XIOS'  
     3774           CALL xios_orchidee_recv_field('soilbulk', bulk)  
     3775       ELSE  
     3776       ! Read using IOIPSL and interpolate using aggregate tool in ORCHIDEE  
     3777           IF (printlev_loc>=3) WRITE (numout,*) 'slowproc_soilt:Read soilbulk and soilph with IOIPSL'       
     3778           !! Read soilbulk  
     3779      
     3780           !Config Key   = SOIL_BULK_FILE  
     3781           !Config Desc  = Name of file from which soil bulk should be read  
     3782           !Config Def   = soil_bulk_and_ph.nc  
     3783           !Config If    =   
     3784           !Config Help  =   
     3785           !Config Units = [FILE]  
     3786 
     3787       ! By default, bulk and ph is stored in the same file but they could be 
     3788       ! separated if needed.  
     3789           filename = 'soil_bulk_and_ph.nc'  
     3790           CALL getin_p('SOIL_BULK_FILE',filename)  
     3791      
     3792           variablename = 'soilbulk'  
     3793           ! Name of the longitude and latitude in the input file  
     3794           lonname = 'nav_lon'  
     3795           latname = 'nav_lat'  
     3796           vmin=0  ! not used in interpweight_2Dcont  
     3797           vmax=0  ! not used in interpweight_2Dcont  
     3798      
     3799           ! Should negative values be set to zero from input file?  
     3800           nonegative = .FALSE.  
     3801           ! Type of mask to apply to the input data (see header for more 
     3802           ! details)  
     3803           maskingtype = 'mabove'  
     3804           ! Values to use for the masking  
     3805           maskvals = (/ min_sechiba, undef_sechiba, undef_sechiba/)  
     3806           ! Name of the variable with the values for the mask in the input file 
     3807           ! (only if maskkingtype='var') ( not used)  
     3808           namemaskvar = ''  
     3809           ! Type of calculation of cell fractions  
     3810           fractype = 'default'  
     3811 
     3812              IF (printlev_loc >= 1) WRITE(numout,*) "slowproc_soilt: Read and interpolate " & 
     3813                   // TRIM(filename) // " for variable " // TRIM(variablename) 
     3814 
     3815 
     3816           CALL interpweight_2Dcont(nbpt, 0, 0, lalo, resolution,neighbours,                           &     
     3817                contfrac, filename, variablename, lonname, latname,vmin, vmax,nonegative, maskingtype,    &     
     3818                maskvals, namemaskvar, -1, fractype, bulk_default,undef_sechiba,                       & 
     3819                bulk, abulkph)  
     3820           WRITE(numout,*) 'bulk density map is read _______' 
     3821 
     3822 
     3823       ENDIF        !      xios_interpolation 
     3824    ENDIF 
     3825 
     3826       DO ib = 1, nbpt 
     3827          njsc(ib) = MAXLOC(soilclass(ib,:),1) 
     3828       ENDDO 
    36903829 
    36913830       ! End of soil texture reading, for 'maps' and classical behavior 
     
    38183957    CALL xios_orchidee_send_field("interp_diag_njsc",REAL(njsc, r_std)) 
    38193958    CALL xios_orchidee_send_field("interp_diag_clayfraction",clayfraction) 
     3959    CALL xios_orchidee_send_field("interp_diag_bulk",bulk) 
    38203960    CALL xios_orchidee_send_field("interp_diag_sandfraction",sandfraction) 
    38213961    CALL xios_orchidee_send_field("interp_diag_siltfraction",siltfraction) 
Note: See TracChangeset for help on using the changeset viewer.