source: LMDZ6/trunk/libf/phylmd/tracco2i_mod.f90

Last change on this file was 5274, checked in by abarral, 9 hours ago

Replace yomcst.h by existing module

File size: 20.0 KB
Line 
1MODULE tracco2i_mod
2!
3! This module does the work for the interactive CO2 tracers
4! Authors: Patricia Cadule and Olivier Boucher
5!
6! Purpose and description:
7!  -----------------------
8! Main routine for the interactive carbon cycle
9! Gather all carbon fluxes and emissions from ORCHIDEE, PISCES and fossil fuel
10! Compute the net flux in source field which is used in phytrac
11! Compute global CO2 mixing ratio for radiation scheme if option is activated
12! Redistribute CO2 evenly over the atmosphere if transport is desactivated
13!
14CONTAINS
15
16  SUBROUTINE tracco2i_init()
17    ! This subroutine calls carbon_cycle_init needed to be done before first call to phys_output_write in physiq.
18    USE carbon_cycle_mod, ONLY: carbon_cycle_init, carbon_cycle_cpl
19
20    ! Initialize carbon_cycle_mod
21    IF (carbon_cycle_cpl) THEN
22       CALL carbon_cycle_init()
23    ENDIF
24
25  END SUBROUTINE tracco2i_init
26
27  SUBROUTINE tracco2i(pdtphys, debutphy, &
28       xlat, xlon, pphis, pphi, &
29       t_seri, pplay, paprs, tr_seri, source)
30
31    USE dimphy
32    USE infotrac_phy, ONLY: nbtr
33    USE geometry_mod, ONLY: cell_area
34    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
35    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
39    USE carbon_cycle_mod, ONLY: fco2_land_nbp, fco2_land_nep, fco2_land_fLuc
40    USE carbon_cycle_mod, ONLY: fco2_land_fwoodharvest, fco2_land_fHarvest
41    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
44    USE mod_grid_phy_lmdz
45    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
46    USE mod_phys_lmdz_para, ONLY: gather, bcast, scatter
47    USE mod_phys_lmdz_omp_data, ONLY: is_omp_root
48    USE phys_cal_mod
49    USE phys_state_var_mod, ONLY: pctsrf
50    USE indice_sol_mod, ONLY: nbsrf, is_ter, is_lic, is_oce, is_sic
51
52    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
53          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
54          , R_ecc, R_peri, R_incl                                      &
55          , RA, RG, R1SA                                         &
56          , RSIGMA                                                     &
57          , R, RMD, RMV, RD, RV, RCPD                    &
58          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
59          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
60          , RCW, RCS                                                 &
61          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
62          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
63          , RALPD, RBETD, RGAMD
64IMPLICIT NONE
65
66    INCLUDE "clesphys.h"
67
68
69! Input argument
70!---------------
71    REAL,INTENT(IN)    :: pdtphys    ! Pas d'integration pour la physique (seconde)
72    LOGICAL,INTENT(IN) :: debutphy   ! le flag de l'initialisation de la physique
73
74    REAL,DIMENSION(klon),INTENT(IN)        :: xlat    ! latitudes pour chaque point
75    REAL,DIMENSION(klon),INTENT(IN)        :: xlon    ! longitudes pour chaque point
76    REAL,DIMENSION(klon),INTENT(IN)        :: pphis   ! geopotentiel du sol
77    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pphi    ! geopotentiel de chaque couche
78
79    REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
80    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
81    REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
82    REAL,DIMENSION(klon,nbtr),INTENT(INOUT):: source  ! flux de traceur [U/m2/s]
83
84! Output argument
85!----------------
86    REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT)  :: tr_seri ! Concentration Traceur [U/kgA] 
87
88! Local variables
89!----------------
90
91    INTEGER                        :: it, k, i, nb
92    REAL, DIMENSION(klon,klev)     :: m_air     ! mass of air in every grid box [kg]
93    REAL, DIMENSION(klon_glo,klev) :: co2_glo   ! variable temporaire sur la grille global
94    REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global
95    REAL, DIMENSION(klon_glo,nbsrf):: pctsrf_glo      !--fractions de maille sur la grille globale
96    REAL, DIMENSION(klon_glo)      :: pctsrf_ter_glo
97    REAL, DIMENSION(klon_glo)      :: pctsrf_oce_glo
98    REAL, DIMENSION(klon_glo)      :: pctsrf_sic_glo
99    REAL, DIMENSION(klon_glo)      :: cell_area_glo   !--aire des mailles sur la grille globale
100
101    LOGICAL, SAVE :: check_fCO2_nbp_in_cfname
102!$OMP THREADPRIVATE(check_fCO2_nbp_in_cfname)
103    INTEGER, SAVE :: day_pre=-1
104!$OMP THREADPRIVATE(day_pre)
105
106    REAL, PARAMETER :: secinday=86400.
107
108    IF (is_mpi_root) THEN
109      PRINT *,'in tracco2i: date from phys_cal_mod =',year_cur,'-',mth_cur,'-',day_cur,'-',hour
110    ENDIF
111
112!--initialisation of CO2 field if not in restart file
113!--dirty way of doing, do it better later
114!--convert 280 ppm into kg CO2 / kg air
115    IF (debutphy) THEN
116
117! Initialization of tr_seri(id_CO2) If it is not initialized
118      IF (MAXVAL(tr_seri(:,:,id_CO2)).LT.1.e-15) THEN
119        tr_seri(:,:,id_CO2)=co2_ppm0*1.e-6/RMD*RMCO2 !--initialised from co2_ppm0 in rdem
120      ENDIF
121
122!--check if fCO2_nbp is in
123      check_fCO2_nbp_in_cfname=.FALSE.
124      DO nb=1, nbcf_in
125        IF (cfname_in(nb)=="fCO2_nbp") check_fCO2_nbp_in_cfname=.TRUE.
126      ENDDO
127
128      CALL gather(pctsrf,pctsrf_glo)
129      CALL gather(pctsrf(:,is_ter),pctsrf_ter_glo)
130      CALL gather(pctsrf(:,is_oce),pctsrf_oce_glo)
131      CALL gather(pctsrf(:,is_sic),pctsrf_sic_glo)
132      CALL gather(cell_area(:),cell_area_glo)
133
134    ENDIF
135
136!--calculate mass of air in every grid box in kg air
137    DO i=1, klon
138    DO k=1, klev
139      m_air(i,k)=(paprs(i,k)-paprs(i,k+1))/RG*cell_area(i)
140    ENDDO
141    ENDDO
142
143!--call CO2 emission routine
144!--co2bb is zero for now
145!--unit kg CO2 m-2 s-1
146    CALL co2_emissions(debutphy)
147
148!--retrieving land and ocean CO2 flux
149    fco2_land(:)=0.0
150    fco2_ocean(:)=0.0
151    fco2_land_nbp(:)=0.
152    fco2_land_nep(:)=0.
153    fco2_land_fLuc(:)=0.
154    fco2_land_fwoodharvest(:)=0.
155    fco2_land_fHarvest(:)=0.
156
157    DO nb=1, nbcf_in
158
159      SELECT CASE(cfname_in(nb))
160!--dealing with the different fluxes coming from ORCHIDEE
161!--fluxes come in unit of kg C m-2 s-1 is converted into kg CO2 m-2 s-1
162      CASE("fCO2_nep")
163          fco2_land_nep(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
164      CASE("fCO2_fLuc")
165          fco2_land_fLuc(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
166      CASE("fCO2_fwoodharvest")
167          fco2_land_fwoodharvest(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
168      CASE("fCO2_fHarvest")
169          fco2_land_fHarvest(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
170      CASE("fCO2_nbp")
171          fco2_land_nbp(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
172!--fCO2_fco2_ocn comes in unit of mol C02 m-2 s-1 is converted into kg CO2 m-2 s-1 + change sign
173      CASE("fCO2_fgco2")
174          fco2_ocean(:)=-1.*fco2_ocn_day(:)*RMCO2/1.e3*(pctsrf(:,is_oce)+pctsrf(:,is_sic))
175      END SELECT
176
177    ENDDO
178
179    PRINT *, 'tracco2i_mod.F90 --- read_fco2_ocean_cor ',read_fco2_ocean_cor
180    PRINT *, 'tracco2i_mod.F90 --- read_fco2_land_cor ',read_fco2_land_cor
181
182IF (debutphy) THEN
183
184    IF (read_fco2_ocean_cor) THEN
185!$OMP MASTER
186       IF (is_mpi_root .AND. is_omp_root) THEN
187          ocean_area_tot=0.
188          PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ',var_fco2_ocean_cor
189          DO i=1, klon_glo
190             ocean_area_tot = ocean_area_tot + (pctsrf_oce_glo(i)+pctsrf_sic_glo(i))*cell_area_glo(i)
191          ENDDO
192      ENDIF !--is_mpi_root and is_omp_root
193!$OMP END MASTER
194      CALL bcast(ocean_area_tot)
195     PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (debutphy) ',ocean_area_tot
196    ENDIF
197
198    IF (read_fco2_land_cor) THEN
199!$OMP MASTER
200       IF (is_mpi_root .AND. is_omp_root) THEN
201          land_area_tot=0.
202          PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (PgC/yr) ',var_fco2_land_cor
203          DO i=1, klon_glo
204             land_area_tot = land_area_tot + pctsrf_ter_glo(i)*cell_area_glo(i)
205          ENDDO
206      ENDIF !--is_mpi_root and is_omp_root
207!$OMP END MASTER
208      CALL bcast(land_area_tot)
209     PRINT *, 'tracco2i_mod.F90 --- land_area_tot (debutphy) ',land_area_tot
210ENDIF
211
212    ENDIF !-- debutphy 
213
214    PRINT *, 'tracco2i_mod.F90 --- ocean_area_tot (m2) ',ocean_area_tot
215    PRINT *, 'tracco2i_mod.F90 --- land_area_tot (m2) ',land_area_tot
216
217    IF (read_fco2_ocean_cor) THEN
218! var_fco2_ocean_cor: correction of the surface downward CO2 flux into the ocean fgco2 (PgC/yr)
219! This is the correction of the the net air to ocean carbon flux. Positive flux is into the ocean.
220!    PRINT *, 'tracco2i_mod.F90 --- var_fco2_ocean_cor (PgC/yr) ',var_fco2_ocean_cor
221
222!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)
223
224! Factors for carbon and carbon dioxide
225! 1 mole CO2 = 44.009 g CO2 = 12.011 g C
226! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C
227! 1 gC = 44.009/12.011 gCO2
228
229! ocean_area_tot: ocean area (m2)
230
231! year_len: year length (in days)
232
233! conversion: PgC/yr --> kg CO2 m-2 s-1
234! fco2_ocean_cor  / (86400.*year_len): PgC/yr to PgC/s
235! fco2_ocean_cor  / (86400.*year_len)*(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot: PgC/s to PgC/s/m2
236! (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
237! (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
238
239      DO i=1, klon 
240         fco2_ocean_cor(i)=(var_fco2_ocean_cor*(RMCO2/RMC) &
241              *(pctsrf(i,is_oce)+pctsrf(i,is_sic))/ocean_area_tot &
242              /(secinday*year_len))*1.e12
243      ENDDO
244
245      PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean_cor) ',MINVAL(fco2_ocean_cor)
246      PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean_cor) ',MAXVAL(fco2_ocean_cor)
247
248    ELSE
249    fco2_ocean_cor(:)=0.
250    ENDIF
251
252    IF (read_fco2_land_cor) THEN
253! var_fco2_land_cor: correction of the carbon Mass Flux out of Atmosphere Due to Net Biospheric Production on Land  (PgC/yr)
254! This is the correction of the net mass flux of carbon between land and atmosphere calculated as
255! photosynthesis MINUS the sum of plant and soil respiration, carbon fluxes from
256! fire, harvest, grazing and land use change. Positive flux is into the land.
257!    PRINT *, 'tracco2i_mod.F90 --- var_fco2_land_cor (m2) ',var_fco2_land_cor
258
259!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)
260
261! Factors for carbon and carbon dioxide
262! 1 mole CO2 = 44.009 g CO2 = 12.011 g C
263! 1 ppm by volume of atmosphere CO2 = 2.13 Gt C
264! 1 gC = 44.009/12.011 gCO2
265
266! land_area_tot: land area (m2)
267
268! year_len: year length (in days)
269
270! conversion: PgC/yr --> kg CO2 m-2 s-1
271! fco2_land_cor  / (86400.*year_len): PgC/yr to PgC/s
272! fco2_land_cor  / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot: PgC/s to PgC/s/m2
273! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) *1e12: PgC/s/m2 to kgC/s/m2
274! (fco2_land_cor / (86400.*year_len)*pctsrf(i,is_ter)/land_area_tot) * 1e12 * (RMCO2/RMC): kgC/s/m2 to kgCO2/s/m2
275
276      DO i=1, klon
277         fco2_land_cor(i)=var_fco2_land_cor*RMCO2/RMC*pctsrf(i,is_ter)/land_area_tot/(secinday*year_len)*1.e12
278      ENDDO
279
280      PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land_cor) ',MINVAL(fco2_land_cor)
281      PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land_cor) ',MAXVAL(fco2_land_cor)
282
283    ELSE
284      fco2_land_cor(:)=0.
285    ENDIF
286
287!--if fCO2_nbp is transferred we use it, otherwise we use the sum of what has been passed from ORCHIDEE
288    IF (check_fCO2_nbp_in_cfname)  THEN
289       fco2_land(:)=fco2_land_nbp(:)
290    ELSE
291       fco2_land(:)=fco2_land_nep(:)+fco2_land_fLuc(:)+fco2_land_fwoodharvest(:)+fco2_land_fHarvest(:)
292    ENDIF
293
294!!--preparing the net anthropogenic flux at the surface for mixing layer
295!!--unit kg CO2 / m2 / s
296!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ff) ',MAXVAL(fco2_ff)
297!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ff) ',MINVAL(fco2_ff)
298!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_bb) ',MAXVAL(fco2_bb)
299!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_bb) ',MINVAL(fco2_bb)
300!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land) ',MAXVAL(fco2_land)
301!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land) ',MINVAL(fco2_land)
302!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean) ',MAXVAL(fco2_ocean)
303!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean) ',MINVAL(fco2_ocean)
304!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(source(:,id_CO2)) ',MAXVAL(source(:,id_CO2))
305!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(source(:,id_CO2)) ',MINVAL(source(:,id_CO2))
306!
307!--build final source term for CO2
308    source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)-fco2_ocean_cor(:)-fco2_land_cor(:)
309
310!--computing global mean CO2 for radiation
311!--for every timestep comment out the IF ENDIF statements
312!--otherwise this is updated every day
313    IF (debutphy.OR.day_cur.NE.day_pre) THEN
314
315      CALL gather(tr_seri(:,:,id_CO2),co2_glo)
316      CALL gather(m_air,m_air_glo)
317
318!$OMP MASTER
319
320!--compute a global mean CO2 value and print its value in ppm
321       IF (is_mpi_root .AND. is_omp_root) THEN
322         RCO2_tot=SUM(co2_glo*m_air_glo)  !--unit kg CO2
323         RCO2_glo=RCO2_tot/SUM(m_air_glo) !--unit kg CO2 / kg air
324         ! the following operation is only to maintain precision consistency
325         ! of RCO2_glo which differs whether it is directly computed or read from
326         ! a restart file (after having been computed)
327         RCO2_glo = FLOAT(INT(RCO2_glo * 1e8))/1e8
328         PRINT *,'tracco2i: global CO2 in ppm =', RCO2_glo*1.e6*RMD/RMCO2
329         PRINT *,'tracco2i: total CO2 in kg =', RCO2_tot
330       ENDIF
331!$OMP END MASTER
332       CALL bcast(RCO2_glo)
333       day_pre=day_cur
334
335!--if not carbon_cycle_tr, then we reinitialize the CO2 each day to its global mean value
336       IF (.NOT.carbon_cycle_tr) THEN
337         tr_seri(:,:,id_CO2)=RCO2_glo
338       ENDIF
339    ENDIF
340
341    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)
342    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)
343
344    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)
345    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)
346
347    co2_send(:) = tr_seri(:,1,id_CO2)*1.e6*RMD/RMCO2
348
349    PRINT *, 'tracco2i_mod.F90 --- MINVAL(co2_send) ',MINVAL(co2_send)
350    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(co2_send) ',MAXVAL(co2_send)
351
352  END SUBROUTINE tracco2i
353
354  SUBROUTINE co2_emissions(debutphy)
355
356    USE dimphy
357!    USE infotrac_phy
358    USE geometry_mod, ONLY : cell_area
359    USE mod_grid_phy_lmdz
360    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
361    USE mod_phys_lmdz_para, ONLY: gather, scatter
362    USE phys_cal_mod
363
364    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open
365    USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
366
367    USE carbon_cycle_mod, ONLY : fco2_ff, fco2_bb, fco2_land, fco2_ocean
368
369    USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
370          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
371          , R_ecc, R_peri, R_incl                                      &
372          , RA, RG, R1SA                                         &
373          , RSIGMA                                                     &
374          , R, RMD, RMV, RD, RV, RCPD                    &
375          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
376          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
377          , RCW, RCS                                                 &
378          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
379          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
380          , RALPD, RBETD, RGAMD
381IMPLICIT NONE
382
383
384    LOGICAL,INTENT(IN) :: debutphy
385
386! For NetCDF:
387    INTEGER ncid_in  ! IDs for input files
388    INTEGER varid, ncerr
389
390    INTEGER :: n_glo, n_month
391    REAL, allocatable:: vector(:), time(:)
392    REAL,ALLOCATABLE       :: flx_co2ff_glo(:,:) !  fossil-fuel CO2
393    REAL,ALLOCATABLE       :: flx_co2bb_glo(:,:) !  biomass-burning CO2
394    REAL,ALLOCATABLE, SAVE :: flx_co2ff(:,:)     !  fossil-fuel CO2
395    REAL,ALLOCATABLE, SAVE :: flx_co2bb(:,:)     !  biomass-burning CO2
396!$OMP THREADPRIVATE(flx_co2ff,flx_co2bb)
397
398!! may be controlled via the .def later on
399!! also co2bb for now comes from ORCHIDEE
400    LOGICAL, PARAMETER :: readco2ff=.TRUE.
401!! this should be left to FALSE for now
402    LOGICAL, PARAMETER :: readco2bb=.FALSE.
403
404    CHARACTER (len = 20) :: modname = 'tracco2i.co2_emissions'
405    CHARACTER (len = 80) :: abort_message
406
407    IF (debutphy) THEN
408
409    ALLOCATE(flx_co2ff(klon,12))
410    ALLOCATE(flx_co2bb(klon,12))
411
412!$OMP MASTER
413    IF (is_mpi_root) THEN
414   
415      IF (.NOT.ALLOCATED(flx_co2ff_glo)) ALLOCATE(flx_co2ff_glo(klon_glo,12))
416      IF (.NOT.ALLOCATED(flx_co2bb_glo)) ALLOCATE(flx_co2bb_glo(klon_glo,12))
417
418!--reading CO2 fossil fuel emissions
419      IF (readco2ff) THEN
420
421        ! ... Open the CO2ff file
422        CALL nf95_open("sflx_lmdz_co2_ff.nc", nf90_nowrite, ncid_in)
423
424        CALL nf95_inq_varid(ncid_in, "vector", varid)
425        CALL nf95_gw_var(ncid_in, varid, vector)
426        n_glo = size(vector)
427        IF (n_glo.NE.klon_glo) THEN
428           abort_message='sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo'
429           CALL abort_physic(modname,abort_message,1)
430        ENDIF
431
432        CALL nf95_inq_varid(ncid_in, "time", varid)
433        CALL nf95_gw_var(ncid_in, varid, time)
434        n_month = size(time)
435        IF (n_month.NE.12) THEN
436           abort_message='sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12'
437           CALL abort_physic(modname,abort_message,1)
438        ENDIF
439
440!--reading flx_co2 for fossil fuel
441        CALL nf95_inq_varid(ncid_in, "flx_co2", varid)
442        ncerr = nf90_get_var(ncid_in, varid, flx_co2ff_glo)
443
444        CALL nf95_close(ncid_in)
445   
446      ELSE  !--co2ff not to be read
447        flx_co2ff_glo(:,:)=0.0
448      ENDIF
449
450!--reading CO2 biomass burning emissions
451!--using it will be inconsistent with treatment in ORCHIDEE
452      IF (readco2bb) THEN
453
454      ! ... Open the CO2bb file
455      CALL nf95_open("sflx_lmdz_co2_bb.nc", nf90_nowrite, ncid_in)
456
457      CALL nf95_inq_varid(ncid_in, "vector", varid)
458      CALL nf95_gw_var(ncid_in, varid, vector)
459      n_glo = size(vector)
460      IF (n_glo.NE.klon_glo) THEN
461         abort_message='sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo'
462         CALL abort_physic(modname,abort_message,1)
463      ENDIF
464
465      CALL nf95_inq_varid(ncid_in, "time", varid)
466      CALL nf95_gw_var(ncid_in, varid, time)
467      n_month = size(time)
468      IF (n_month.NE.12) THEN
469         abort_message='sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12'
470         CALL abort_physic(modname,abort_message,1)
471      ENDIF
472
473!--reading flx_co2 for biomass burning
474      CALL nf95_inq_varid(ncid_in, "flx_co2", varid)
475      ncerr = nf90_get_var(ncid_in, varid, flx_co2bb_glo)
476
477      CALL nf95_close(ncid_in)
478   
479      ELSE  !--co2bb not to be read
480        flx_co2bb_glo(:,:)=0.0
481      ENDIF
482
483    ENDIF
484!$OMP END MASTER
485
486    ! Allocation needed for all proc otherwise scatter might complain
487    IF (.NOT.ALLOCATED(flx_co2ff_glo)) ALLOCATE(flx_co2ff_glo(0,0))
488    IF (.NOT.ALLOCATED(flx_co2bb_glo)) ALLOCATE(flx_co2bb_glo(0,0))
489
490!--scatter on all proc
491    CALL scatter(flx_co2ff_glo,flx_co2ff)
492    CALL scatter(flx_co2bb_glo,flx_co2bb)
493
494   IF (ALLOCATED(flx_co2ff_glo)) DEALLOCATE(flx_co2ff_glo)
495   IF (ALLOCATED(flx_co2bb_glo)) DEALLOCATE(flx_co2bb_glo)
496
497  ENDIF !--end debuthy
498
499!---select the correct month
500  IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
501    PRINT *,'probleme avec le mois dans co2_ini =', mth_cur
502  ENDIF
503
504  fco2_ff(:) = flx_co2ff(:,mth_cur)
505  fco2_bb(:) = flx_co2bb(:,mth_cur)
506
507  END SUBROUTINE co2_emissions
508
509END MODULE tracco2i_mod
Note: See TracBrowser for help on using the repository browser.