Ignore:
Timestamp:
Feb 26, 2021, 8:37:59 PM (3 years ago)
Author:
oboucher
Message:

Additions for the interactive carbon cycle

File:
1 edited

Legend:

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

    r3651 r3857  
    3434    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
    3535    USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean
     36    USE carbon_cycle_mod, ONLY: read_fco2_ocean_cor,var_fco2_ocean_cor,fco2_ocean_cor
     37    USE carbon_cycle_mod, ONLY: read_fco2_land_cor,var_fco2_land_cor,fco2_land_cor
     38    USE carbon_cycle_mod, ONLY: co2_send
    3639    USE carbon_cycle_mod, ONLY: fco2_land_nbp, fco2_land_nep, fco2_land_fLuc
    3740    USE carbon_cycle_mod, ONLY: fco2_land_fwoodharvest, fco2_land_fHarvest
    3841    USE carbon_cycle_mod, ONLY: carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, RCO2_glo, RCO2_tot
     42    USE carbon_cycle_mod, ONLY: ocean_area_tot
     43    USE carbon_cycle_mod, ONLY: land_area_tot
    3944    USE mod_grid_phy_lmdz
    4045    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
    4146    USE mod_phys_lmdz_para, ONLY: gather, bcast, scatter
     47    USE mod_phys_lmdz_omp_data, ONLY: is_omp_root
    4248    USE phys_cal_mod
    4349    USE phys_state_var_mod, ONLY: pctsrf
     
    7581    REAL, DIMENSION(klon_glo,klev) :: co2_glo   ! variable temporaire sur la grille global
    7682    REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global
     83    REAL, DIMENSION(klon_glo,nbsrf):: pctsrf_glo      !--fractions de maille sur la grille globale
     84    REAL, DIMENSION(klon_glo)      :: pctsrf_ter_glo
     85    REAL, DIMENSION(klon_glo)      :: pctsrf_oce_glo
     86    REAL, DIMENSION(klon_glo)      :: pctsrf_sic_glo
     87    REAL, DIMENSION(klon_glo)      :: cell_area_glo   !--aire des mailles sur la grille globale
    7788
    7889    LOGICAL, SAVE :: check_fCO2_nbp_in_cfname
     
    8091    INTEGER, SAVE :: day_pre=-1
    8192!$OMP THREADPRIVATE(day_pre)
     93
     94    REAL, PARAMETER :: secinday=86400.
    8295
    8396    IF (is_mpi_root) THEN
     
    100113        IF (cfname_in(nb)=="fCO2_nbp") check_fCO2_nbp_in_cfname=.TRUE.
    101114      ENDDO
     115
     116      CALL gather(pctsrf,pctsrf_glo)
     117      CALL gather(pctsrf(:,is_ter),pctsrf_ter_glo)
     118      CALL gather(pctsrf(:,is_oce),pctsrf_oce_glo)
     119      CALL gather(pctsrf(:,is_sic),pctsrf_sic_glo)
     120      CALL gather(cell_area(:),cell_area_glo)
    102121
    103122    ENDIF
     
    146165    ENDDO
    147166
     167    PRINT *, 'tracco2i_mod.F90 --- read_fco2_ocean_cor ',read_fco2_ocean_cor
     168    PRINT *, 'tracco2i_mod.F90 --- read_fco2_land_cor ',read_fco2_land_cor
     169
     170IF (debutphy) THEN
     171
     172    IF (read_fco2_ocean_cor) THEN
     173!$OMP MASTER
     174       IF (is_mpi_root .AND. is_omp_root) THEN
     175          ocean_area_tot=0.
     176          PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ',var_fco2_ocean_cor
     177          DO i=1, klon_glo
     178             ocean_area_tot = ocean_area_tot + (pctsrf_oce_glo(i)+pctsrf_sic_glo(i))*cell_area_glo(i)
     179          ENDDO
     180      ENDIF !--is_mpi_root and is_omp_root
     181!$OMP END MASTER
     182      CALL bcast(ocean_area_tot)
     183     PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (debutphy) ',ocean_area_tot
     184    ENDIF
     185
     186    IF (read_fco2_land_cor) THEN
     187!$OMP MASTER
     188       IF (is_mpi_root .AND. is_omp_root) THEN
     189          land_area_tot=0.
     190          PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (PgC/yr) ',var_fco2_land_cor
     191          DO i=1, klon_glo
     192             land_area_tot = land_area_tot + pctsrf_ter_glo(i)*cell_area_glo(i)
     193          ENDDO
     194      ENDIF !--is_mpi_root and is_omp_root
     195!$OMP END MASTER
     196      CALL bcast(land_area_tot)
     197     PRINT *, 'tracco2i_mod.F90 --- land_area_tot (debutphy) ',land_area_tot
     198ENDIF
     199
     200    ENDIF !-- debutphy 
     201
     202    PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (m2) ',ocean_area_tot
     203    PRINT *, 'tracco2i_mod.F90 --- land_area_tot (m2) ',land_area_tot
     204
     205    IF (read_fco2_ocean_cor) THEN
     206! var_fco2_ocean_cor: correction of the surface downward CO2 flux into the ocean fgco2 (PgC/yr)
     207! This is the correction of the the net air to ocean carbon flux. Positive flux is into the ocean.
     208!    PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ',var_fco2_ocean_cor
     209
     210!var_fco2_ocean_cor: correction of the net air to ocean carbon flux (input data is a scalar in PgC/yr and must be converted in kg CO2 m-2 s-1)
     211
     212! Factors for carbon and carbon dioxide
     213! 1 mole CO2 = 44.009 g CO2 = 12.011 g C
     214! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C
     215! 1 gC = 44.009/12.011 gCO2
     216
     217! ocean_area_tot: ocean area (m2)
     218
     219! year_len: year length (in days)
     220
     221! conversion: PgC/yr --> kg CO2 m-2 s-1
     222! fco2_ocean_cor  / (86400.*year_len): PgC/yr to PgC/s
     223! fco2_ocean_cor  / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot: PgC/s to PgC/s/m2
     224! (fco2_ocean_cor / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot) *1e12: PgC/s/m2 to kgC/s/m2
     225! (fco2_ocean_cor / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot) * 1e12 * (RMCO2/RMC): kgC/s/m2 to kgCO2/s/m2
     226
     227      DO i=1, klon 
     228          fco2_ocean_cor(i)=(var_fco2_ocean_cor*(RMCO2/RMC)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot/(secinday*year_len))*1.e12
     229      ENDDO
     230
     231      PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean_cor) ',MINVAL(fco2_ocean_cor)
     232      PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean_cor) ',MAXVAL(fco2_ocean_cor)
     233
     234    ELSE
     235    fco2_ocean_cor(:)=0.
     236    ENDIF
     237
     238    IF (read_fco2_land_cor) THEN
     239! var_fco2_land_cor: correction of the carbon Mass Flux out of Atmosphere Due to Net Biospheric Production on Land  (PgC/yr)
     240! This is the correction of the net mass flux of carbon between land and atmosphere calculated as
     241! photosynthesis MINUS the sum of plant and soil respiration, carbon fluxes from
     242! fire, harvest, grazing and land use change. Positive flux is into the land.
     243!    PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (m2) ',var_fco2_land_cor
     244
     245!var_fco2_land_cor: correction of the et air to land carbon flux (input data is a scalar in PgC/yr and must be converted in kg CO2 m-2 s-1)
     246
     247! Factors for carbon and carbon dioxide
     248! 1 mole CO2 = 44.009 g CO2 = 12.011 g C
     249! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C
     250! 1 gC = 44.009/12.011 gCO2
     251
     252! land_area_tot: land area (m2)
     253
     254! year_len: year length (in days)
     255
     256! conversion: PgC/yr --> kg CO2 m-2 s-1
     257! fco2_land_cor  / (86400.*year_len): PgC/yr to PgC/s
     258! fco2_land_cor  / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot: PgC/s to PgC/s/m2
     259! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) *1e12: PgC/s/m2 to kgC/s/m2
     260! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) * 1e12 * (RMCO2/RMC): kgC/s/m2 to kgCO2/s/m2
     261
     262      DO i=1, klon
     263         fco2_land_cor(i)=var_fco2_land_cor*RMCO2/RMC*pctsrf(i,is_ter)/land_area_tot/(secinday*year_len)*1.e12
     264      ENDDO
     265
     266      PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land_cor) ',MINVAL(fco2_land_cor)
     267      PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land_cor) ',MAXVAL(fco2_land_cor)
     268
     269    ELSE
     270      fco2_land_cor(:)=0.
     271    ENDIF
     272
    148273!--if fCO2_nbp is transferred we use it, otherwise we use the sum of what has been passed from ORCHIDEE
    149274    IF (check_fCO2_nbp_in_cfname)  THEN
     
    167292!
    168293!--build final source term for CO2
    169     source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)
     294    source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)-fco2_ocean_cor(:)-fco2_land_cor(:)
    170295
    171296!--computing global mean CO2 for radiation
     
    195320    ENDIF
    196321
     322    PRINT *, 'tracco2i_mod.F90 --- MINVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2): L1: ',MINVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2)
     323    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2): L1: ',MAXVAL(tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2)
     324
     325    PRINT *, 'tracco2i_mod.F90 --- MINVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2): L79: ',MINVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2)
     326    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2): L79: ',MAXVAL(tr_seri(:,79,id_CO2)*1.e6*RMD/RMCO2)
     327
     328    co2_send(:) = tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2
     329
     330    PRINT *, 'tracco2i_mod.F90 --- MINVAL(co2_send) ',MINVAL(co2_send)
     331    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(co2_send) ',MAXVAL(co2_send)
     332
    197333  END SUBROUTINE tracco2i
    198334
     
    252388      IF (readco2ff) THEN
    253389
    254         ! ... Open the COZff file
     390        ! ... Open the CO2ff file
    255391        CALL nf95_open("sflx_lmdz_co2_ff.nc", nf90_nowrite, ncid_in)
    256392
Note: See TracChangeset for help on using the changeset viewer.