51 REAL,
DIMENSION(:,:),
ALLOCATABLE ::
dtr_add
61 REAL,
DIMENSION(:),
ALLOCATABLE,
PUBLIC ::
co2_send
66 CHARACTER(len = 8) :: name
68 CHARACTER(len=30) :: file
100 REAL,
DIMENSION(klon,klev,nbtr),
INTENT(IN) :: tr_seri
101 REAL,
INTENT(IN) :: pdtphys
104 LOGICAL,
DIMENSION(nbtr),
INTENT(INOUT) :: aerosol
105 LOGICAL,
DIMENSION(nbtr),
INTENT(INOUT) :: radio
108 INTEGER :: ierr, it, iiq, itc
137 CALL abort_physic(
'carbon_cycle_init',
'carbon_cycle_emis_comp option not yet implemented!!',1)
150 WRITE(
lunout,*)
'RCO2 will be recalculated once a day'
151 WRITE(
lunout,*)
'RCO2 initial = ', rco2
162 SELECT CASE(
tname(iiq))
167 co2trac(itc)%file=
'fl_co2_ocean.nc'
170 co2trac(itc)%updatefreq = 86400
179 co2trac(itc)%file=
'fl_co2_land.nc'
182 co2trac(itc)%updatefreq = int(pdtphys)
188 CASE(
"fCO2_land_use")
190 co2trac(itc)%name=
'fCO2_land_use'
192 co2trac(itc)%file=
'fl_co2_land_use.nc'
195 co2trac(itc)%updatefreq = int(pdtphys)
198 co2trac(itc)%updatefreq = 10800
200 CASE(
"fCO2_fos_fuel")
202 co2trac(itc)%name=
'fCO2_fos_fuel'
204 co2trac(itc)%file=
'fossil_fuel.nc'
212 co2trac(itc)%file=
'fl_co2_bbg.nc'
226 co2trac(itc)%updatefreq = 86400
228 CALL abort_physic(
'carbon_cycle_init',
'transport of total CO2 has to be implemented and tested',1)
250 IF (ierr /= 0)
CALL abort_physic(
'carbon_cycle_init',
'pb in allocation 11',1)
256 IF (ierr /= 0)
CALL abort_physic(
'carbon_cycle_init',
'pb in allocation 2',1)
260 IF (ierr /= 0)
CALL abort_physic(
'carbon_cycle_init',
'pb in allocation 3',1)
281 CALL abort_physic(
'carbon_cycle_init',
'Entering loop from 1 to 0',1)
286 WRITE(
lunout,*)
'No carbon tracers found in tracer.def. Not ok with carbon_cycle_tr and/or carbon_cycle_cp'
287 CALL abort_physic(
'carbon_cycle_init',
'No carbon tracers found in tracer.def',1)
298 SUBROUTINE carbon_cycle(nstep, pdtphys, pctsrf, tr_seri, source)
321 INTEGER,
INTENT(IN) :: nstep
322 REAL,
INTENT(IN) :: pdtphys
323 REAL,
DIMENSION(klon,nbsrf),
INTENT(IN) :: pctsrf
324 REAL,
DIMENSION(klon,klev,nbtr),
INTENT(INOUT) :: tr_seri
325 REAL,
DIMENSION(klon,nbtr),
INTENT(INOUT) :: source
333 REAL,
PARAMETER :: fact=1.e-15/2.12
334 REAL,
DIMENSION(klon) :: fco2_tmp
336 REAL :: delta_co2_ppm
344 IF (mod(nstep,int(86400./pdtphys))==1) newday=.
true.
345 IF (mod(nstep,int(86400./pdtphys))==0) endday=.
true.
351 IF ( mod(nstep,int(
co2trac(it)%updatefreq/pdtphys)) == 1 )
THEN
361 IF (
co2trac(it)%updatenow )
THEN
367 CASE(
'fCO2_land_use')
373 CALL abort_physic(
'carbon_cycle',
'No coupling implemented for this tracer',1)
387 CASE(
'fCO2_land_use')
455 rco2 =
co2_ppm * 1.0e-06 * 44.011/28.97
457 WRITE(
lunout,*)
'RCO2 is now updated! RCO2 = ', rco2
integer, parameter is_ter
real, dimension(:,:), allocatable dtr_add
integer, parameter maxco2trac
logical carbon_cycle_emis_comp_omp
subroutine, public carbon_cycle(nstep, pdtphys, pctsrf, tr_seri, source)
subroutine, public carbon_cycle_init(tr_seri, pdtphys, aerosol, radio)
real, dimension(:), allocatable, public fco2_land_inst
real, dimension(:), allocatable, public fco2_lu_inst
subroutine read_map2d(filename, varname, timestep, inverse, varout)
logical carbon_cycle_emis_comp
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
integer, dimension(:), allocatable, save niadv
real, dimension(:), allocatable fco2_land_day
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL co2_ppm
real, dimension(:), allocatable, public fco2_ocn_day
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
character(len=20), dimension(:), allocatable, save tname
character(len=6), save type_ocean
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_ener_conserv REAL co2_ppm0
logical, public carbon_cycle_tr
type(co2_trac_type), dimension(maxco2trac) co2trac
subroutine abort_physic(modname, message, ierr)
logical, public carbon_cycle_cpl
real, dimension(:), allocatable, public co2_send
real, dimension(:), allocatable fco2_lu_day
integer, parameter is_oce
real, dimension(:), allocatable, save cell_area
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout