source: LMDZ6/trunk/libf/phylmd/carbon_cycle_mod.F90 @ 3385

Last change on this file since 3385 was 3385, checked in by oboucher, 6 years ago

Committed too much in the previous commit, this goes back to the N-1 version
with just the definition of level_coupling_esm as a new flag

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 19.0 KB
Line 
1MODULE carbon_cycle_mod
2! Controle module for the carbon CO2 tracers :
3!   - Identification
4!   - Get concentrations comming from coupled model or read from file to tracers
5!   - Calculate new RCO2 for radiation scheme
6!   - Calculate new carbon flux for sending to coupled models (PISCES and ORCHIDEE)
7!
8! Author : Josefine GHATTAS, Patricia CADULE
9
10  IMPLICIT NONE
11  SAVE
12  PRIVATE
13  PUBLIC :: carbon_cycle_init, carbon_cycle
14
15! Variables read from parmeter file physiq.def
16  LOGICAL, PUBLIC :: carbon_cycle_tr        ! 3D transport of CO2 in the atmosphere, parameter read in conf_phys
17!$OMP THREADPRIVATE(carbon_cycle_tr)
18  LOGICAL, PUBLIC :: carbon_cycle_cpl       ! Coupling of CO2 fluxes between LMDZ/ORCHIDEE and LMDZ/OCEAN(PISCES)
19!$OMP THREADPRIVATE(carbon_cycle_cpl)
20  INTEGER, SAVE, PUBLIC :: level_coupling_esm ! Level of coupling for the ESM - 0, 1, 2, 3
21!$OMP THREADPRIVATE(level_coupling_esm)
22
23  LOGICAL :: carbon_cycle_emis_comp_omp=.FALSE.
24  LOGICAL :: carbon_cycle_emis_comp=.FALSE. ! Calculation of emission compatible
25!$OMP THREADPRIVATE(carbon_cycle_emis_comp)
26
27  LOGICAL :: RCO2_inter_omp
28  LOGICAL :: RCO2_inter  ! RCO2 interactive : if true calculate new value RCO2 for the radiation scheme
29!$OMP THREADPRIVATE(RCO2_inter)
30
31! Scalare values when no transport, from physiq.def
32  REAL :: fos_fuel_s_omp
33  REAL :: fos_fuel_s  ! carbon_cycle_fos_fuel dans physiq.def
34!$OMP THREADPRIVATE(fos_fuel_s)
35  REAL :: emis_land_s ! not yet implemented
36!$OMP THREADPRIVATE(emis_land_s)
37
38  REAL :: airetot     ! Total area of the earth surface
39!$OMP THREADPRIVATE(airetot)
40
41  INTEGER :: ntr_co2  ! Number of tracers concerning the carbon cycle
42!$OMP THREADPRIVATE(ntr_co2)
43
44! fco2_ocn_day : flux CO2 from ocean for 1 day (cumulated) [gC/m2/d]. Allocation and initalization done in cpl_mod
45  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_ocn_day
46!$OMP THREADPRIVATE(fco2_ocn_day)
47
48  REAL, DIMENSION(:), ALLOCATABLE :: fco2_land_day   ! flux CO2 from land for 1 day (cumulated)  [gC/m2/d]
49!$OMP THREADPRIVATE(fco2_land_day)
50  REAL, DIMENSION(:), ALLOCATABLE :: fco2_lu_day     ! Emission from land use change for 1 day (cumulated) [gC/m2/d]
51!$OMP THREADPRIVATE(fco2_lu_day)
52
53  REAL, DIMENSION(:,:), ALLOCATABLE :: dtr_add       ! Tracer concentration to be injected
54!$OMP THREADPRIVATE(dtr_add)
55
56! Following 2 fields will be allocated and initialized in surf_land_orchidee
57  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_land_inst  ! flux CO2 from land at one time step
58!$OMP THREADPRIVATE(fco2_land_inst)
59  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: fco2_lu_inst    ! Emission from land use change at one time step
60!$OMP THREADPRIVATE(fco2_lu_inst)
61
62! Calculated co2 field to be send to the ocean via the coupler and to ORCHIDEE
63  REAL, DIMENSION(:), ALLOCATABLE, PUBLIC :: co2_send ! Field allocated in phyetat0
64!$OMP THREADPRIVATE(co2_send)
65
66
67  TYPE, PUBLIC ::   co2_trac_type
68     CHARACTER(len = 8) :: name       ! Tracer name in tracer.def
69     INTEGER            :: id         ! Index in total tracer list, tr_seri
70     CHARACTER(len=30)  :: file       ! File name
71     LOGICAL            :: cpl        ! True if this tracers is coupled from ORCHIDEE or PISCES.
72                                      ! False if read from file.
73     INTEGER            :: updatefreq ! Frequence to inject in second
74     INTEGER            :: readstep   ! Actual time step to read in file
75     LOGICAL            :: updatenow  ! True if this tracer should be updated this time step
76  END TYPE co2_trac_type
77  INTEGER,PARAMETER :: maxco2trac=5  ! Maximum number of different CO2 fluxes
78  TYPE(co2_trac_type), DIMENSION(maxco2trac) :: co2trac
79
80CONTAINS
81 
82  SUBROUTINE carbon_cycle_init(tr_seri, pdtphys, aerosol, radio)
83! This subroutine is called from traclmdz_init, only at first timestep.
84! - Read controle parameters from .def input file
85! - Search for carbon tracers and set default values
86! - Allocate variables
87! - Test for compatibility
88
89    USE dimphy
90    USE geometry_mod, ONLY : cell_area
91    USE mod_phys_lmdz_transfert_para
92    USE infotrac_phy, ONLY: nbtr, nqo, niadv, tname
93    USE IOIPSL
94    USE surface_data, ONLY : ok_veget, type_ocean
95    USE phys_cal_mod, ONLY : mth_len
96    USE print_control_mod, ONLY: lunout
97
98    IMPLICIT NONE
99    INCLUDE "clesphys.h"
100 
101! Input argument
102    REAL,DIMENSION(klon,klev,nbtr),INTENT(IN) :: tr_seri ! Concentration Traceur [U/KgA] 
103    REAL,INTENT(IN)                           :: pdtphys ! length of time step in physiq (sec)
104
105! InOutput arguments
106    LOGICAL,DIMENSION(nbtr), INTENT(INOUT) :: aerosol
107    LOGICAL,DIMENSION(nbtr), INTENT(INOUT) :: radio
108
109! Local variables
110    INTEGER               :: ierr, it, iiq, itc
111    INTEGER               :: teststop
112
113
114
115! 1) Read controle parameters from .def input file
116! ------------------------------------------------
117    ! Read fosil fuel value if no transport
118    IF (.NOT. carbon_cycle_tr) THEN
119!$OMP MASTER
120       fos_fuel_s_omp = 0.
121       CALL getin ('carbon_cycle_fos_fuel',fos_fuel_s_omp)
122!$OMP END MASTER
123!$OMP BARRIER
124       fos_fuel_s=fos_fuel_s_omp
125       WRITE(lunout,*) 'carbon_cycle_fos_fuel = ', fos_fuel_s
126    END IF
127
128
129    ! Read parmeter for calculation compatible emission
130    IF (.NOT. carbon_cycle_tr) THEN
131!$OMP MASTER
132       carbon_cycle_emis_comp_omp=.FALSE.
133       CALL getin('carbon_cycle_emis_comp',carbon_cycle_emis_comp_omp)
134!$OMP END MASTER
135!$OMP BARRIER
136       carbon_cycle_emis_comp=carbon_cycle_emis_comp_omp
137       WRITE(lunout,*) 'carbon_cycle_emis_comp = ',carbon_cycle_emis_comp
138       IF (carbon_cycle_emis_comp) THEN
139          CALL abort_physic('carbon_cycle_init', 'carbon_cycle_emis_comp option not yet implemented!!',1)
140       END IF
141    END IF
142
143    ! Read parameter for interactive calculation of the CO2 value for the radiation scheme
144!$OMP MASTER
145    RCO2_inter_omp=.FALSE.
146    CALL getin('RCO2_inter',RCO2_inter_omp)
147!$OMP END MASTER
148!$OMP BARRIER
149    RCO2_inter=RCO2_inter_omp
150    WRITE(lunout,*) 'RCO2_inter = ', RCO2_inter
151    IF (RCO2_inter) THEN
152       WRITE(lunout,*) 'RCO2 will be recalculated once a day'
153       WRITE(lunout,*) 'RCO2 initial = ', RCO2
154    END IF
155
156
157! 2) Search for carbon tracers and set default values
158! ---------------------------------------------------
159    itc=0
160    DO it=1,nbtr
161!!       iiq=niadv(it+2)                                                            ! jyg
162       iiq=niadv(it+nqo)                                                            ! jyg
163       
164       SELECT CASE(tname(iiq))
165       CASE("fCO2_ocn")
166          itc = itc + 1
167          co2trac(itc)%name='fCO2_ocn'
168          co2trac(itc)%id=it
169          co2trac(itc)%file='fl_co2_ocean.nc'
170          IF (carbon_cycle_cpl .AND. type_ocean=='couple') THEN
171             co2trac(itc)%cpl=.TRUE.
172             co2trac(itc)%updatefreq = 86400 ! Once a day as the coupling with OASIS/PISCES
173          ELSE
174             co2trac(itc)%cpl=.FALSE.
175             co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
176          END IF
177       CASE("fCO2_land")
178          itc = itc + 1
179          co2trac(itc)%name='fCO2_land'
180          co2trac(itc)%id=it
181          co2trac(itc)%file='fl_co2_land.nc'
182          IF (carbon_cycle_cpl .AND. ok_veget) THEN
183             co2trac(itc)%cpl=.TRUE.
184             co2trac(itc)%updatefreq = INT(pdtphys) ! Each timestep as the coupling with ORCHIDEE
185          ELSE
186             co2trac(itc)%cpl=.FALSE.
187!             co2trac(itc)%updatefreq = 10800   ! 10800sec = 3H
188             co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
189          END IF
190       CASE("fCO2_land_use")
191          itc = itc + 1
192          co2trac(itc)%name='fCO2_land_use'
193          co2trac(itc)%id=it
194          co2trac(itc)%file='fl_co2_land_use.nc'
195          IF (carbon_cycle_cpl .AND. ok_veget) THEN
196             co2trac(it)%cpl=.TRUE.
197             co2trac(itc)%updatefreq = INT(pdtphys) ! Each timestep as the coupling with ORCHIDEE
198          ELSE
199             co2trac(itc)%cpl=.FALSE.
200             co2trac(itc)%updatefreq = 10800   ! 10800sec = 3H
201          END IF
202       CASE("fCO2_fos_fuel")
203          itc = itc + 1
204          co2trac(itc)%name='fCO2_fos_fuel'
205          co2trac(itc)%id=it
206          co2trac(itc)%file='fossil_fuel.nc'
207          co2trac(itc)%cpl=.FALSE.       ! This tracer always read from file
208!         co2trac(itc)%updatefreq = 86400  ! 86400sec = 24H Cadule case
209          co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
210       CASE("fCO2_bbg")
211          itc = itc + 1
212          co2trac(itc)%name='fCO2_bbg'
213          co2trac(itc)%id=it
214          co2trac(itc)%file='fl_co2_bbg.nc'
215          co2trac(itc)%cpl=.FALSE.       ! This tracer always read from file
216          co2trac(itc)%updatefreq = 86400*mth_len ! Once a month
217       CASE("fCO2")
218          ! fCO2 : One tracer transporting the total CO2 flux
219          itc = itc + 1
220          co2trac(itc)%name='fCO2'
221          co2trac(itc)%id=it
222          co2trac(itc)%file='fl_co2.nc'
223          IF (carbon_cycle_cpl) THEN
224             co2trac(itc)%cpl=.TRUE.
225          ELSE
226             co2trac(itc)%cpl=.FALSE.
227          END IF
228          co2trac(itc)%updatefreq = 86400
229          ! DOES THIS WORK ???? Problematic due to implementation of the coupled fluxes...
230          CALL abort_physic('carbon_cycle_init','transport of total CO2 has to be implemented and tested',1)
231       END SELECT
232    END DO
233
234    ! Total number of carbon CO2 tracers
235    ntr_co2 = itc
236   
237    ! Definition of control varaiables for the tracers
238    DO it=1,ntr_co2
239       aerosol(co2trac(it)%id) = .FALSE.
240       radio(co2trac(it)%id)   = .FALSE.
241    END DO
242   
243    ! Vector indicating which timestep to read for each tracer
244    ! Always start read in the beginning of the file
245    co2trac(:)%readstep = 0
246   
247
248! 3) Allocate variables
249! ---------------------
250    ! Allocate vector for storing fluxes to inject
251    ALLOCATE(dtr_add(klon,maxco2trac), stat=ierr)
252    IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 11',1)       
253   
254    ! Allocate variables for cumulating fluxes from ORCHIDEE
255    IF (RCO2_inter) THEN
256       IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl) THEN
257          ALLOCATE(fco2_land_day(klon), stat=ierr)
258          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 2',1)
259          fco2_land_day(1:klon) = 0.
260         
261          ALLOCATE(fco2_lu_day(klon), stat=ierr)
262          IF (ierr /= 0) CALL abort_physic('carbon_cycle_init', 'pb in allocation 3',1)
263          fco2_lu_day(1:klon)   = 0.
264       END IF
265    END IF
266
267
268! 4) Test for compatibility
269! -------------------------
270!    IF (carbon_cycle_cpl .AND. type_ocean/='couple') THEN
271!       WRITE(lunout,*) 'Coupling with ocean model is needed for carbon_cycle_cpl'
272!       CALL abort_physic('carbon_cycle_init', 'coupled ocean is needed for carbon_cycle_cpl',1)
273!    END IF
274!
275!    IF (carbon_cycle_cpl .AND..NOT. ok_veget) THEN
276!       WRITE(lunout,*) 'Coupling with surface land model ORCHDIEE is needed for carbon_cycle_cpl'
277!       CALL abort_physic('carbon_cycle_init', 'ok_veget is needed for carbon_cycle_cpl',1)
278!    END IF
279
280    ! Compiler test : following should never happen
281    teststop=0
282    DO it=1,teststop
283       CALL abort_physic('carbon_cycle_init', 'Entering loop from 1 to 0',1)
284    END DO
285
286    IF (ntr_co2==0) THEN
287       ! No carbon tracers found in tracer.def. It is not possible to do carbon cycle
288       WRITE(lunout,*) 'No carbon tracers found in tracer.def. Not ok with carbon_cycle_tr and/or carbon_cycle_cp'
289       CALL abort_physic('carbon_cycle_init', 'No carbon tracers found in tracer.def',1)
290    END IF
291   
292! 5) Calculate total area of the earth surface
293! --------------------------------------------
294    CALL reduce_sum(SUM(cell_area),airetot)
295    CALL bcast(airetot)
296
297  END SUBROUTINE carbon_cycle_init
298
299
300  SUBROUTINE carbon_cycle(nstep, pdtphys, pctsrf, tr_seri, source)
301! Subroutine for injection of co2 in the tracers
302!
303! - Find out if it is time to update
304! - Get tracer from coupled model or from file
305! - Calculate new RCO2 value for the radiation scheme
306! - Calculate CO2 flux to send to ocean and land models (PISCES and ORCHIDEE)
307
308    USE infotrac_phy, ONLY: nbtr
309    USE dimphy
310    USE mod_phys_lmdz_transfert_para
311    USE phys_cal_mod, ONLY : mth_cur, mth_len
312    USE phys_cal_mod, ONLY : day_cur
313    USE indice_sol_mod
314    USE print_control_mod, ONLY: lunout
315    USE geometry_mod, ONLY : cell_area
316
317    IMPLICIT NONE
318
319    INCLUDE "clesphys.h"
320    INCLUDE "YOMCST.h"
321
322! In/Output arguments
323    INTEGER,INTENT(IN) :: nstep      ! time step in physiq
324    REAL,INTENT(IN)    :: pdtphys    ! length of time step in physiq (sec)
325    REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: pctsrf            ! Surface fraction
326    REAL, DIMENSION(klon,klev,nbtr), INTENT(INOUT)  :: tr_seri ! All tracers
327    REAL, DIMENSION(klon,nbtr), INTENT(INOUT)       :: source  ! Source for all tracers
328
329! Local variables
330    INTEGER :: it
331    LOGICAL :: newmonth ! indicates if a new month just started
332    LOGICAL :: newday   ! indicates if a new day just started
333    LOGICAL :: endday   ! indicated if last time step in a day
334
335    REAL, PARAMETER :: fact=1.E-15/2.12  ! transformation factor from gC/m2/day => ppm/m2/day
336    REAL, DIMENSION(klon) :: fco2_tmp
337    REAL :: sumtmp
338    REAL :: delta_co2_ppm
339   
340
341! 1) Calculate logicals indicating if it is a new month, new day or the last time step in a day (end day)
342! -------------------------------------------------------------------------------------------------------
343
344    newday = .FALSE.; endday = .FALSE.; newmonth = .FALSE.
345
346    IF (MOD(nstep,INT(86400./pdtphys))==1) newday=.TRUE.
347    IF (MOD(nstep,INT(86400./pdtphys))==0) endday=.TRUE.
348    IF (newday .AND. day_cur==1) newmonth=.TRUE.
349
350! 2)  For each carbon tracer find out if it is time to inject (update)
351! --------------------------------------------------------------------
352    DO it = 1, ntr_co2
353       IF ( MOD(nstep,INT(co2trac(it)%updatefreq/pdtphys)) == 1 ) THEN
354          co2trac(it)%updatenow = .TRUE.
355       ELSE
356          co2trac(it)%updatenow = .FALSE.
357       END IF
358    END DO
359
360! 3) Get tracer update
361! --------------------------------------
362    DO it = 1, ntr_co2
363       IF ( co2trac(it)%updatenow ) THEN
364          IF ( co2trac(it)%cpl ) THEN
365             ! Get tracer from coupled model
366             SELECT CASE(co2trac(it)%name)
367             CASE('fCO2_land')     ! from ORCHIDEE
368                dtr_add(:,it) = fco2_land_inst(:)*pctsrf(:,is_ter)*fact ! [ppm/m2/day]
369             CASE('fCO2_land_use') ! from ORCHIDEE
370                dtr_add(:,it) = fco2_lu_inst(:)  *pctsrf(:,is_ter)*fact ! [ppm/m2/day]
371             CASE('fCO2_ocn')      ! from PISCES
372                dtr_add(:,it) = fco2_ocn_day(:)  *pctsrf(:,is_oce)*fact ! [ppm/m2/day]
373             CASE DEFAULT
374                WRITE(lunout,*) 'Error with tracer ',co2trac(it)%name
375                CALL abort_physic('carbon_cycle', 'No coupling implemented for this tracer',1)
376             END SELECT
377          ELSE
378             ! Read tracer from file
379             co2trac(it)%readstep = co2trac(it)%readstep + 1 ! increment time step in file
380! Patricia   CALL read_map2D(co2trac(it)%file,'fco2',co2trac(it)%readstep,.FALSE.,dtr_add(:,it))
381             CALL read_map2D(co2trac(it)%file,'fco2',co2trac(it)%readstep,.TRUE.,dtr_add(:,it))
382
383             ! Converte from kgC/m2/h to kgC/m2/s
384             dtr_add(:,it) = dtr_add(:,it)/3600
385             ! Add individual treatment of values read from file
386             SELECT CASE(co2trac(it)%name)
387             CASE('fCO2_land')
388                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_ter)
389             CASE('fCO2_land_use')
390                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_ter)
391             CASE('fCO2_ocn')
392                dtr_add(:,it) = dtr_add(:,it) *pctsrf(:,is_oce)
393! Patricia :
394!             CASE('fCO2_fos_fuel')
395!                dtr_add(:,it) = dtr_add(:,it)/mth_len
396!                co2trac(it)%readstep = 0 ! Always read same value for fossil fuel(Cadule case)
397             END SELECT
398          END IF
399       END IF
400    END DO
401
402! 4) Update co2 tracers :
403!    Loop over all carbon tracers and add source
404! ------------------------------------------------------------------
405    IF (carbon_cycle_tr) THEN
406       DO it = 1, ntr_co2
407          IF (.FALSE.) THEN
408             tr_seri(1:klon,1,co2trac(it)%id) = tr_seri(1:klon,1,co2trac(it)%id) + dtr_add(1:klon,it)
409             source(1:klon,co2trac(it)%id) = 0.
410          ELSE
411             source(1:klon,co2trac(it)%id) = dtr_add(1:klon,it)
412          END IF
413       END DO
414    END IF
415
416
417! 5) Calculations for new CO2 value for the radiation scheme(instead of reading value from .def)
418! ----------------------------------------------------------------------------------------------
419    IF (RCO2_inter) THEN
420       ! Cumulate fluxes from ORCHIDEE at each timestep
421       IF (.NOT. carbon_cycle_tr .AND. carbon_cycle_cpl) THEN
422          IF (newday) THEN ! Reset cumulative variables once a day
423             fco2_land_day(1:klon) = 0.
424             fco2_lu_day(1:klon)   = 0.
425          END IF
426          fco2_land_day(1:klon) = fco2_land_day(1:klon) + fco2_land_inst(1:klon) ![gC/m2/day]
427          fco2_lu_day(1:klon)   = fco2_lu_day(1:klon)   + fco2_lu_inst(1:klon)   ![gC/m2/day]
428       END IF
429
430       ! At the end of a new day, calculate a mean scalare value of CO2
431       ! JG : Ici on utilise uniquement le traceur du premier couche du modele. Est-ce que c'est correcte ?
432       IF (endday) THEN
433
434          IF (carbon_cycle_tr) THEN
435             ! Sum all co2 tracers to get the total delta CO2 flux
436             fco2_tmp(:) = 0.
437             DO it = 1, ntr_co2
438                fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2trac(it)%id)
439             END DO
440             
441          ELSE IF (carbon_cycle_cpl) THEN ! no carbon_cycle_tr
442             ! Sum co2 fluxes comming from coupled models and parameter for fossil fuel
443             fco2_tmp(1:klon) = fos_fuel_s + ((fco2_lu_day(1:klon) + fco2_land_day(1:klon))*pctsrf(1:klon,is_ter) &
444                  + fco2_ocn_day(:)*pctsrf(:,is_oce)) * fact
445          END IF
446
447          ! Calculate a global mean value of delta CO2 flux
448          fco2_tmp(1:klon) = fco2_tmp(1:klon) * cell_area(1:klon)
449          CALL reduce_sum(SUM(fco2_tmp),sumtmp)
450          CALL bcast(sumtmp)
451          delta_co2_ppm = sumtmp/airetot
452         
453          ! Add initial value for co2_ppm and delta value
454          co2_ppm = co2_ppm0 + delta_co2_ppm
455         
456          ! Transformation of atmospheric CO2 concentration for the radiation code
457          RCO2 = co2_ppm * 1.0e-06  * 44.011/28.97
458         
459          WRITE(lunout,*) 'RCO2 is now updated! RCO2 = ', RCO2
460       END IF ! endday
461
462    END IF ! RCO2_inter
463
464
465! 6) Calculate CO2 flux to send to ocean and land models : PISCES and ORCHIDEE         
466! ----------------------------------------------------------------------------
467    IF (carbon_cycle_cpl) THEN
468
469       IF (carbon_cycle_tr) THEN
470          ! Sum all co2 tracers to get the total delta CO2 flux at first model layer
471          fco2_tmp(:) = 0.
472          DO it = 1, ntr_co2
473             fco2_tmp(1:klon) = fco2_tmp(1:klon) + tr_seri(1:klon,1,co2trac(it)%id)
474          END DO
475          co2_send(1:klon) = fco2_tmp(1:klon) + co2_ppm0
476       ELSE
477          ! Send a scalare value in 2D variable to ocean and land model (PISCES and ORCHIDEE)
478          co2_send(1:klon) = co2_ppm
479       END IF
480
481    END IF
482
483  END SUBROUTINE carbon_cycle
484 
485END MODULE carbon_cycle_mod
Note: See TracBrowser for help on using the repository browser.