Ignore:
Timestamp:
2021-10-20T18:39:22+02:00 (3 years ago)
Author:
josefine.ghattas
Message:

Corrected bug on carbon balance closure. See ticket #785
Integration in branch 2_2 done by P. Cadule

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

Legend:

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

    r6369 r7326  
    646646         contfrac,       totfrac_nobio,     clay,         temp_air,          & 
    647647         lai,            veget,             veget_max,                       & 
    648          co2_to_bm_radia,deadleaf_cover,    assim_param,  temp_growth ) 
     648         deadleaf_cover,    assim_param,  temp_growth ) 
    649649 
    650650 
     
    674674    !! 0.2 Output variables 
    675675 
    676     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_to_bm_radia   !! virtual gpp flux between atmosphere and biosphere 
    677676    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: deadleaf_cover    !! Fraction of soil covered by dead leaves (unitless) 
    678677    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(out) :: assim_param !! min+max+opt temperatures (K) & vmax for photosynthesis   
     
    805804         leaf_age, leaf_frac, & 
    806805         senescence, when_growthinit, age, & 
    807          resp_hetero_d, resp_maint_d, resp_growth_d, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & 
     806         resp_hetero_d, resp_maint_d, resp_growth_d, co2_fire, co2_to_bm_dgvm, & 
    808807         veget_lastlight, everywhere, need_adjacent, RIP_time, & 
    809808         time_hum_min, hum_min_dormance, & 
     
    11961195       &  rest_id_stom, hist_id_stom, hist_id_stom_IPCC, & 
    11971196       &  co2_flux_out, fco2_lu_out, fco2_wh_out, fco2_ha_out, & 
    1198        &  resp_maint, resp_hetero, resp_growth, co2_to_bm_radia, temp_growth) 
     1197       &  resp_maint, resp_hetero, resp_growth, temp_growth) 
    11991198     
    12001199    IMPLICIT NONE 
     
    12621261    REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: resp_hetero       !! Heterotrophic respiration in   
    12631262                                                                         !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex   
    1264     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(out) :: co2_to_bm_radia   !! Virtual gpp created for equilibrium of carbon mass   
    1265                                                                          !! @tex $(gC m^{-2} dt_stomate^{-1})$ @endtex   
    12661263    REAL(r_std),DIMENSION(kjpindex),INTENT(out)     :: temp_growth       !! Growth temperature (°C)   
    12671264                                                                         !! Is equal to t2m_month  
     
    16021599            &             veget_lastlight, everywhere, need_adjacent, RIP_time, & 
    16031600            &             lai, rprof,npp_daily, turnover_daily, turnover_time,& 
    1604             &             control_moist_inst, control_temp_inst, soilcarbon_input_inst, & 
     1601            &             control_moist_inst, control_temp_inst, soilcarbon_input_daily, & 
    16051602            &             co2_to_bm_dgvm, co2_fire, & 
    16061603            &             resp_hetero_d, resp_hetero_litter_d, resp_hetero_soil_d, resp_maint_d, resp_growth_d, & 
     
    17711768       ! - (6) co2 emission from fire 
    17721769       ! co2_to_bm is not added as it is already encounted in gpp 
    1773        nep_daily(:,:)= gpp_daily(:,:)       & 
     1770       nep_daily(:,:)= gpp_daily(:,:) + co2_to_bm_dgvm(:,:)      & 
    17741771                     - resp_maint_d(:,:)  - resp_growth_d(:,:)   & 
    17751772                     - resp_hetero_d(:,:) - co2_fire(:,:)  
     
    17801777       ! This variable will be used for the coupling to LMDZ for ESM configuration. 
    17811778       co2_flux(:,:) = (resp_hetero_d(:,:) + resp_maint_d(:,:) + resp_growth_d(:,:) & 
    1782             + co2_fire(:,:) - gpp_daily(:,:))*veget_cov_max 
     1779            + co2_fire(:,:) - co2_to_bm_dgvm(:,:) - gpp_daily(:,:))*veget_cov_max 
    17831780       
    17841781       IF ( hist_id_stom_IPCC > 0 ) THEN 
     
    18751872    resp_maint(:,ibare_sechiba) = zero 
    18761873    resp_growth(:,:)= resp_growth_d(:,:)*veget_cov_max(:,:)*dt_sechiba/one_day 
    1877     co2_to_bm_radia(:,:)=co2_to_bm_dgvm(:,:)*veget_cov_max(:,:)*dt_sechiba/one_day 
    18781874    resp_hetero(:,:) = resp_hetero_radia(:,:)*veget_cov_max(:,:) 
    18791875     
     
    20172013!_ ================================================================================================================================ 
    20182014 
    2019   SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, co2_to_bm_radia, assim_param)  
     2015  SUBROUTINE stomate_finalize (kjit, kjpindex, index, clay, assim_param)  
    20202016     
    20212017    IMPLICIT NONE 
     
    20272023    INTEGER(i_std),DIMENSION(kjpindex),INTENT(in)   :: index             !! Indices of the terrestrial pixels only (unitless) 
    20282024    REAL(r_std),DIMENSION(kjpindex),INTENT(in)      :: clay              !! Clay fraction of soil (0-1, unitless) 
    2029     REAL(r_std),DIMENSION(kjpindex,nvm),INTENT(in)  :: co2_to_bm_radia   !! virtual gpp flux between atmosphere and biosphere 
    20302025    REAL(r_std),DIMENSION(kjpindex,nvm,npco2),INTENT(in) :: assim_param  !! min+max+opt temperatures (K) & vmax for photosynthesis   
    20312026 
     
    21322127         leaf_age, leaf_frac, & 
    21332128         senescence, when_growthinit, age, & 
    2134          resp_hetero_d, resp_maint_d, resp_growth_d, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & 
     2129         resp_hetero_d, resp_maint_d, resp_growth_d, co2_fire, co2_to_bm_dgvm, & 
    21352130         veget_lastlight, everywhere, need_adjacent, & 
    21362131         RIP_time, & 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_io.f90

    r6319 r7326  
    7575       &  turnover_longterm, gpp_week, biomass, resp_maint_part, & 
    7676       &  leaf_age, leaf_frac, senescence, when_growthinit, age, & 
    77        &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & 
     77       &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, & 
    7878       &  veget_lastlight, everywhere, need_adjacent, RIP_time, & 
    7979       &  time_hum_min, hum_min_dormance, & 
     
    249249    ! biomass uptaken (gC/(m**2 of total ground)/day) 
    250250    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_dgvm 
    251     ! biomass uptaken (gC/(m**2 of total ground)/dt_sechiba) 
    252     REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: co2_to_bm_radia 
    253251    ! vegetation fractions (on ground) after last light competition 
    254252    REAL(r_std),DIMENSION(npts,nvm),INTENT(out) :: veget_lastlight 
     
    941939    IF (ALL(co2_to_bm_dgvm(:,:) == val_exp)) co2_to_bm_dgvm(:,:) = zero 
    942940 
    943     co2_to_bm_radia(:,:) = val_exp 
    944     var_name = 'co2_to_bm_radia' 
    945     CALL restget_p (rest_id_stomate, var_name, nbp_glo, nvm     , 1, itime, & 
    946          &                .TRUE., co2_to_bm_radia, 'gather', nbp_glo, index_g) 
    947     IF (ALL(co2_to_bm_radia(:,:) == val_exp)) co2_to_bm_radia(:,:) = zero 
    948941    !- 
    949942    ! 14 vegetation distribution after last light competition 
     
    13471340       &  turnover_longterm, gpp_week, biomass, resp_maint_part, & 
    13481341       &  leaf_age, leaf_frac, senescence, when_growthinit, age, & 
    1349        &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, co2_to_bm_radia, & 
     1342       &  resp_hetero, resp_maint, resp_growth, co2_fire, co2_to_bm_dgvm, & 
    13501343       &  veget_lastlight, everywhere, need_adjacent, RIP_time, & 
    13511344       &  time_hum_min, hum_min_dormance, & 
     
    15131506    ! biomass uptaken (gC/(m**2 of total ground)/day) 
    15141507    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_dgvm 
    1515     ! biomass uptaken (gC/(m**2 of total ground)/dt_sechiba) 
    1516     REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: co2_to_bm_radia 
    15171508    ! vegetation fractions (on ground) after last light competition 
    15181509    REAL(r_std),DIMENSION(npts,nvm),INTENT(in) :: veget_lastlight 
     
    20242015    CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
    20252016         &                co2_to_bm_dgvm, 'scatter', nbp_glo, index_g) 
    2026     !- 
    2027     var_name = 'co2_to_bm_radia' 
    2028     CALL restput_p (rest_id_stomate, var_name, nbp_glo, nvm, 1, itime, & 
    2029          &                co2_to_bm_radia, 'scatter', nbp_glo, index_g) 
    20302017    !- 
    20312018    ! 14 vegetation distribution after last light competition 
  • branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_lpj.f90

    r6369 r7326  
    875875    sum_cVegTree = zero 
    876876 
    877     DO j=2,nvm 
     877    DO j=1,nvm 
    878878 
    879879       tot_litter_carb(:,j) = tot_litter_carb(:,j) + (litter(:,istructural,j,iabove,icarbon) + & 
     
    958958    CALL xios_orchidee_send_field("LAI",lai) 
    959959    CALL xios_orchidee_send_field("VEGET_COV_MAX",veget_cov_max) 
    960     CALL xios_orchidee_send_field("NPP_STOMATE",npp_daily) 
    961     CALL xios_orchidee_send_field("GPP",gpp_daily) 
     960    CALL xios_orchidee_send_field("NPP_STOMATE",npp_daily+co2_to_bm) 
     961    CALL xios_orchidee_send_field("GPP",gpp_daily+co2_to_bm) 
    962962    CALL xios_orchidee_send_field("IND",ind) 
    963963    CALL xios_orchidee_send_field("CN_IND",cn_ind) 
     
    10531053     
    10541054    ! Carbon fluxes transformed from gC/m2/d into kgC/m2/s 
    1055     CALL xios_orchidee_send_field("gpp_ipcc",SUM(gpp_daily*veget_cov_max,dim=2)/1e3/one_day) 
     1055    CALL xios_orchidee_send_field("gpp_ipcc",SUM((gpp_daily+co2_to_bm)*veget_cov_max,dim=2)/1e3/one_day) 
    10561056    CALL xios_orchidee_send_field("ra",SUM((resp_maint+resp_growth)*veget_cov_max,dim=2)/1e3/one_day) 
    10571057    vartmp(:)=zero 
     
    10791079    CALL xios_orchidee_send_field("raTree",vartmp/1e3/one_day) 
    10801080 
    1081     CALL xios_orchidee_send_field("npp_ipcc",SUM(npp_daily*veget_cov_max,dim=2)/1e3/one_day) 
     1081    CALL xios_orchidee_send_field("npp_ipcc",SUM((npp_daily+co2_to_bm)*veget_cov_max,dim=2)/1e3/one_day) 
     1082 
    10821083    vartmp(:)=zero 
    10831084    DO j = 2, nvm 
    10841085       IF ( .NOT. is_tree(j) .AND. natural(j) ) THEN 
    1085           vartmp(:) = vartmp(:) + npp_daily(:,j)*veget_cov_max(:,j) 
     1086          vartmp(:) = vartmp(:) +( npp_daily(:,j)+co2_to_bm(:,j))*veget_cov_max(:,j) 
    10861087       ENDIF 
    10871088    ENDDO 
     
    10901091    DO j = 2, nvm 
    10911092       IF ( (.NOT. is_tree(j)) .AND. (.NOT. natural(j)) ) THEN 
    1092           vartmp(:) = vartmp(:) + npp_daily(:,j)*veget_cov_max(:,j) 
     1093          vartmp(:) = vartmp(:) + (npp_daily(:,j)+co2_to_bm(:,j))*veget_cov_max(:,j) 
    10931094       ENDIF 
    10941095    ENDDO 
     
    10981099    DO j = 2, nvm 
    10991100       IF ( is_tree(j) ) THEN 
    1100           vartmp(:) = vartmp(:) + npp_daily(:,j)*veget_cov_max(:,j) 
     1101          vartmp(:) = vartmp(:) + (npp_daily(:,j)+co2_to_bm(:,j))*veget_cov_max(:,j) 
    11011102       ENDIF 
    11021103    ENDDO 
     
    11961197    CALL xios_orchidee_send_field("flulccatmlut",flulccatmlut) 
    11971198 
    1198    ! co2_to_bm is not added as it is already included in gpp 
    1199     CALL xios_orchidee_send_field("nbp",(SUM((gpp_daily-(resp_maint+resp_growth+resp_hetero)-co2_fire) * & 
     1199    CALL xios_orchidee_send_field("nbp",(SUM((gpp_daily+co2_to_bm-(resp_maint+resp_growth+resp_hetero)-co2_fire) * & 
    12001200          veget_cov_max,dim=2)-cflux_prod_total-cflux_prod_harvest_total-harvest_above)/1e3/one_day) 
    12011201    CALL xios_orchidee_send_field("fVegLitter",SUM((tot_bm_to_litter(:,:,icarbon) + tot_turnover(:,:,icarbon))*& 
     
    12671267               resp_hetero(:,j)*veget_cov_max(:,j)/1e3/one_day 
    12681268          npplut(:,id_psl) = npplut(:,id_psl) + & 
    1269                npp_daily(:,j)*veget_cov_max(:,j)/1e3/one_day 
     1269               (npp_daily(:,j)+co2_to_bm(:,j))*veget_cov_max(:,j)/1e3/one_day 
    12701270       ELSE 
    12711271          clitterlut(:,id_crp) = clitterlut(:,id_crp) + tot_litter_carb(:,j)*veget_cov_max(:,j)/1e3 
     
    12781278               resp_hetero(:,j)*veget_cov_max(:,j)/1e3/one_day 
    12791279          npplut(:,id_crp) = npplut(:,id_crp) + & 
    1280                npp_daily(:,j)*veget_cov_max(:,j)/1e3/one_day 
     1280               (npp_daily(:,j)+co2_to_bm(:,j))*veget_cov_max(:,j)/1e3/one_day 
    12811281       END IF 
    12821282    END DO 
     
    14221422         veget_cov_max, npts*nvm, horipft_index) 
    14231423    CALL histwrite_p (hist_id_stomate, 'NPP', itime, & 
    1424          npp_daily, npts*nvm, horipft_index) 
     1424         npp_daily+co2_to_bm, npts*nvm, horipft_index) 
    14251425    CALL histwrite_p (hist_id_stomate, 'GPP', itime, & 
    1426          gpp_daily, npts*nvm, horipft_index) 
     1426         gpp_daily+co2_to_bm, npts*nvm, horipft_index) 
    14271427    CALL histwrite_p (hist_id_stomate, 'IND', itime, & 
    14281428         ind, npts*nvm, horipft_index) 
     
    15281528       CALL histwrite_p (hist_id_stomate_IPCC, "lai", itime, & 
    15291529            vartmp, npts, hori_index) 
    1530        vartmp(:)=SUM(gpp_daily*veget_cov_max,dim=2)/1e3/one_day 
     1530       vartmp(:)=SUM((gpp_daily+co2_to_bm)*veget_cov_max,dim=2)/1e3/one_day 
    15311531       CALL histwrite_p (hist_id_stomate_IPCC, "gpp", itime, & 
    15321532            vartmp, npts, hori_index) 
     
    15341534       CALL histwrite_p (hist_id_stomate_IPCC, "ra", itime, & 
    15351535            vartmp, npts, hori_index) 
    1536        vartmp(:)=SUM(npp_daily*veget_cov_max,dim=2)/1e3/one_day 
     1536       vartmp(:)=SUM((npp_daily+co2_to_bm)*veget_cov_max,dim=2)/1e3/one_day 
    15371537       CALL histwrite_p (hist_id_stomate_IPCC, "npp", itime, & 
    15381538            vartmp, npts, hori_index) 
     
    15531553            vartmp, npts, hori_index) 
    15541554       ! co2_to_bm is not added as it is already included in gpp 
    1555        vartmp(:)=(SUM((gpp_daily-(resp_maint+resp_growth+resp_hetero)-co2_fire) & 
     1555       vartmp(:)=(SUM((gpp_daily+co2_to_bm-(resp_maint+resp_growth+resp_hetero)-co2_fire) & 
    15561556            &        *veget_cov_max,dim=2)-cflux_prod_total-cflux_prod_harvest_total-harvest_above)/1e3/one_day 
    15571557       CALL histwrite_p (hist_id_stomate_IPCC, "nbp", itime, & 
Note: See TracChangeset for help on using the changeset viewer.