Ignore:
Timestamp:
2019-11-08T13:00:52+01:00 (5 years ago)
Author:
josefine.ghattas
Message:

Improvment for the ESM CO2 configuration:

  • Separate variable fco2_lu into 3 parts: fco2_lu, fco2_wh and fco2_ha
  • Move calculation of co2_flux from dt_sechiba time-step to daily time-step (in the part for do_slow)
  • Removed co2_flux and fco2_lu from stomate_intialize argument list. These variables were never used in the intialization phase.
  • Add co2_flux, and fco2_wh, fco2_ha to restart file
  • Corrected output unit for nee to be consistent with LMDZ and stomate output variables. It is now in kgC/m2/s.
  • Corrected output for znetco2
  • Added fCO2_fWoodharvest and fCO2_fHarvest as new possible tracers in LMDZ (intersurf).
  • Added diagnostic output for fCO2_fWoodharvest and fCO2_fHarvest
  1. Cadule
File:
1 edited

Legend:

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

    r6160 r6319  
    8080       &  litterpart, litter, dead_leaves, & 
    8181       &  carbon, lignin_struc,turnover_time, & 
    82        &  fco2_lu, & 
     82       &  co2_flux, fco2_lu, fco2_wh, fco2_ha, & 
    8383       &  prod10,prod100,flux10, flux100, & 
    8484       &  convflux, cflux_prod10, cflux_prod100, & 
     
    327327    ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment 
    328328    ! (10 or 100 + 1 : input from year of land cover change) 
     329    REAL(r_std),DIMENSION(npts, nvm),INTENT(out)                           :: co2_flux 
    329330    REAL(r_std),DIMENSION(npts),INTENT(out)                                :: fco2_lu 
     331    REAL(r_std),DIMENSION(npts),INTENT(out)                                :: fco2_wh 
     332    REAL(r_std),DIMENSION(npts),INTENT(out)                                :: fco2_ha 
    330333    REAL(r_std),DIMENSION(npts,0:10),INTENT(out)                           :: prod10 
    331334    REAL(r_std),DIMENSION(npts,0:100),INTENT(out)                          :: prod100 
     
    10341037    !- 
    10351038    ! Read from restart file or set to zero if the variables or restart file were not found 
     1039 
     1040    var_name = 'co2_flux' 
     1041    CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
     1042         .TRUE., co2_flux, 'gather', nbp_glo, index_g) 
     1043    IF (ALL(co2_flux(:,:) == val_exp)) co2_flux(:,:) = zero 
     1044 
    10361045    var_name = 'fco2_lu' 
    10371046    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 
    10381047         .TRUE., fco2_lu, 'gather', nbp_glo, index_g) 
    10391048    IF (ALL(fco2_lu(:) == val_exp)) fco2_lu(:) = zero 
     1049 
     1050    var_name = 'fco2_wh' 
     1051    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 
     1052         .TRUE., fco2_wh, 'gather', nbp_glo, index_g) 
     1053    IF (ALL(fco2_wh(:) == val_exp)) fco2_wh(:) = zero 
     1054 
     1055    var_name = 'fco2_ha' 
     1056    CALL restget_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 
     1057         .TRUE., fco2_ha, 'gather', nbp_glo, index_g) 
     1058    IF (ALL(fco2_ha(:) == val_exp)) fco2_ha(:) = zero 
     1059 
    10401060        
    10411061    IF (vegetmap_reset) THEN 
     
    13321352       &  litterpart, litter, dead_leaves, & 
    13331353       &  carbon, lignin_struc, turnover_time, & 
    1334        &  fco2_lu, & 
     1354       &  co2_flux, fco2_lu, fco2_wh, fco2_ha, & 
    13351355       &  prod10,prod100 ,flux10, flux100, & 
    13361356       &  convflux, cflux_prod10, cflux_prod100, &  
     
    15701590    ! products remaining in the 10/100 year-turnover pool after the annual release for each compartment 
    15711591    ! (10 or 100 + 1 : input from year of land cover change) 
     1592    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)                            :: co2_flux 
    15721593    REAL(r_std),DIMENSION(npts),INTENT(in)                                :: fco2_lu 
     1594    REAL(r_std),DIMENSION(npts),INTENT(in)                                :: fco2_wh 
     1595    REAL(r_std),DIMENSION(npts),INTENT(in)                                :: fco2_ha 
    15731596    REAL(r_std),DIMENSION(npts,0:10),INTENT(in)                           :: prod10 
    15741597    REAL(r_std),DIMENSION(npts,0:100),INTENT(in)                          :: prod100 
     
    20742097    ! 18 land cover change 
    20752098    !- 
     2099    var_name = 'co2_flux' 
     2100    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
     2101         &                co2_flux, 'scatter', nbp_glo, index_g) 
    20762102    var_name = 'fco2_lu' 
    20772103    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 
    20782104         &                fco2_lu, 'scatter', nbp_glo, index_g) 
     2105    var_name = 'fco2_wh' 
     2106    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 
     2107         &                fco2_wh, 'scatter', nbp_glo, index_g) 
     2108    var_name = 'fco2_ha' 
     2109    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 1, 1, itime, & 
     2110         &                fco2_ha, 'scatter', nbp_glo, index_g) 
     2111 
    20792112    var_name = 'prod10' 
    20802113    CALL restput_p (rest_id_stomate, var_name, nbp_glo, 11, 1, itime, & 
Note: See TracChangeset for help on using the changeset viewer.