Ignore:
Timestamp:
Jan 28, 2019, 7:31:11 PM (5 years ago)
Author:
oboucher
Message:

Adding some diagnostics for type_trac=co2i

Location:
LMDZ6/trunk/libf/phylmd
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/carbon_cycle_mod.F90

    r3447 r3453  
    8282  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_bb ! Emission from biomass burning [kgCO2/m2/s]
    8383!$OMP THREADPRIVATE(fco2_bb)
     84  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_land  ! Net flux from terrestrial ecocsystems [kgCO2/m2/s]
     85!$OMP THREADPRIVATE(fco2_land)
     86  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocean ! Net flux from ocean [kgCO2/m2/s]
     87!$OMP THREADPRIVATE(fco2_ocean)
    8488
    8589  REAL, DIMENSION(:,:), ALLOCATABLE :: dtr_add       ! Tracer concentration to be injected
  • LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r3332 r3453  
    77  USE indice_sol_mod
    88  USE aero_mod
    9 
    10 
    119
    1210  IMPLICIT NONE
     
    10141012!FC
    10151013
    1016 
    10171014  TYPE(ctrl_out), SAVE, DIMENSION(4) :: o_l_mixmin      = (/             &
    10181015      ctrl_out((/ 10, 10, 10, 10, 10, 10, 11, 11, 11, 11/),'l_mixmin_ter',       &
     
    12801277!--end add ThL
    12811278
     1279!---CO2 fluxes for interactive CO2 configuration
     1280  TYPE(ctrl_out), SAVE :: o_flx_co2_ff = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
     1281    'flx_co2_ff', 'CO2 flux from fossil fuel and cement', '1', (/ ('', i=1, 10) /))
     1282  TYPE(ctrl_out), SAVE :: o_flx_co2_bb = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
     1283    'flx_co2_bb', 'CO2 flux from biomass burning', '1', (/ ('', i=1, 10) /))
     1284  TYPE(ctrl_out), SAVE :: o_flx_co2_ocean = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
     1285    'flx_co2_ocean', 'CO2 flux from the ocean', '1', (/ ('', i=1, 10) /))
     1286  TYPE(ctrl_out), SAVE :: o_flx_co2_land = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 1/), &
     1287    'flx_co2_land', 'CO2 flux from the land', '1', (/ ('', i=1, 10) /))
     1288
    12821289#ifdef CPP_StratAer
    12831290!--extinction coefficient
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r3435 r3453  
    196196! Tropopause
    197197         o_p_tropopause, o_z_tropopause, o_t_tropopause,  &
    198          o_col_O3_strato, o_col_O3_tropo               ! Added ThL
     198         o_col_O3_strato, o_col_O3_tropo,                 &
     199!--interactive CO2
     200         o_flx_co2_ocean, o_flx_co2_land, o_flx_co2_ff, o_flx_co2_bb
    199201
    200202
     
    327329    USE CHEM_REP, ONLY : nas, nbnas, tnamenas, ttextnas
    328330#endif
     331
     332    USE carbon_cycle_mod, ONLY: fco2_ff, fco2_bb, fco2_land, fco2_ocean
    329333
    330334    USE phys_output_var_mod, ONLY: vars_defined, snow_o, zfra_o, bils_diss, &
     
    12531257          IF (slab_gm) THEN
    12541258             CALL histwrite_phy(o_slab_gm, dt_gm(:,1:nslay))
    1255           END IF
     1259          ENDIF
    12561260          IF (slab_hdiff) THEN
    12571261            IF (nslay.EQ.1) THEN
     
    16631667       ENDIF
    16641668       CALL histwrite_phy(o_dtcon, zx_tmp_fi3d)
    1665        if(iflag_thermals.eq.0)then
     1669       IF (iflag_thermals.EQ.0) THEN
    16661670          IF (vars_defined) THEN
    16671671             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
     
    16691673          ENDIF
    16701674          CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
    1671        else if(iflag_thermals.ge.1.and.iflag_wake.EQ.1)then
     1675       ELSE IF(iflag_thermals.GE.1.AND.iflag_wake.EQ.1) THEN
    16721676          IF (vars_defined) THEN
    16731677             zx_tmp_fi3d(1:klon,1:klev)=d_t_con(1:klon,1:klev)/pdtphys + &
     
    16761680          ENDIF
    16771681          CALL histwrite_phy(o_tntc, zx_tmp_fi3d)
    1678        endif
     1682       ENDIF
    16791683       IF (vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_con(1:klon,1:klev)/pdtphys
    16801684       CALL histwrite_phy(o_ducon, zx_tmp_fi3d)
     
    17271731          CALL histwrite_phy(o_plulst, plul_st)
    17281732          IF (vars_defined) THEN
    1729              do i=1,klon
     1733             DO i=1,klon
    17301734                zx_tmp_fi2d(1:klon)=lmax_th(:)
    1731              enddo
     1735             ENDDO
    17321736          ENDIF
    17331737          CALL histwrite_phy(o_lmaxth, zx_tmp_fi2d)
     
    21922196            IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag') THEN
    21932197             !--3D fields
    2194 !             CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
    2195 !             CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
    2196 !             CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo))
    2197 !             CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo))
    2198 !             CALL histwrite_phy(o_dtr_lessi_impa(iq-nqo),d_tr_lessi_impa(:,:,iq-nqo))
    2199 !             CALL histwrite_phy(o_dtr_lessi_nucl(iq-nqo),d_tr_lessi_nucl(:,:,iq-nqo))
    2200 !             CALL histwrite_phy(o_dtr_insc(iq-nqo),d_tr_insc(:,:,iq-nqo))
    2201 !             CALL histwrite_phy(o_dtr_bcscav(iq-nqo),d_tr_bcscav(:,:,iq-nqo))
    2202 !             CALL histwrite_phy(o_dtr_evapls(iq-nqo),d_tr_evapls(:,:,iq-nqo))
    2203 !             CALL histwrite_phy(o_dtr_ls(iq-nqo),d_tr_ls(:,:,iq-nqo))
    2204 !             CALL histwrite_phy(o_dtr_trsp(iq-nqo),d_tr_trsp(:,:,iq-nqo))
    2205 !             CALL histwrite_phy(o_dtr_sscav(iq-nqo),d_tr_sscav(:,:,iq-nqo))
    2206 !             CALL histwrite_phy(o_dtr_sat(iq-nqo),d_tr_sat(:,:,iq-nqo))
    2207 !             CALL histwrite_phy(o_dtr_uscav(iq-nqo),d_tr_uscav(:,:,iq-nqo))
    2208              !--2D fields
    2209 !             CALL histwrite_phy(o_dtr_dry(iq-nqo), flux_tr_dry(:,iq-nqo))
     2198             CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
     2199             CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
     2200             CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo))
     2201             CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo))
     2202             CALL histwrite_phy(o_dtr_lessi_impa(iq-nqo),d_tr_lessi_impa(:,:,iq-nqo))
     2203             CALL histwrite_phy(o_dtr_lessi_nucl(iq-nqo),d_tr_lessi_nucl(:,:,iq-nqo))
     2204             CALL histwrite_phy(o_dtr_insc(iq-nqo),d_tr_insc(:,:,iq-nqo))
     2205             CALL histwrite_phy(o_dtr_bcscav(iq-nqo),d_tr_bcscav(:,:,iq-nqo))
     2206             CALL histwrite_phy(o_dtr_evapls(iq-nqo),d_tr_evapls(:,:,iq-nqo))
     2207             CALL histwrite_phy(o_dtr_ls(iq-nqo),d_tr_ls(:,:,iq-nqo))
     2208             CALL histwrite_phy(o_dtr_trsp(iq-nqo),d_tr_trsp(:,:,iq-nqo))
     2209             CALL histwrite_phy(o_dtr_sscav(iq-nqo),d_tr_sscav(:,:,iq-nqo))
     2210             CALL histwrite_phy(o_dtr_sat(iq-nqo),d_tr_sat(:,:,iq-nqo))
     2211             CALL histwrite_phy(o_dtr_uscav(iq-nqo),d_tr_uscav(:,:,iq-nqo))
     2212            !--2D fields
     2213             CALL histwrite_phy(o_dtr_dry(iq-nqo), flux_tr_dry(:,iq-nqo))
    22102214             zx_tmp_fi2d=0.
    22112215             IF (vars_defined) THEN
     
    22172221             CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d)
    22182222#endif
    2219             ENDIF
    2220           ENDDO
    2221        ENDIF
     2223            ENDIF   !--type_trac
     2224!
     2225            IF (type_trac == 'co2i') THEN
     2226             !--3D fields
     2227             CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
     2228             CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
     2229             CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo))
     2230             CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo))
     2231             !--2D fields
     2232             !--CO2 burden
     2233             zx_tmp_fi2d=0.
     2234             IF (vars_defined) THEN
     2235                DO k=1,klev
     2236                   zx_tmp_fi2d(:)=zx_tmp_fi2d(:)+zmasse(:,k)*tr_seri(:,k,iq-nqo)
     2237                ENDDO
     2238             ENDIF
     2239             CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d)
     2240             !--CO2 net fluxes
     2241             CALL histwrite_phy(o_flx_co2_land,  fco2_land)
     2242             CALL histwrite_phy(o_flx_co2_ocean, fco2_ocean)
     2243             CALL histwrite_phy(o_flx_co2_ff,    fco2_ff)
     2244             CALL histwrite_phy(o_flx_co2_bb,    fco2_bb)
     2245            ENDIF !--type_trac co2i
     2246
     2247          ENDDO !--iq
     2248       ENDIF !--nqtot > nqo+1
    22222249
    22232250       IF (type_trac == 'repr') THEN
     
    22302257
    22312258       ENDIF   !(iflag_phytrac==1)
    2232 
    22332259
    22342260       IF (.NOT.vars_defined) THEN
  • LMDZ6/trunk/libf/phylmd/tracco2i_mod.F90

    r3450 r3453  
    1212    USE infotrac_phy
    1313    USE geometry_mod, ONLY: cell_area
    14     USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in, fco2_ocn_day, fco2_ff, fco2_bb
     14    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
     15    USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean
    1516    USE carbon_cycle_mod, ONLY: carbon_cycle_tr, carbon_cycle_rad, RCO2_glo, RCO2_tot
    1617    USE mod_grid_phy_lmdz
     
    5051    INTEGER                        :: it, k, i, nb
    5152    REAL, DIMENSION(klon,klev)     :: m_air     ! mass of air in every grid box [kg]
    52     REAL, DIMENSION(klon)          :: co2land   ! surface land CO2 emissions [kg CO2/m2/s]
    53     REAL, DIMENSION(klon)          :: co2ocean  ! surface ocean CO2 emissions [kg CO2/m2/s]
    5453    REAL, DIMENSION(klon_glo,klev) :: co2_glo   ! variable temporaire sur la grille global
    5554    REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global
     
    8584
    8685!--retrieving land and ocean CO2 flux
    87     co2land(:)=0.0
    88     co2ocean(:)=0.0
     86    fco2_land(:)=0.0
     87    fco2_ocean(:)=0.0
    8988    DO nb=1, nbcf_in
    9089!--fCO2_nep comes in unit of kg C m-2 s-1
    9190!--converting to kg CO2 m-2 s-1
    92       IF (cfname_in(nb) == "fCO2_nep" )   co2land(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
     91      IF (cfname_in(nb) == "fCO2_nep" )   fco2_land(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
    9392!--fCO2_fgco2 comes in unit of mol C02 m-2 s-1
    9493!--converting to kg CO2 m-2 s-1 + change sign
    95       IF (cfname_in(nb) == "fCO2_fgco2" ) co2ocean(:)=-1.*fco2_ocn_day(:)*RMCO2/1.e3*(pctsrf(:,is_oce)+pctsrf(:,is_sic))
     94      IF (cfname_in(nb) == "fCO2_fgco2" ) fco2_ocean(:)=-1.*fco2_ocn_day(:)*RMCO2/1.e3*(pctsrf(:,is_oce)+pctsrf(:,is_sic))
    9695    ENDDO
    9796
    98 !--preparing the net anthropogenic flux at the surface for mixing layer 
     97!--preparing the net anthropogenic flux at the surface for mixing layer
    9998!--unit kg CO2 / m2 / s
    100     source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+co2land(:)+co2ocean(:)
     99    source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)
    101100
    102101!--computing global mean CO2 for radiation
Note: See TracChangeset for help on using the changeset viewer.