Ignore:
Timestamp:
Nov 21, 2019, 4:43:45 PM (4 years ago)
Author:
lguez
Message:

Merge revisions 3427:3600 of trunk into branch Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/phylmd/tracco2i_mod.F90

    r3421 r3605  
    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
     
    1019
    1120    USE dimphy
    12     USE infotrac
    13     USE geometry_mod, ONLY : cell_area
    14     USE carbon_cycle_mod, ONLY : nbcf_in, fields_in, cfname_in, fco2_ocn_day, fco2_ff, fco2_bb
     21    USE infotrac_phy
     22    USE geometry_mod, ONLY: cell_area
     23    USE carbon_cycle_mod, ONLY: carbon_cycle_init
     24    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
     25    USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean
     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
    1529    USE mod_grid_phy_lmdz
    16     USE mod_phys_lmdz_mpi_data, ONLY : is_mpi_root
     30    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
    1731    USE mod_phys_lmdz_para, ONLY: gather, bcast, scatter
    1832    USE phys_cal_mod
     33    USE phys_state_var_mod, ONLY: pctsrf
     34    USE indice_sol_mod, ONLY: nbsrf, is_ter, is_lic, is_oce, is_sic
    1935
    2036    IMPLICIT NONE
     
    4561!----------------
    4662
    47     INTEGER, PARAMETER :: id_CO2=1              !--temporaire OB -- to be changed
    4863    INTEGER                        :: it, k, i, nb
    4964    REAL, DIMENSION(klon,klev)     :: m_air     ! mass of air in every grid box [kg]
    50     REAL, DIMENSION(klon)          :: co2land   ! surface land CO2 emissions [kg CO2/m2/s]
    51     REAL, DIMENSION(klon)          :: co2ocean  ! surface ocean CO2 emissions [kg CO2/m2/s]
    5265    REAL, DIMENSION(klon_glo,klev) :: co2_glo   ! variable temporaire sur la grille global
    5366    REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global
    5467
    55 
    56     INTEGER, SAVE :: mth_pre=0
    57 !$OMP THREADPRIVATE(mth_pre)
    58     REAL, SAVE :: RCO2_glo
    59 !$OMP THREADPRIVATE(RCO2_glo)
     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)
    6072
    6173    IF (is_mpi_root) THEN
     
    6779!--convert 280 ppm into kg CO2 / kg air
    6880    IF (debutphy) THEN
     81
     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
    6988      IF (MAXVAL(tr_seri(:,:,id_CO2)).LT.1.e-15) THEN
    70         tr_seri(:,:,id_CO2)=280.e-6/RMD*RMCO2
     89        tr_seri(:,:,id_CO2)=co2_ppm0*1.e-6/RMD*RMCO2 !--initialised from co2_ppm0 in rdem
    7190      ENDIF
     91
     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
     97
    7298    ENDIF
    7399
     
    85111
    86112!--retrieving land and ocean CO2 flux
    87 !--fCO2_nep comes in unit of g CO2 m-2 dt_stomate-1
    88 !--this needs to be changed in ORCHIDEE
    89     co2land(:)=0.0
    90     co2ocean(:)=0.0
     113    fco2_land(:)=0.0
     114    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
    91121    DO nb=1, nbcf_in
    92       IF (cfname_in(nb) == "fCO2_nep" )   co2land(:)=fields_in(:,nb)*RMCO2/RMC/86400./1000.
    93       !!IF (cfname_in(nb) == "fCO2_fgco2" ) co2ocean(:)=fco2_ocn_day(:) !--for now
     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
    94141    ENDDO
    95142
    96 !--preparing the net anthropogenic flux at the surface for mixing layer
    97 !--unit kg CO2 / m2 / s
    98     source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+co2land(:)+co2ocean(:)
     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
     164    source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)
    99165
    100166!--computing global mean CO2 for radiation
    101 !--every timestep for now but enough every month
    102 !    IF (debutphy.OR.mth_cur.NE.mth_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
    103171      CALL gather(tr_seri(:,:,id_CO2),co2_glo)
    104172      CALL gather(m_air,m_air_glo)
     173
    105174!$OMP MASTER
    106 !--conversion from kg CO2/kg air into ppm
     175
     176!--compute a global mean CO2 value and print its value in ppm
    107177       IF (is_mpi_root) THEN
    108          RCO2_glo=SUM(co2_glo*m_air_glo)/SUM(m_air_glo)*1.e6*RMD/RMCO2
     178         RCO2_tot=SUM(co2_glo*m_air_glo)  !--unit kg CO2
     179         RCO2_glo=RCO2_tot/SUM(m_air_glo) !--unit kg CO2 / kg air
     180         PRINT *,'tracco2i: global CO2 in ppm =', RCO2_glo*1.e6*RMD/RMCO2
     181         PRINT *,'tracco2i: total CO2 in kg =', RCO2_tot
    109182       ENDIF
    110        PRINT *,'toto in tracco2i: global CO2 in ppm =', RCO2_glo
    111183!$OMP END MASTER
    112184       CALL bcast(RCO2_glo)
    113        mth_pre=mth_cur
    114 !    ENDIF
     185       day_pre=day_cur
     186!--if not carbon_cycle_tr, then we reinitialize the CO2 each day to its global mean value
     187       IF (.NOT.carbon_cycle_tr) THEN
     188         tr_seri(:,:,id_CO2)=RCO2_glo
     189       ENDIF
     190    ENDIF
    115191
    116192  END SUBROUTINE tracco2i
     
    119195
    120196    USE dimphy
    121     USE infotrac
     197    USE infotrac_phy
    122198    USE geometry_mod, ONLY : cell_area
    123199    USE mod_grid_phy_lmdz
     
    129205    USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
    130206
    131     USE carbon_cycle_mod, ONLY : fco2_ff, fco2_bb
     207    USE carbon_cycle_mod, ONLY : fco2_ff, fco2_bb, fco2_land, fco2_ocean
    132208
    133209    IMPLICIT NONE
     
    150226!! may be controlled via the .def later on
    151227!! also co2bb for now comes from ORCHIDEE
    152     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.
     231
     232    CHARACTER (len = 20) :: modname = 'tracco2i.co2_emissions'
     233    CHARACTER (len = 80) :: abort_message
    153234
    154235    IF (debutphy) THEN
     
    173254        n_glo = size(vector)
    174255        IF (n_glo.NE.klon_glo) THEN
    175            PRINT *,'sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo'
    176            STOP
     256           abort_message='sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo'
     257           CALL abort_physic(modname,abort_message,1)
    177258        ENDIF
    178259
     
    181262        n_month = size(time)
    182263        IF (n_month.NE.12) THEN
    183            PRINT *,'sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12'
    184            STOP
     264           abort_message='sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12'
     265           CALL abort_physic(modname,abort_message,1)
    185266        ENDIF
    186267
     
    196277
    197278!--reading CO2 biomass burning emissions
     279!--using it will be inconsistent with treatment in ORCHIDEE
    198280      IF (readco2bb) THEN
    199281
     
    205287      n_glo = size(vector)
    206288      IF (n_glo.NE.klon_glo) THEN
    207          PRINT *,'sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo'
    208          STOP
     289         abort_message='sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo'
     290         CALL abort_physic(modname,abort_message,1)
    209291      ENDIF
    210292
     
    213295      n_month = size(time)
    214296      IF (n_month.NE.12) THEN
    215          PRINT *,'sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12'
    216          STOP
     297         abort_message='sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12'
     298         CALL abort_physic(modname,abort_message,1)
    217299      ENDIF
    218300
     
    247329    PRINT *,'probleme avec le mois dans co2_ini =', mth_cur
    248330  ENDIF
    249   IF (.NOT.ALLOCATED(fco2_ff)) ALLOCATE(fco2_ff(klon))
    250   IF (.NOT.ALLOCATED(fco2_bb)) ALLOCATE(fco2_bb(klon))
     331
    251332  fco2_ff(:) = flx_co2ff(:,mth_cur)
    252333  fco2_bb(:) = flx_co2bb(:,mth_cur)
Note: See TracChangeset for help on using the changeset viewer.