Ignore:
Timestamp:
2024-03-07T18:38:03+01:00 (4 months ago)
Author:
josefine.ghattas
Message:

The Moyano function describing the soil moisture effect on OM decomposition is added. It has been developed by Elodie Salmon in another branch and integrated in ORCHIDEE_2_2 by Bertrad Guenet. This commit corresponds to a corrected version of [8418].

File:
1 edited

Legend:

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

    r8423 r8462  
    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    IF (ok_moyano_soilhumsat) CALL restput_p (rest_id, 'bulk', nbp_glo, 1, 1, kjit, bulk, 'scatter',  nbp_glo,index_g)  
     953 
    906954    !salma: added the following lines for restput of the soil parameters 
    907955    CALL restput_p (rest_id, 'ks', nbp_glo, 1, 1, kjit, ks, 'scatter',  nbp_glo, index_g) 
     
    929977    ! 2.2 Write restart variables managed by STOMATE 
    930978    IF ( ok_stomate ) THEN 
    931        CALL stomate_finalize (kjit, kjpindex, indexLand, clayfraction, assim_param)  
     979       CALL stomate_finalize (kjit, kjpindex, indexLand, clayfraction, bulk, assim_param)  
    932980    ENDIF 
    933981     
     
    10571105    siltfraction(:)=undef_sechiba 
    10581106 
     1107    ALLOCATE (bulk(kjpindex),stat=ier) 
     1108    IF (ier /= 0) CALL ipslerr_p(3,'slowproc_init','Problem in allocation of variable bulk','','') 
     1109    bulk(:)=undef_sechiba 
     1110 
    10591111    ! Allocation of last year vegetation fraction in case of land use change 
    10601112    ALLOCATE(veget_max_new(kjpindex, nvm), STAT=ier) 
     
    12111263    END IF 
    12121264 
     1265 
     1266    IF (ok_moyano_soilhumsat) THEN 
     1267       var_name= 'bulk'  
     1268       CALL ioconf_setatt_p('UNITS', '-') 
     1269       CALL ioconf_setatt_p('LONG_NAME','Bulk density in each mesh') 
     1270       CALL restget_p (rest_id, var_name, nbp_glo, 1, 1, kjit, .TRUE., bulk, "gather", nbp_glo, index_g)  
     1271       IF ( ALL(bulk(:) .EQ. val_exp ) ) THEN 
     1272          ! bulk is not in restart file 
     1273          call_slowproc_soilt=.TRUE. 
     1274       END IF 
     1275    END IF 
     1276 
     1277     
     1278     
    12131279    ! Calculate siltfraction not needed to be in restart file 
    12141280    IF ( ALL( sandfraction(:) .EQ. val_exp) ) THEN 
     
    13081374       CALL setvar_p (ks, val_exp, 'KS_IMP', ks_default) 
    13091375 
     1376       !Config Key   = BULK   
     1377       !Config Desc  = Bulk density (0-dim mode)  
     1378       !Config Def   = 1000.0 
     1379       !Config If    = IMPOSE_SOIL  
     1380       !Config Help  = Determines the bulk density in the grid box.  The bulk density  
     1381       !Config         is the weight of soil in a given volume.  
     1382       !Config Units = [-]   
     1383       CALL setvar_p (bulk, val_exp, 'BULK', bulk_default)  
     1384        
    13101385       ! By default, we calculate mcf and mcw from the above values, as in slowproc_soilt, 
    13111386       ! but they can be overruled by values from run.def 
     
    13571432          CALL slowproc_soilt(njsc, ks, nvan, avan, mcr, mcs, mcfc, mcw, kjpindex, & 
    13581433               lalo, neighbours, resolution, contfrac, soilclass, & 
    1359                clayfraction, sandfraction, siltfraction) 
     1434               clayfraction, sandfraction, siltfraction, bulk) 
    13601435           
    13611436          call_slowproc_soilt=.FALSE. 
     
    15361611    ENDIF 
    15371612 
     1613 
    15381614    var_name= 'lai' 
    15391615    CALL ioconf_setatt_p('UNITS', '-') 
     
    16111687       !Config Units = [-] 
    16121688       CALL setvar_p (lai, val_exp, 'SECHIBA_LAI', llaimax) 
     1689  
    16131690 
    16141691       !Config Key   = SLOWPROC_HEIGHT 
     
    17231800    ENDIF 
    17241801     
    1725  
    17261802    !! 4.3 Dynamic irrigation map 
    17271803    !  If do_irrigation, it will look to the dynamical irrig. map in restart 
     
    18431919    IF (ALLOCATED (sandfraction)) DEALLOCATE (sandfraction) 
    18441920    IF (ALLOCATED (siltfraction)) DEALLOCATE (siltfraction) 
     1921    IF (ALLOCATED (bulk)) DEALLOCATE (bulk)  
    18451922    IF (ALLOCATED (laimap)) DEALLOCATE (laimap) 
    18461923    IF (ALLOCATED (veget_max_new)) DEALLOCATE (veget_max_new) 
     
    25312608    END IF  
    25322609 
    2533     ! Assigning the right values and giving a value where information was not found 
     2610    ! Assiggning the right values and giving a value where information was not found 
    25342611    DO ib=1,nbpt 
    25352612      IF (alaimap(ib) < min_sechiba) THEN 
     
    29313008!>\BRIEF         looks for nearest grid point on the fine map 
    29323009!! 
    2933 !! DESCRIPTION  : (definitions, functional, design, flags):  
    2934 !! 
     3010!! DESCRIPTION  : (definitions, functional, design, flags): 
     3011!!            
    29353012!! RECENT CHANGE(S): None 
    29363013!! 
     
    30033080!! 
    30043081!>\BRIEF         Interpolate the Zobler or Reynolds/USDA soil type map 
     3082!!               Read and interpolate soil bulk from file.  
    30053083!! 
    30063084!! DESCRIPTION  : (definitions, functional, design, flags):  
     
    30103088!!                             and everything needed to read all maps and assign parameter values.   
    30113089!! 
    3012 !! MAIN OUTPUT VARIABLE(S): ::soiltype, ::clayfraction, sandfraction, siltfraction 
     3090!! MAIN OUTPUT VARIABLE(S): ::soiltype, ::clayfraction, sandfraction, siltfraction, bulk 
    30133091!! 
    30143092!! REFERENCE(S) : Reynold, Jackson, and Rawls (2000). Estimating soil water-holding capacities  
     
    30193097!! \n 
    30203098!_ ================================================================================================================================ 
    3021   SUBROUTINE slowproc_soilt(njsc,  ks,  nvan, avan, mcr, mcs, mcfc, mcw, nbpt, lalo, neighbours, resolution, contfrac, soilclass, clayfraction, sandfraction, siltfraction) 
     3099  SUBROUTINE slowproc_soilt(njsc,  ks,  nvan, avan, mcr, mcs, mcfc, mcw, nbpt, lalo, neighbours, resolution, contfrac, soilclass, clayfraction, sandfraction, siltfraction, bulk) 
    30223100 
    30233101    USE interpweight 
     
    30613139    REAL(r_std), INTENT(out)      :: sandfraction(nbpt)     !! The fraction of sand (for SP-MIP) 
    30623140    REAL(r_std), INTENT(out)      :: siltfraction(nbpt)     !! The fraction of silt (for SP-MIP) 
     3141    REAL(r_std), INTENT(out)      :: bulk(nbpt)             !! Bulk density  as used by STOMATE  
    30633142    ! 
    30643143    ! 
     
    30883167    CHARACTER(LEN=80)                                    :: spmipexp          !! designing the number of sp-mip experiment 
    30893168    CHARACTER(LEN=80)                                    :: unif_case               !! designing the model of experiment 4 (sp_mip) 
    3090  
     3169    REAL(r_std), DIMENSION(nbpt)                         :: abulkph          !!Availability of the bulk and ph interpolation  
    30913170    REAL(r_std)                                          :: vmin, vmax       !! min/max values to use for the  
    30923171 
     
    36373716                      IF ( (solt(ilf) .LE. nscm) .AND. (solt(ilf) .GT. 0) ) THEN 
    36383717                         soilclass(ib,solt(ilf)) = textrefrac(ib,solt(ilf)) 
    3639                          clayfraction(ib) = clayfraction(ib) + textfrac_table(solt(ilf),3) *                & 
     3718                         clayfraction(ib) = clayfraction(ib) + textfrac_table(solt(ilf),3) * & 
    36403719                              textrefrac(ib,solt(ilf)) 
    36413720                         sandfraction(ib) = sandfraction(ib) + textfrac_table(solt(ilf),2) * & 
     
    36883767 
    36893768       ENDIF        !      xios_interpolation 
     3769 
     3770    !!  
     3771    !! Read and interpolate soil bulk and soil ph using IOIPSL or XIOS  
     3772    !! 
     3773    IF (ok_moyano_soilhumsat) THEN 
     3774       IF (xios_interpolation) THEN  
     3775         ! Read and interpolate using XIOS  
     3776     
     3777           ! Check if the restart file for sechiba is read.  
     3778           ! Reading of soilbulk and soilph with XIOS is only activated if restname==NONE.  
     3779           IF (restname_in /= 'NONE') THEN  
     3780              CALL ipslerr_p(3,'slowproc_soilt','soilbulk and soilph can not be read with XIOS if sechiba restart file exist', & 
     3781              'Remove sechiba restart file and start again','')  
     3782           END IF  
     3783      
     3784           IF (printlev_loc>=3) WRITE (numout,*) 'slowproc_soilt:Read soilbulk and soilph with XIOS'  
     3785           CALL xios_orchidee_recv_field('soilbulk', bulk)  
     3786       ELSE  
     3787       ! Read using IOIPSL and interpolate using aggregate tool in ORCHIDEE  
     3788           IF (printlev_loc>=3) WRITE (numout,*) 'slowproc_soilt:Read soilbulk and soilph with IOIPSL'       
     3789           !! Read soilbulk  
     3790      
     3791           !Config Key   = SOIL_BULK_FILE  
     3792           !Config Desc  = Name of file from which soil bulk should be read  
     3793           !Config Def   = soil_bulk_and_ph.nc  
     3794           !Config If    =   
     3795           !Config Help  =   
     3796           !Config Units = [FILE]  
     3797 
     3798       ! By default, bulk and ph is stored in the same file but they could be 
     3799       ! separated if needed.  
     3800           filename = 'soil_bulk_and_ph.nc'  
     3801           CALL getin_p('SOIL_BULK_FILE',filename)  
     3802      
     3803           variablename = 'soilbulk'  
     3804           ! Name of the longitude and latitude in the input file  
     3805           lonname = 'nav_lon'  
     3806           latname = 'nav_lat'  
     3807           vmin=0  ! not used in interpweight_2Dcont  
     3808           vmax=0  ! not used in interpweight_2Dcont  
     3809      
     3810           ! Should negative values be set to zero from input file?  
     3811           nonegative = .FALSE.  
     3812           ! Type of mask to apply to the input data (see header for more 
     3813           ! details)  
     3814           maskingtype = 'mabove'  
     3815           ! Values to use for the masking  
     3816           maskvals = (/ min_sechiba, undef_sechiba, undef_sechiba/)  
     3817           ! Name of the variable with the values for the mask in the input file 
     3818           ! (only if maskkingtype='var') ( not used)  
     3819           namemaskvar = ''  
     3820           ! Type of calculation of cell fractions  
     3821           fractype = 'default'  
     3822 
     3823              IF (printlev_loc >= 1) WRITE(numout,*) "slowproc_soilt: Read and interpolate " & 
     3824                   // TRIM(filename) // " for variable " // TRIM(variablename) 
     3825 
     3826 
     3827           CALL interpweight_2Dcont(nbpt, 0, 0, lalo, resolution,neighbours,                           &     
     3828                contfrac, filename, variablename, lonname, latname,vmin, vmax,nonegative, maskingtype,    &     
     3829                maskvals, namemaskvar, -1, fractype, bulk_default,undef_sechiba,                       & 
     3830                bulk, abulkph)  
     3831           WRITE(numout,*) 'bulk density map is read _______' 
     3832 
     3833 
     3834       ENDIF        !      xios_interpolation 
     3835    ENDIF 
    36903836 
    36913837       ! End of soil texture reading, for 'maps' and classical behavior 
     
    38183964    CALL xios_orchidee_send_field("interp_diag_njsc",REAL(njsc, r_std)) 
    38193965    CALL xios_orchidee_send_field("interp_diag_clayfraction",clayfraction) 
     3966    CALL xios_orchidee_send_field("interp_diag_bulk",bulk) 
    38203967    CALL xios_orchidee_send_field("interp_diag_sandfraction",sandfraction) 
    38213968    CALL xios_orchidee_send_field("interp_diag_siltfraction",siltfraction) 
Note: See TracChangeset for help on using the changeset viewer.