Ignore:
Timestamp:
Oct 10, 2019, 2:35:59 PM (5 years ago)
Author:
oboucher
Message:

Big update to the interactive carbon cycle
from Patricia's code

File:
1 edited

Legend:

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

    r3549 r3581  
    22!
    33! This module does the work for the interactive CO2 tracers
     4! Authors: Patricia Cadule and Olivier Boucher
     5!
     6! Purpose and description:
     7!  -----------------------
     8! Main routine for the interactive carbon cycle
     9! Gather all carbon fluxes and emissions from ORCHIDEE, PISCES and fossil fuel
     10! Compute the net flux in source field which is used in phytrac
     11! Compute global CO2 mixing ratio for radiation scheme if option is activated
     12! Redistribute CO2 evenly over the atmosphere if transport is desactivated
    413!
    514CONTAINS
     
    1221    USE infotrac_phy
    1322    USE geometry_mod, ONLY: cell_area
     23    USE carbon_cycle_mod, ONLY: carbon_cycle_init
    1424    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
    1525    USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean
    16     USE carbon_cycle_mod, ONLY: carbon_cycle_tr, carbon_cycle_rad, RCO2_glo, RCO2_tot
     26    USE carbon_cycle_mod, ONLY: fco2_land_nbp, fco2_land_nep, fco2_land_fLuc
     27    USE carbon_cycle_mod, ONLY: fco2_land_fwoodharvest, fco2_land_fHarvest
     28    USE carbon_cycle_mod, ONLY: carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, RCO2_glo, RCO2_tot
    1729    USE mod_grid_phy_lmdz
    1830    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
     
    5466    REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global
    5567
    56     INTEGER, SAVE :: mth_pre=0, day_pre=0
    57 !$OMP THREADPRIVATE(mth_pre, day_pre)
     68    LOGICAL, SAVE :: check_fCO2_nbp_in_cfname
     69!$OMP THREADPRIVATE(check_fCO2_nbp_in_cfname)
     70    INTEGER, SAVE :: day_pre=-1
     71!$OMP THREADPRIVATE(day_pre)
    5872
    5973    IF (is_mpi_root) THEN
     
    6680    IF (debutphy) THEN
    6781
     82! Initialisation de module carbon_cycle_mod
     83      IF (carbon_cycle_cpl) THEN
     84        CALL carbon_cycle_init()
     85      ENDIF
     86
     87! Initialisation de tr_seri(id_CO2) si pas initialise
    6888      IF (MAXVAL(tr_seri(:,:,id_CO2)).LT.1.e-15) THEN
    69         !!tr_seri(:,:,id_CO2)=280.e-6/RMD*RMCO2
    70         tr_seri(:,:,id_CO2)=400.e-6/RMD*RMCO2 !--initialised to 400 ppm for a test
     89        tr_seri(:,:,id_CO2)=co2_ppm0*1.e-6/RMD*RMCO2 !--initialised from co2_ppm0 in rdem
    7190      ENDIF
    7291
    73       ALLOCATE(fco2_ff(klon))
    74       ALLOCATE(fco2_bb(klon))
    75       ALLOCATE(fco2_land(klon))
    76       ALLOCATE(fco2_ocean(klon))
     92!--check if fCO2_nbp is in
     93      check_fCO2_nbp_in_cfname=.FALSE.
     94      DO nb=1, nbcf_in
     95        IF (cfname_in(nb)=="fCO2_nbp") check_fCO2_nbp_in_cfname=.TRUE.
     96      ENDDO
    7797
    7898    ENDIF
     
    93113    fco2_land(:)=0.0
    94114    fco2_ocean(:)=0.0
     115    fco2_land_nbp(:)=0.
     116    fco2_land_nep(:)=0.
     117    fco2_land_fLuc(:)=0.
     118    fco2_land_fwoodharvest(:)=0.
     119    fco2_land_fHarvest(:)=0.
     120
    95121    DO nb=1, nbcf_in
    96       print *,'nb tracco2=', nb, cfname_in(nb)
    97 !--fCO2_nep comes in unit of kg C m-2 s-1
    98 !--converting to kg CO2 m-2 s-1
    99       IF (cfname_in(nb) == "fCO2_nbp" )   fco2_land(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
    100 !--fCO2_fgco2 comes in unit of mol C02 m-2 s-1
    101 !--converting to kg CO2 m-2 s-1 + change sign
    102       IF (cfname_in(nb) == "fCO2_fgco2" ) fco2_ocean(:)=-1.*fco2_ocn_day(:)*RMCO2/1.e3*(pctsrf(:,is_oce)+pctsrf(:,is_sic))
     122
     123      SELECT CASE(cfname_in(nb))
     124!--dealing with the different fluxes coming from ORCHIDEE
     125!--fluxes come in unit of kg C m-2 s-1 is converted into kg CO2 m-2 s-1
     126      CASE("fCO2_nep")
     127          fco2_land_nep(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
     128      CASE("fCO2_fLuc")
     129          fco2_land_fLuc(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
     130      CASE("fCO2_fwoodharvest")
     131          fco2_land_fwoodharvest(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
     132      CASE("fCO2_fHarvest")
     133          fco2_land_fHarvest(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
     134      CASE("fCO2_nbp")
     135          fco2_land_nbp(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
     136!--fCO2_fco2_ocn comes in unit of mol C02 m-2 s-1 is converted into kg CO2 m-2 s-1 + change sign
     137      CASE("fCO2_fgco2")
     138          fco2_ocean(:)=-1.*fco2_ocn_day(:)*RMCO2/1.e3*(pctsrf(:,is_oce)+pctsrf(:,is_sic))
     139      END SELECT
     140
    103141    ENDDO
    104142
    105 !--preparing the net anthropogenic flux at the surface for mixing layer
    106 !--unit kg CO2 / m2 / s
     143!--if fCO2_nbp is transferred we use it, otherwise we use the sum of what has been passed from ORCHIDEE
     144    IF (check_fCO2_nbp_in_cfname)  THEN
     145       fco2_land(:)=fco2_land_nbp(:)
     146    ELSE
     147       fco2_land(:)=fco2_land_nep(:)+fco2_land_fLuc(:)+fco2_land_fwoodharvest(:)+fco2_land_fHarvest(:)
     148    ENDIF
     149
     150!!--preparing the net anthropogenic flux at the surface for mixing layer
     151!!--unit kg CO2 / m2 / s
     152!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ff) ',MAXVAL(fco2_ff)
     153!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ff) ',MINVAL(fco2_ff)
     154!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_bb) ',MAXVAL(fco2_bb)
     155!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_bb) ',MINVAL(fco2_bb)
     156!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land) ',MAXVAL(fco2_land)
     157!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land) ',MINVAL(fco2_land)
     158!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean) ',MAXVAL(fco2_ocean)
     159!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean) ',MINVAL(fco2_ocean)
     160!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(source(:,id_CO2)) ',MAXVAL(source(:,id_CO2))
     161!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(source(:,id_CO2)) ',MINVAL(source(:,id_CO2))
     162!
     163!--build final source term for CO2
    107164    source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)
    108165
    109166!--computing global mean CO2 for radiation
    110 !--every timestep for now but enough every day
    111 !    IF (debutphy.OR.mth_cur.NE.mth_pre) THEN
    112 !    IF (debutphy.OR.day_cur.NE.day_pre) THEN
     167!--for every timestep comment out the IF ENDIF statements
     168!--otherwise this is updated every day
     169    IF (debutphy.OR.day_cur.NE.day_pre) THEN
     170
    113171      CALL gather(tr_seri(:,:,id_CO2),co2_glo)
    114172      CALL gather(m_air,m_air_glo)
     173
    115174!$OMP MASTER
    116175
     
    124183!$OMP END MASTER
    125184       CALL bcast(RCO2_glo)
    126        mth_pre=mth_cur
    127185       day_pre=day_cur
    128186!--if not carbon_cycle_tr, then we reinitialize the CO2 each day to its global mean value
     
    130188         tr_seri(:,:,id_CO2)=RCO2_glo
    131189       ENDIF
    132 !    ENDIF
     190    ENDIF
    133191
    134192  END SUBROUTINE tracco2i
     
    168226!! may be controlled via the .def later on
    169227!! also co2bb for now comes from ORCHIDEE
    170     LOGICAL, PARAMETER :: readco2ff=.TRUE., readco2bb=.FALSE.
     228    LOGICAL, PARAMETER :: readco2ff=.TRUE.
     229!! this should be left to FALSE for now
     230    LOGICAL, PARAMETER :: readco2bb=.FALSE.
    171231
    172232    CHARACTER (len = 20) :: modname = 'tracco2i.co2_emissions'
     
    217277
    218278!--reading CO2 biomass burning emissions
     279!--using it will be inconsistent with treatment in ORCHIDEE
    219280      IF (readco2bb) THEN
    220281
Note: See TracChangeset for help on using the changeset viewer.