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
Location:
branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate
Files:
2 edited

Legend:

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

    r6160 r6319  
    430430                                                                         !! dimension(#pixels,0:100) 
    431431!$OMP THREADPRIVATE(flux100) 
     432  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: co2_flux             !! CO2 flux between atmosphere and biosphere 
     433                                                                         !! @tex $(gC m^{-2} one_day^{-1})$ @endtex 
     434!$OMP THREADPRIVATE(co2_flux) 
    432435  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: fco2_lu              !! CO2 flux between atmosphere and biosphere from land-use  
    433436                                                                         !! (without forest management) 
    434437                                                                         !! @tex $(gC m^{-2} one_day^{-1})$ @endtex 
    435438!$OMP THREADPRIVATE(fco2_lu) 
     439  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: fco2_wh              !! CO2 Flux to Atmosphere from Wood Harvesting (positive from atm to land) 
     440                                                                         !! @tex $(gC m^{-2} one_day^{-1})$ @endtex 
     441!$OMP THREADPRIVATE(fco2_wh) 
     442  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: fco2_ha              !! CO2 Flux to Atmosphere from Crop Harvesting (positive from atm to land) 
     443                                                                         !! @tex $(gC m^{-2} one_day^{-1})$ @endtex 
     444!$OMP THREADPRIVATE(fco2_ha) 
     445 
    436446  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)      :: convflux             !! Release during first year following land cover change  
    437447                                                                         !! (paper, burned, etc...)  
     
    630640         contfrac,       totfrac_nobio,     clay,         temp_air,          & 
    631641         lai,            veget,             veget_max,                       & 
    632          co2_flux,       co2_to_bm_radia,   fco2_lu_out,  deadleaf_cover,  assim_param, temp_growth ) 
     642         co2_to_bm_radia,deadleaf_cover,    assim_param,  temp_growth ) 
     643 
    633644 
    634645    IMPLICIT NONE 
     
    656667 
    657668    !! 0.2 Output variables 
    658     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_flux          !! CO2 flux between atmosphere and biosphere 
     669 
    659670    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_to_bm_radia   !! virtual gpp flux between atmosphere and biosphere 
    660     REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_lu_out       !! CO2 flux between atmosphere and biosphere from land-use (without forest management)   
    661671    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: deadleaf_cover    !! Fraction of soil covered by dead leaves (unitless) 
    662672    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(out) :: assim_param !! min+max+opt temperatures (K) & vmax for photosynthesis   
     
    764774     
    765775    !! 1.4.3.1 Read initial values for STOMATE's variables from the _restart_ file 
    766     co2_flux(:,:) = zero 
    767776 
    768777    ! Get values from _restart_ file. Note that only ::kjpindex, ::index, ::lalo  
     
    795804         litterpart, litter, dead_leaves, & 
    796805         carbon, lignin_struc,turnover_time,& 
    797          fco2_lu,& 
     806         co2_flux, fco2_lu, fco2_wh, fco2_ha, & 
    798807         prod10,prod100,flux10, flux100, & 
    799808         convflux, cflux_prod10, cflux_prod100, & 
     
    807816         MatrixV, VectorU, previous_stock, current_stock, assim_param) 
    808817     
    809     ! Copy module variable fco2_lu into local variable to allow it to be in the argument output list of the subroutine 
    810     fco2_lu_out(:)=fco2_lu(:) 
    811  
    812818    !! 1.4.5 Check time step 
    813819        
     
    11601166!! 
    11611167!! MAIN OUTPUT VARIABLE(S): deadleaf_cover, assim_param, lai, height, veget,  
    1162 !! veget_max, resp_maint,  
    1163 !! resp_hetero,resp_growth, co2_flux, fco2_lu_out. 
     1168!! veget_max, resp_maint, resp_hetero, resp_growth,  
     1169!! co2_flux_out, fco2_lu_out, fco2_wh_out, fco2_ha_out. 
    11641170!! 
    11651171!! REFERENCES   :  
     
    11831189       &  veget_max_new, woodharvest, totfrac_nobio_new, fraclut, & 
    11841190       &  rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & 
    1185        &  co2_flux, fco2_lu_out, resp_maint,resp_hetero,resp_growth,co2_to_bm_radia,temp_growth) 
     1191       &  co2_flux_out, fco2_lu_out, fco2_wh_out, fco2_ha_out, & 
     1192       &  resp_maint, resp_hetero, resp_growth, co2_to_bm_radia, temp_growth) 
    11861193     
    11871194    IMPLICIT NONE 
     
    12361243    !! 0.2 Output variables 
    12371244 
    1238     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_flux          !! CO2 flux between atmosphere and biosphere per  
     1245    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_flux_out      !! CO2 flux between atmosphere and biosphere per  
    12391246                                                                         !! average ground area  
    12401247                                                                         !! @tex $(gC m^{-2} dt_sechiba^{-1})$ @endtex   
    12411248    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_lu_out       !! CO2 flux between atmosphere and biosphere from  
    1242                                                                          !! land-use (without forest management)   
    1243                                                                          !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex   
     1249                                                                         !! land-use (without forest management) (gC/m2/dt_stomate) 
     1250    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_wh_out       !! CO2 Flux to Atmosphere from Wood Harvesting (gC/m2/dt_stomate) 
     1251    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: fco2_ha_out       !! CO2 Flux to Atmosphere from Crop Harvesting (gC/m2/dt_stomate) 
    12441252    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_maint        !! Maitenance component of autotrophic respiration in  
    12451253                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex  
     
    15991607            &             Tseason, Tmin_spring_time, begin_leaves, onset_date) 
    16001608        
     1609 
    16011610       !! 5.3.2 Calculate the total CO2 flux from land use change 
    1602        fco2_lu(:) = convflux(:) & 
    1603             &             + cflux_prod10(:)  & 
    1604             &             + cflux_prod100(:) & 
    1605             &             + harvest_above(:) & 
    1606             &             + convflux_harvest(:) & 
    1607             &             + cflux_prod10_harvest(:)  & 
    1608             &             + cflux_prod100_harvest(:) 
     1611 
     1612       ! CO2 from land-use change 
     1613       fco2_lu(:) = convflux(:) + cflux_prod10(:) + cflux_prod100(:)  
     1614 
     1615       ! CO2 from wood harvest 
     1616       fco2_wh(:) = convflux_harvest(:) + cflux_prod10_harvest(:) + cflux_prod100_harvest(:) 
    16091617        
     1618       ! CO2 from harvest 
     1619       fco2_ha(:) = harvest_above(:)  
     1620               
    16101621       !! 5.4 Calculate veget and veget_max 
    16111622       veget_max(:,:) = zero  
     
    17581769       CALL xios_orchidee_send_field("rhSoil",SUM(resp_hetero_soil*veget_cov_max,dim=2)/1e3) 
    17591770       CALL xios_orchidee_send_field("rhLitter",SUM(resp_hetero_litter*veget_cov_max,dim=2)/1e3) 
    1760         
    1761  
     1771 
     1772       ! Calculate co2_flux as (-1)*nep_daily*veget_cov_max.  
     1773       ! This variable will be used for the coupling to LMDZ for ESM configuration. 
     1774       co2_flux(:,:) = (resp_hetero_d(:,:) + resp_maint_d(:,:) + resp_growth_d(:,:) & 
     1775            + co2_fire(:,:) -  gpp_daily(:,:))*veget_cov_max 
     1776       
    17621777       IF ( hist_id_stom_IPCC > 0 ) THEN 
    17631778          vartmp(:) = SUM(nep_daily*veget_cov_max,dim=2)/1e3/one_day*contfrac 
     
    18461861  !! 6. Outputs from Stomate 
    18471862 
    1848     ! co2_flux receives a value from STOMATE only if STOMATE is activated. 
    1849     ! Otherwise, the calling hydrological module must do this itself. 
    1850  
    18511863    !! 6.1 Respiration and fluxes 
    18521864    resp_maint(:,:) = resp_maint_radia(:,:)*veget_cov_max(:,:) 
     
    18561868    resp_hetero(:,:) = resp_hetero_radia(:,:)*veget_cov_max(:,:) 
    18571869     
    1858     !! 6.2 Derived CO2 fluxes 
    1859     ! CO2 flux in gC m^{-2} s^{-1} (positive towards the atmosphere) is sum of: 
    1860     ! (1) heterotrophic respiration from ground + (2) maintenance respiration  
    1861     ! from the plants + (3) growth respiration from the plants + (4) co2  
    1862     ! emissions from fire - (5) co2 taken up in the DGVM to establish  
    1863     ! saplings - (6) co2 taken up by photosyntyhesis 
    1864     ! co2_to_bm is not included here as it is already encounted in the gpp 
    1865     co2_flux(:,:) = resp_hetero(:,:) + resp_maint(:,:) + resp_growth(:,:) & 
    1866          & + co2_fire(:,:)*veget_cov_max(:,:)*dt_sechiba/one_day & 
    1867          & - gpp(:,:) 
    1868      
    18691870    temp_growth(:)=t2m_month(:)-tp_00  
    18701871 
    1871     ! Copy module variable fco2_lu into local variable to allow it to be in the argument output list of the subroutine 
     1872 
     1873    ! Copy module variables into local variables to allow them to be in the argument output list of the subroutine 
     1874    co2_flux_out(:,:)=co2_flux(:,:) 
    18721875    fco2_lu_out(:)=fco2_lu(:) 
     1876    fco2_wh_out(:)=fco2_wh(:) 
     1877    fco2_ha_out(:)=fco2_ha(:) 
    18731878 
    18741879 
     
    21232128         litterpart, litter, dead_leaves, & 
    21242129         carbon, lignin_struc,turnover_time,& 
    2125          fco2_lu,& 
     2130         co2_flux, fco2_lu, fco2_wh, fco2_ha, & 
    21262131         prod10,prod100,flux10, flux100, & 
    21272132         convflux, cflux_prod10, cflux_prod100, & 
     
    30803085    ENDIF 
    30813086 
     3087    ALLOCATE (co2_flux(kjpindex,nvm), stat=ier) 
     3088    l_error = l_error .OR. (ier /= 0) 
     3089    IF (l_error) THEN 
     3090       WRITE(numout,*) 'Memory allocation error for co2_flux. We stop. We need kjpindex words',kjpindex,nvm 
     3091       STOP 'stomate_init' 
     3092    ENDIF 
     3093 
    30823094    ALLOCATE (fco2_lu(kjpindex), stat=ier) 
    30833095    l_error = l_error .OR. (ier /= 0) 
    30843096    IF (l_error) THEN 
    30853097       WRITE(numout,*) 'Memory allocation error for fco2_lu. We stop. We need kjpindex words',kjpindex 
     3098       STOP 'stomate_init' 
     3099    ENDIF 
     3100 
     3101    ALLOCATE (fco2_wh(kjpindex), stat=ier) 
     3102    l_error = l_error .OR. (ier /= 0) 
     3103    IF (l_error) THEN 
     3104       WRITE(numout,*) 'Memory allocation error for fco2_wh. We stop. We need kjpindex words',kjpindex 
     3105       STOP 'stomate_init' 
     3106    ENDIF 
     3107 
     3108    ALLOCATE (fco2_ha(kjpindex), stat=ier) 
     3109    l_error = l_error .OR. (ier /= 0) 
     3110    IF (l_error) THEN 
     3111       WRITE(numout,*) 'Memory allocation error for fco2_ha. We stop. We need kjpindex words',kjpindex 
    30863112       STOP 'stomate_init' 
    30873113    ENDIF 
     
    35943620    IF ( ALLOCATED (horip11_index)) DEALLOCATE (horip11_index) 
    35953621    IF ( ALLOCATED (horip101_index)) DEALLOCATE (horip101_index) 
     3622    IF ( ALLOCATED (co2_flux)) DEALLOCATE (co2_flux) 
    35963623    IF ( ALLOCATED (fco2_lu)) DEALLOCATE (fco2_lu) 
     3624    IF ( ALLOCATED (fco2_wh)) DEALLOCATE (fco2_wh) 
     3625    IF ( ALLOCATED (fco2_ha)) DEALLOCATE (fco2_ha) 
    35973626    IF ( ALLOCATED (prod10)) DEALLOCATE (prod10) 
    35983627    IF ( ALLOCATED (prod100)) DEALLOCATE (prod100) 
  • 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.