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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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.