MODULE tracco2i_mod ! This module does the work for the interactive CO2 tracers ! Authors: Patricia Cadule and Olivier Boucher ! Purpose and description: ! ----------------------- ! Main routine for the interactive carbon cycle ! Gather all carbon fluxes and emissions from ORCHIDEE, PISCES and fossil fuel ! Compute the net flux in source field which is used in phytrac ! Compute global CO2 mixing ratio for radiation scheme if option is activated ! Redistribute CO2 evenly over the atmosphere if transport is desactivated CONTAINS SUBROUTINE tracco2i_init() ! This SUBROUTINE calls carbon_cycle_init needed to be done before first CALL to phys_output_write in physiq. USE carbon_cycle_mod, ONLY: carbon_cycle_init, carbon_cycle_cpl ! Initialize carbon_cycle_mod IF (carbon_cycle_cpl) THEN CALL carbon_cycle_init() ENDIF END SUBROUTINE tracco2i_init SUBROUTINE tracco2i(pdtphys, debutphy, & xlat, xlon, pphis, pphi, & t_seri, pplay, paprs, tr_seri, source) USE dimphy USE infotrac_phy, ONLY: nbtr USE lmdz_geometry, ONLY: cell_area USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean USE carbon_cycle_mod, ONLY: read_fco2_ocean_cor, var_fco2_ocean_cor, fco2_ocean_cor USE carbon_cycle_mod, ONLY: read_fco2_land_cor, var_fco2_land_cor, fco2_land_cor USE carbon_cycle_mod, ONLY: co2_send USE carbon_cycle_mod, ONLY: fco2_land_nbp, fco2_land_nep, fco2_land_fLuc USE carbon_cycle_mod, ONLY: fco2_land_fwoodharvest, fco2_land_fHarvest USE carbon_cycle_mod, ONLY: carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, RCO2_glo, RCO2_tot USE carbon_cycle_mod, ONLY: ocean_area_tot USE carbon_cycle_mod, ONLY: land_area_tot USE lmdz_grid_phy USE lmdz_phys_mpi_data, ONLY: is_mpi_root USE lmdz_phys_para, ONLY: gather, bcast, scatter USE lmdz_phys_omp_data, ONLY: is_omp_root USE phys_cal_mod USE phys_state_var_mod, ONLY: pctsrf USE indice_sol_mod, ONLY: nbsrf, is_ter, is_lic, is_oce, is_sic IMPLICIT NONE INCLUDE "clesphys.h" INCLUDE "YOMCST.h" ! Input argument !--------------- REAL, INTENT(IN) :: pdtphys ! Pas d'integration pour la physique (seconde) LOGICAL, INTENT(IN) :: debutphy ! le flag de l'initialisation de la physique REAL, DIMENSION(klon), INTENT(IN) :: xlat ! latitudes pour chaque point REAL, DIMENSION(klon), INTENT(IN) :: xlon ! longitudes pour chaque point REAL, DIMENSION(klon), INTENT(IN) :: pphis ! geopotentiel du sol REAL, DIMENSION(klon, klev), INTENT(IN) :: pphi ! geopotentiel de chaque couche REAL, DIMENSION(klon, klev), INTENT(IN) :: t_seri ! Temperature REAL, DIMENSION(klon, klev), INTENT(IN) :: pplay ! pression pour le mileu de chaque couche (en Pa) REAL, DIMENSION(klon, klev + 1), INTENT(IN) :: paprs ! pression pour chaque inter-couche (en Pa) REAL, DIMENSION(klon, nbtr), INTENT(INOUT) :: source ! flux de traceur [U/m2/s] ! Output argument !---------------- REAL, DIMENSION(klon, klev, nbtr), INTENT(INOUT) :: tr_seri ! Concentration Traceur [U/kgA] ! Local variables !---------------- INTEGER :: it, k, i, nb REAL, DIMENSION(klon, klev) :: m_air ! mass of air in every grid box [kg] REAL, DIMENSION(klon_glo, klev) :: co2_glo ! variable temporaire sur la grille global REAL, DIMENSION(klon_glo, klev) :: m_air_glo ! variable temporaire sur la grille global REAL, DIMENSION(klon_glo, nbsrf) :: pctsrf_glo !--fractions de maille sur la grille globale REAL, DIMENSION(klon_glo) :: pctsrf_ter_glo REAL, DIMENSION(klon_glo) :: pctsrf_oce_glo REAL, DIMENSION(klon_glo) :: pctsrf_sic_glo REAL, DIMENSION(klon_glo) :: cell_area_glo !--aire des mailles sur la grille globale LOGICAL, SAVE :: check_fCO2_nbp_in_cfname !$OMP THREADPRIVATE(check_fCO2_nbp_in_cfname) INTEGER, SAVE :: day_pre = -1 !$OMP THREADPRIVATE(day_pre) REAL, PARAMETER :: secinday = 86400. IF (is_mpi_root) THEN PRINT *, 'in tracco2i: date from phys_cal_mod =', year_cur, '-', mth_cur, '-', day_cur, '-', hour ENDIF !--initialisation of CO2 field if not in restart file !--dirty way of doing, do it better later !--convert 280 ppm into kg CO2 / kg air IF (debutphy) THEN ! Initialization of tr_seri(id_CO2) If it is not initialized IF (MAXVAL(tr_seri(:, :, id_CO2))<1.e-15) THEN tr_seri(:, :, id_CO2) = co2_ppm0 * 1.e-6 / RMD * RMCO2 !--initialised from co2_ppm0 in rdem ENDIF !--check if fCO2_nbp is in check_fCO2_nbp_in_cfname = .FALSE. DO nb = 1, nbcf_in IF (cfname_in(nb)=="fCO2_nbp") check_fCO2_nbp_in_cfname = .TRUE. ENDDO CALL gather(pctsrf, pctsrf_glo) CALL gather(pctsrf(:, is_ter), pctsrf_ter_glo) CALL gather(pctsrf(:, is_oce), pctsrf_oce_glo) CALL gather(pctsrf(:, is_sic), pctsrf_sic_glo) CALL gather(cell_area(:), cell_area_glo) ENDIF !--calculate mass of air in every grid box in kg air DO i = 1, klon DO k = 1, klev m_air(i, k) = (paprs(i, k) - paprs(i, k + 1)) / RG * cell_area(i) ENDDO ENDDO !--CALL CO2 emission routine !--co2bb is zero for now !--unit kg CO2 m-2 s-1 CALL co2_emissions(debutphy) !--retrieving land and ocean CO2 flux fco2_land(:) = 0.0 fco2_ocean(:) = 0.0 fco2_land_nbp(:) = 0. fco2_land_nep(:) = 0. fco2_land_fLuc(:) = 0. fco2_land_fwoodharvest(:) = 0. fco2_land_fHarvest(:) = 0. DO nb = 1, nbcf_in SELECT CASE(cfname_in(nb)) !--dealing with the different fluxes coming from ORCHIDEE !--fluxes come in unit of kg C m-2 s-1 is converted into kg CO2 m-2 s-1 CASE("fCO2_nep") fco2_land_nep(:) = fields_in(:, nb) * RMCO2 / RMC * pctsrf(:, is_ter) CASE("fCO2_fLuc") fco2_land_fLuc(:) = fields_in(:, nb) * RMCO2 / RMC * pctsrf(:, is_ter) CASE("fCO2_fwoodharvest") fco2_land_fwoodharvest(:) = fields_in(:, nb) * RMCO2 / RMC * pctsrf(:, is_ter) CASE("fCO2_fHarvest") fco2_land_fHarvest(:) = fields_in(:, nb) * RMCO2 / RMC * pctsrf(:, is_ter) CASE("fCO2_nbp") fco2_land_nbp(:) = fields_in(:, nb) * RMCO2 / RMC * pctsrf(:, is_ter) !--fCO2_fco2_ocn comes in unit of mol C02 m-2 s-1 is converted into kg CO2 m-2 s-1 + change sign CASE("fCO2_fgco2") fco2_ocean(:) = -1. * fco2_ocn_day(:) * RMCO2 / 1.e3 * (pctsrf(:, is_oce) + pctsrf(:, is_sic)) END SELECT ENDDO PRINT *, 'tracco2i_mod.F90 --- read_fco2_ocean_cor ', read_fco2_ocean_cor PRINT *, 'tracco2i_mod.F90 --- read_fco2_land_cor ', read_fco2_land_cor IF (debutphy) THEN IF (read_fco2_ocean_cor) THEN !$OMP MASTER IF (is_mpi_root .AND. is_omp_root) THEN ocean_area_tot = 0. PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ', var_fco2_ocean_cor DO i = 1, klon_glo ocean_area_tot = ocean_area_tot + (pctsrf_oce_glo(i) + pctsrf_sic_glo(i)) * cell_area_glo(i) ENDDO ENDIF !--is_mpi_root and is_omp_root !$OMP END MASTER CALL bcast(ocean_area_tot) PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (debutphy) ', ocean_area_tot ENDIF IF (read_fco2_land_cor) THEN !$OMP MASTER IF (is_mpi_root .AND. is_omp_root) THEN land_area_tot = 0. PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (PgC/yr) ', var_fco2_land_cor DO i = 1, klon_glo land_area_tot = land_area_tot + pctsrf_ter_glo(i) * cell_area_glo(i) ENDDO ENDIF !--is_mpi_root and is_omp_root !$OMP END MASTER CALL bcast(land_area_tot) PRINT *, 'tracco2i_mod.F90 --- land_area_tot (debutphy) ', land_area_tot ENDIF ENDIF !-- debutphy PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (m2) ', ocean_area_tot PRINT *, 'tracco2i_mod.F90 --- land_area_tot (m2) ', land_area_tot IF (read_fco2_ocean_cor) THEN ! var_fco2_ocean_cor: correction of the surface downward CO2 flux into the ocean fgco2 (PgC/yr) ! This is the correction of the the net air to ocean carbon flux. Positive flux is into the ocean. ! PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ',var_fco2_ocean_cor !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) ! Factors for carbon and carbon dioxide ! 1 mole CO2 = 44.009 g CO2 = 12.011 g C ! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C ! 1 gC = 44.009/12.011 gCO2 ! ocean_area_tot: ocean area (m2) ! year_len: year length (in days) ! conversion: PgC/yr --> kg CO2 m-2 s-1 ! fco2_ocean_cor / (86400.*year_len): PgC/yr to PgC/s ! fco2_ocean_cor / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot: PgC/s to PgC/s/m2 ! (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 ! (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 DO i = 1, klon 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 ENDDO PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean_cor) ', MINVAL(fco2_ocean_cor) PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean_cor) ', MAXVAL(fco2_ocean_cor) ELSE fco2_ocean_cor(:) = 0. ENDIF IF (read_fco2_land_cor) THEN ! var_fco2_land_cor: correction of the carbon Mass Flux out of Atmosphere Due to Net Biospheric Production on Land (PgC/yr) ! This is the correction of the net mass flux of carbon between land and atmosphere calculated as ! photosynthesis MINUS the sum of plant and soil respiration, carbon fluxes from ! fire, harvest, grazing and land use change. Positive flux is into the land. ! PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (m2) ',var_fco2_land_cor !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) ! Factors for carbon and carbon dioxide ! 1 mole CO2 = 44.009 g CO2 = 12.011 g C ! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C ! 1 gC = 44.009/12.011 gCO2 ! land_area_tot: land area (m2) ! year_len: year length (in days) ! conversion: PgC/yr --> kg CO2 m-2 s-1 ! fco2_land_cor / (86400.*year_len): PgC/yr to PgC/s ! fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot: PgC/s to PgC/s/m2 ! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) *1e12: PgC/s/m2 to kgC/s/m2 ! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) * 1e12 * (RMCO2/RMC): kgC/s/m2 to kgCO2/s/m2 DO i = 1, klon fco2_land_cor(i) = var_fco2_land_cor * RMCO2 / RMC * pctsrf(i, is_ter) / land_area_tot / (secinday * year_len) * 1.e12 ENDDO PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land_cor) ', MINVAL(fco2_land_cor) PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land_cor) ', MAXVAL(fco2_land_cor) ELSE fco2_land_cor(:) = 0. ENDIF !--if fCO2_nbp is transferred we use it, otherwise we use the sum of what has been passed from ORCHIDEE IF (check_fCO2_nbp_in_cfname) THEN fco2_land(:) = fco2_land_nbp(:) ELSE fco2_land(:) = fco2_land_nep(:) + fco2_land_fLuc(:) + fco2_land_fwoodharvest(:) + fco2_land_fHarvest(:) ENDIF !!--preparing the net anthropogenic flux at the surface for mixing layer !!--unit kg CO2 / m2 / s ! PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ff) ',MAXVAL(fco2_ff) ! PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ff) ',MINVAL(fco2_ff) ! PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_bb) ',MAXVAL(fco2_bb) ! PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_bb) ',MINVAL(fco2_bb) ! PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land) ',MAXVAL(fco2_land) ! PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land) ',MINVAL(fco2_land) ! PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean) ',MAXVAL(fco2_ocean) ! PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean) ',MINVAL(fco2_ocean) ! PRINT *, 'tracco2i_mod.F90 --- MAXVAL(source(:,id_CO2)) ',MAXVAL(source(:,id_CO2)) ! PRINT *, 'tracco2i_mod.F90 --- MINVAL(source(:,id_CO2)) ',MINVAL(source(:,id_CO2)) !--build final source term for CO2 source(:, id_CO2) = fco2_ff(:) + fco2_bb(:) + fco2_land(:) + fco2_ocean(:) - fco2_ocean_cor(:) - fco2_land_cor(:) !--computing global mean CO2 for radiation !--for every timestep comment out the IF ENDIF statements !--otherwise this is updated every day IF (debutphy.OR.day_cur/=day_pre) THEN CALL gather(tr_seri(:, :, id_CO2), co2_glo) CALL gather(m_air, m_air_glo) !$OMP MASTER !--compute a global mean CO2 value and print its value in ppm IF (is_mpi_root .AND. is_omp_root) THEN RCO2_tot = SUM(co2_glo * m_air_glo) !--unit kg CO2 RCO2_glo = RCO2_tot / SUM(m_air_glo) !--unit kg CO2 / kg air ! the following operation is only to maintain precision consistency ! of RCO2_glo which differs whether it is directly computed or read from ! a restart file (after having been computed) RCO2_glo = FLOAT(INT(RCO2_glo * 1e8)) / 1e8 PRINT *, 'tracco2i: global CO2 in ppm =', RCO2_glo * 1.e6 * RMD / RMCO2 PRINT *, 'tracco2i: total CO2 in kg =', RCO2_tot ENDIF !$OMP END MASTER CALL bcast(RCO2_glo) day_pre = day_cur !--if not carbon_cycle_tr, then we reinitialize the CO2 each day to its global mean value IF (.NOT.carbon_cycle_tr) THEN tr_seri(:, :, id_CO2) = RCO2_glo ENDIF ENDIF 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) 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) 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) 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) co2_send(:) = tr_seri(:, 1, id_CO2) * 1.e6 * RMD / RMCO2 PRINT *, 'tracco2i_mod.F90 --- MINVAL(co2_send) ', MINVAL(co2_send) PRINT *, 'tracco2i_mod.F90 --- MAXVAL(co2_send) ', MAXVAL(co2_send) END SUBROUTINE tracco2i SUBROUTINE co2_emissions(debutphy) USE dimphy ! USE infotrac_phy USE lmdz_geometry, ONLY: cell_area USE lmdz_grid_phy USE lmdz_phys_mpi_data, ONLY: is_mpi_root USE lmdz_phys_para, ONLY: gather, scatter USE phys_cal_mod USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite USE carbon_cycle_mod, ONLY: fco2_ff, fco2_bb, fco2_land, fco2_ocean USE lmdz_abort_physic, ONLY: abort_physic IMPLICIT NONE INCLUDE "YOMCST.h" LOGICAL, INTENT(IN) :: debutphy ! For NetCDF: INTEGER ncid_in ! IDs for input files INTEGER varid, ncerr INTEGER :: n_glo, n_month REAL, allocatable :: vector(:), time(:) REAL, ALLOCATABLE :: flx_co2ff_glo(:, :) ! fossil-fuel CO2 REAL, ALLOCATABLE :: flx_co2bb_glo(:, :) ! biomass-burning CO2 REAL, ALLOCATABLE, SAVE :: flx_co2ff(:, :) ! fossil-fuel CO2 REAL, ALLOCATABLE, SAVE :: flx_co2bb(:, :) ! biomass-burning CO2 !$OMP THREADPRIVATE(flx_co2ff,flx_co2bb) !! may be controlled via the .def later on !! also co2bb for now comes from ORCHIDEE LOGICAL, PARAMETER :: readco2ff = .TRUE. !! this should be left to FALSE for now LOGICAL, PARAMETER :: readco2bb = .FALSE. CHARACTER (len = 20) :: modname = 'tracco2i.co2_emissions' CHARACTER (len = 80) :: abort_message IF (debutphy) THEN ALLOCATE(flx_co2ff(klon, 12)) ALLOCATE(flx_co2bb(klon, 12)) !$OMP MASTER IF (is_mpi_root) THEN IF (.NOT.ALLOCATED(flx_co2ff_glo)) ALLOCATE(flx_co2ff_glo(klon_glo, 12)) IF (.NOT.ALLOCATED(flx_co2bb_glo)) ALLOCATE(flx_co2bb_glo(klon_glo, 12)) !--reading CO2 fossil fuel emissions IF (readco2ff) THEN ! ... Open the CO2ff file CALL nf95_open("sflx_lmdz_co2_ff.nc", nf90_nowrite, ncid_in) CALL nf95_inq_varid(ncid_in, "vector", varid) CALL nf95_gw_var(ncid_in, varid, vector) n_glo = size(vector) IF (n_glo/=klon_glo) THEN abort_message = 'sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo' CALL abort_physic(modname, abort_message, 1) ENDIF CALL nf95_inq_varid(ncid_in, "time", varid) CALL nf95_gw_var(ncid_in, varid, time) n_month = size(time) IF (n_month/=12) THEN abort_message = 'sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12' CALL abort_physic(modname, abort_message, 1) ENDIF !--reading flx_co2 for fossil fuel CALL nf95_inq_varid(ncid_in, "flx_co2", varid) ncerr = nf90_get_var(ncid_in, varid, flx_co2ff_glo) CALL nf95_close(ncid_in) ELSE !--co2ff not to be read flx_co2ff_glo(:, :) = 0.0 ENDIF !--reading CO2 biomass burning emissions !--using it will be inconsistent with treatment in ORCHIDEE IF (readco2bb) THEN ! ... Open the CO2bb file CALL nf95_open("sflx_lmdz_co2_bb.nc", nf90_nowrite, ncid_in) CALL nf95_inq_varid(ncid_in, "vector", varid) CALL nf95_gw_var(ncid_in, varid, vector) n_glo = size(vector) IF (n_glo/=klon_glo) THEN abort_message = 'sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo' CALL abort_physic(modname, abort_message, 1) ENDIF CALL nf95_inq_varid(ncid_in, "time", varid) CALL nf95_gw_var(ncid_in, varid, time) n_month = size(time) IF (n_month/=12) THEN abort_message = 'sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12' CALL abort_physic(modname, abort_message, 1) ENDIF !--reading flx_co2 for biomass burning CALL nf95_inq_varid(ncid_in, "flx_co2", varid) ncerr = nf90_get_var(ncid_in, varid, flx_co2bb_glo) CALL nf95_close(ncid_in) ELSE !--co2bb not to be read flx_co2bb_glo(:, :) = 0.0 ENDIF ENDIF !$OMP END MASTER ! Allocation needed for all proc otherwise scatter might complain IF (.NOT.ALLOCATED(flx_co2ff_glo)) ALLOCATE(flx_co2ff_glo(0, 0)) IF (.NOT.ALLOCATED(flx_co2bb_glo)) ALLOCATE(flx_co2bb_glo(0, 0)) !--scatter on all proc CALL scatter(flx_co2ff_glo, flx_co2ff) CALL scatter(flx_co2bb_glo, flx_co2bb) IF (ALLOCATED(flx_co2ff_glo)) DEALLOCATE(flx_co2ff_glo) IF (ALLOCATED(flx_co2bb_glo)) DEALLOCATE(flx_co2bb_glo) ENDIF !--end debuthy !---select the correct month IF (mth_cur<1.OR.mth_cur>12) THEN PRINT *, 'probleme avec le mois dans co2_ini =', mth_cur ENDIF fco2_ff(:) = flx_co2ff(:, mth_cur) fco2_bb(:) = flx_co2bb(:, mth_cur) END SUBROUTINE co2_emissions END MODULE tracco2i_mod