16 LOGICAL,
PUBLIC :: carbon_cycle_tr
18 LOGICAL,
PUBLIC :: carbon_cycle_cpl
21 LOGICAL :: carbon_cycle_emis_comp_omp=.FALSE.
22 LOGICAL :: carbon_cycle_emis_comp=.FALSE.
25 LOGICAL :: RCO2_inter_omp
30 REAL :: fos_fuel_s_omp
43 REAL,
DIMENSION(:),
ALLOCATABLE,
PUBLIC :: fco2_ocn_day
46 REAL,
DIMENSION(:),
ALLOCATABLE :: fco2_land_day
48 REAL,
DIMENSION(:),
ALLOCATABLE :: fco2_lu_day
51 REAL,
DIMENSION(:,:),
ALLOCATABLE :: dtr_add
55 REAL,
DIMENSION(:),
ALLOCATABLE,
PUBLIC :: fco2_land_inst
57 REAL,
DIMENSION(:),
ALLOCATABLE,
PUBLIC :: fco2_lu_inst
61 REAL,
DIMENSION(:),
ALLOCATABLE,
PUBLIC :: co2_send
66 CHARACTER(len = 8) :: name
68 CHARACTER(len=30) :: file
75 INTEGER,
PARAMETER :: maxco2trac=5
100 REAL,
DIMENSION(klon,klev,nbtr),
INTENT(IN) :: tr_seri
104 LOGICAL,
DIMENSION(nbtr),
INTENT(INOUT) :: aerosol
105 LOGICAL,
DIMENSION(nbtr),
INTENT(INOUT) :: radio
108 INTEGER :: ierr,
it, iiq, itc
116 IF (.NOT. carbon_cycle_tr)
THEN
119 CALL
getin(
'carbon_cycle_fos_fuel',fos_fuel_s_omp)
122 fos_fuel_s=fos_fuel_s_omp
123 WRITE(
lunout,*)
'carbon_cycle_fos_fuel = ', fos_fuel_s
128 IF (.NOT. carbon_cycle_tr)
THEN
130 carbon_cycle_emis_comp_omp=.false.
131 CALL
getin(
'carbon_cycle_emis_comp',carbon_cycle_emis_comp_omp)
134 carbon_cycle_emis_comp=carbon_cycle_emis_comp_omp
135 WRITE(
lunout,*)
'carbon_cycle_emis_comp = ',carbon_cycle_emis_comp
136 IF (carbon_cycle_emis_comp)
THEN
137 CALL
abort_gcm(
'carbon_cycle_init',
'carbon_cycle_emis_comp option not yet implemented!!',1)
143 rco2_inter_omp=.false.
144 CALL
getin(
'RCO2_inter',rco2_inter_omp)
147 rco2_inter=rco2_inter_omp
148 WRITE(
lunout,*)
'RCO2_inter = ', rco2_inter
150 WRITE(
lunout,*)
'RCO2 will be recalculated once a day'
151 WRITE(
lunout,*)
'RCO2 initial = ', rco2
161 SELECT CASE(tname(iiq))
164 co2trac(itc)%name=
'fCO2_ocn'
166 co2trac(itc)%file=
'fl_co2_ocean.nc'
167 IF (carbon_cycle_cpl .AND. type_ocean==
'couple')
THEN
168 co2trac(itc)%cpl=.true.
169 co2trac(itc)%updatefreq = 86400
171 co2trac(itc)%cpl=.false.
172 co2trac(itc)%updatefreq = 86400*mth_len
176 co2trac(itc)%name=
'fCO2_land'
178 co2trac(itc)%file=
'fl_co2_land.nc'
179 IF (carbon_cycle_cpl .AND. ok_veget)
THEN
180 co2trac(itc)%cpl=.true.
181 co2trac(itc)%updatefreq = int(
pdtphys)
183 co2trac(itc)%cpl=.false.
185 co2trac(itc)%updatefreq = 86400*mth_len
187 CASE(
"fCO2_land_use")
189 co2trac(itc)%name=
'fCO2_land_use'
191 co2trac(itc)%file=
'fl_co2_land_use.nc'
192 IF (carbon_cycle_cpl .AND. ok_veget)
THEN
193 co2trac(
it)%cpl=.true.
194 co2trac(itc)%updatefreq = int(
pdtphys)
196 co2trac(itc)%cpl=.false.
197 co2trac(itc)%updatefreq = 10800
199 CASE(
"fCO2_fos_fuel")
201 co2trac(itc)%name=
'fCO2_fos_fuel'
203 co2trac(itc)%file=
'fossil_fuel.nc'
204 co2trac(itc)%cpl=.false.
206 co2trac(itc)%updatefreq = 86400*mth_len
209 co2trac(itc)%name=
'fCO2_bbg'
211 co2trac(itc)%file=
'fl_co2_bbg.nc'
212 co2trac(itc)%cpl=.false.
213 co2trac(itc)%updatefreq = 86400*mth_len
217 co2trac(itc)%name=
'fCO2'
219 co2trac(itc)%file=
'fl_co2.nc'
220 IF (carbon_cycle_cpl)
THEN
221 co2trac(itc)%cpl=.true.
223 co2trac(itc)%cpl=.false.
225 co2trac(itc)%updatefreq = 86400
227 CALL
abort_gcm(
'carbon_cycle_init',
'transport of total CO2 has to be implemented and tested',1)
236 aerosol(co2trac(
it)%id) = .false.
237 radio(co2trac(
it)%id) = .false.
242 co2trac(:)%readstep = 0
248 ALLOCATE(dtr_add(klon,maxco2trac), stat=ierr)
249 IF (ierr /= 0) CALL
abort_gcm(
'carbon_cycle_init',
'pb in allocation 11',1)
253 IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl)
THEN
254 ALLOCATE(fco2_land_day(klon), stat=ierr)
255 IF (ierr /= 0) CALL
abort_gcm(
'carbon_cycle_init',
'pb in allocation 2',1)
256 fco2_land_day(1:klon) = 0.
258 ALLOCATE(fco2_lu_day(klon), stat=ierr)
259 IF (ierr /= 0) CALL
abort_gcm(
'carbon_cycle_init',
'pb in allocation 3',1)
260 fco2_lu_day(1:klon) = 0.
280 CALL
abort_gcm(
'carbon_cycle_init',
'Entering loop from 1 to 0',1)
285 WRITE(
lunout,*)
'No carbon tracers found in tracer.def. Not ok with carbon_cycle_tr and/or carbon_cycle_cp'
286 CALL
abort_gcm(
'carbon_cycle_init',
'No carbon tracers found in tracer.def',1)
315 include
"indicesol.h"
320 INTEGER,
INTENT(IN) :: nstep
322 REAL,
DIMENSION(klon,nbsrf),
INTENT(IN) :: pctsrf
323 REAL,
DIMENSION(klon,klev,nbtr),
INTENT(INOUT) :: tr_seri
324 REAL,
DIMENSION(klon,nbtr),
INTENT(INOUT) :: source
332 REAL,
PARAMETER :: fact=1.e-15/2.12
333 REAL,
DIMENSION(klon) :: fco2_tmp
335 REAL :: delta_co2_ppm
341 newday = .false.; endday = .false.; newmonth = .false.
343 IF (mod(nstep,int(86400./
pdtphys))==1) newday=.true.
344 IF (mod(nstep,int(86400./
pdtphys))==0) endday=.true.
345 IF (newday .AND. day_cur==1) newmonth=.true.
350 IF ( mod(nstep,int(co2trac(
it)%updatefreq/
pdtphys)) == 1 )
THEN
351 co2trac(
it)%updatenow = .true.
353 co2trac(
it)%updatenow = .false.
360 IF ( co2trac(
it)%updatenow )
THEN
361 IF ( co2trac(
it)%cpl )
THEN
363 SELECT CASE(co2trac(
it)%name)
365 dtr_add(:,
it) = fco2_land_inst(:)*pctsrf(:,is_ter)*fact
366 CASE(
'fCO2_land_use')
367 dtr_add(:,
it) = fco2_lu_inst(:) *pctsrf(:,is_ter)*fact
369 dtr_add(:,
it) = fco2_ocn_day(:) *pctsrf(:,is_oce)*fact
371 WRITE(
lunout,*)
'Error with tracer ',co2trac(
it)%name
372 CALL
abort_gcm(
'carbon_cycle',
'No coupling implemented for this tracer',1)
376 co2trac(
it)%readstep = co2trac(
it)%readstep + 1
378 CALL
read_map2d(co2trac(
it)%file,
'fco2',co2trac(
it)%readstep,.true.,dtr_add(:,
it))
381 dtr_add(:,
it) = dtr_add(:,
it)/3600
383 SELECT CASE(co2trac(
it)%name)
385 dtr_add(:,
it) = dtr_add(:,
it) *pctsrf(:,is_ter)
386 CASE(
'fCO2_land_use')
387 dtr_add(:,
it) = dtr_add(:,
it) *pctsrf(:,is_ter)
389 dtr_add(:,
it) = dtr_add(:,
it) *pctsrf(:,is_oce)
402 IF (carbon_cycle_tr)
THEN
405 tr_seri(1:klon,1,co2trac(
it)%id) = tr_seri(1:klon,1,co2trac(
it)%id) + dtr_add(1:klon,
it)
406 source(1:klon,co2trac(
it)%id) = 0.
408 source(1:klon,co2trac(
it)%id) = dtr_add(1:klon,
it)
418 IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl)
THEN
420 fco2_land_day(1:klon) = 0.
421 fco2_lu_day(1:klon) = 0.
423 fco2_land_day(1:klon) = fco2_land_day(1:klon) + fco2_land_inst(1:klon)
424 fco2_lu_day(1:klon) = fco2_lu_day(1:klon) + fco2_lu_inst(1:klon)
431 IF (carbon_cycle_tr)
THEN
435 fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2trac(
it)%id)
438 ELSE IF (carbon_cycle_cpl)
THEN
440 fco2_tmp(1:klon) = fos_fuel_s + ((fco2_lu_day(1:klon) + fco2_land_day(1:klon))*pctsrf(1:klon,is_ter) &
441 + fco2_ocn_day(:)*pctsrf(:,is_oce)) * fact
445 fco2_tmp(1:klon) = fco2_tmp(1:klon) *
airephy(1:klon)
448 delta_co2_ppm = sumtmp/airetot
454 rco2 =
co2_ppm * 1.0e-06 * 44.011/28.97
456 WRITE(
lunout,*)
'RCO2 is now updated! RCO2 = ', rco2
464 IF (carbon_cycle_cpl)
THEN
466 IF (carbon_cycle_tr)
THEN
470 fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2trac(
it)%id)
472 co2_send(1:klon) = fco2_tmp(1:klon) +
co2_ppm0