source: LMDZ6/branches/Ocean_skin/libf/phylmd/tracco2i_mod.F90 @ 3605

Last change on this file since 3605 was 3605, checked in by lguez, 4 years ago

Merge revisions 3427:3600 of trunk into branch Ocean_skin

File size: 11.6 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(pdtphys, debutphy, &
17       xlat, xlon, pphis, pphi, &
18       t_seri, pplay, paprs, tr_seri, source)
19
20    USE dimphy
21    USE infotrac_phy
22    USE geometry_mod, ONLY: cell_area
23    USE carbon_cycle_mod, ONLY: carbon_cycle_init
24    USE carbon_cycle_mod, ONLY: id_CO2, nbcf_in, fields_in, cfname_in
25    USE carbon_cycle_mod, ONLY: fco2_ocn_day, fco2_ff, fco2_bb, fco2_land, fco2_ocean
26    USE carbon_cycle_mod, ONLY: fco2_land_nbp, fco2_land_nep, fco2_land_fLuc
27    USE carbon_cycle_mod, ONLY: fco2_land_fwoodharvest, fco2_land_fHarvest
28    USE carbon_cycle_mod, ONLY: carbon_cycle_cpl, carbon_cycle_tr, carbon_cycle_rad, RCO2_glo, RCO2_tot
29    USE mod_grid_phy_lmdz
30    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
31    USE mod_phys_lmdz_para, ONLY: gather, bcast, scatter
32    USE phys_cal_mod
33    USE phys_state_var_mod, ONLY: pctsrf
34    USE indice_sol_mod, ONLY: nbsrf, is_ter, is_lic, is_oce, is_sic
35
36    IMPLICIT NONE
37
38    INCLUDE "clesphys.h"
39    INCLUDE "YOMCST.h"
40
41! Input argument
42!---------------
43    REAL,INTENT(IN)    :: pdtphys    ! Pas d'integration pour la physique (seconde)
44    LOGICAL,INTENT(IN) :: debutphy   ! le flag de l'initialisation de la physique
45
46    REAL,DIMENSION(klon),INTENT(IN)        :: xlat    ! latitudes pour chaque point
47    REAL,DIMENSION(klon),INTENT(IN)        :: xlon    ! longitudes pour chaque point
48    REAL,DIMENSION(klon),INTENT(IN)        :: pphis   ! geopotentiel du sol
49    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pphi    ! geopotentiel de chaque couche
50
51    REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
52    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
53    REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
54    REAL,DIMENSION(klon,nbtr),INTENT(INOUT):: source  ! flux de traceur [U/m2/s]
55
56! Output argument
57!----------------
58    REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT)  :: tr_seri ! Concentration Traceur [U/kgA] 
59
60! Local variables
61!----------------
62
63    INTEGER                        :: it, k, i, nb
64    REAL, DIMENSION(klon,klev)     :: m_air     ! mass of air in every grid box [kg]
65    REAL, DIMENSION(klon_glo,klev) :: co2_glo   ! variable temporaire sur la grille global
66    REAL, DIMENSION(klon_glo,klev) :: m_air_glo ! variable temporaire sur la grille global
67
68    LOGICAL, SAVE :: check_fCO2_nbp_in_cfname
69!$OMP THREADPRIVATE(check_fCO2_nbp_in_cfname)
70    INTEGER, SAVE :: day_pre=-1
71!$OMP THREADPRIVATE(day_pre)
72
73    IF (is_mpi_root) THEN
74      PRINT *,'in tracco2i: date from phys_cal_mod =',year_cur,'-',mth_cur,'-',day_cur,'-',hour
75    ENDIF
76
77!--initialisation of CO2 field if not in restart file
78!--dirty way of doing, do it better later
79!--convert 280 ppm into kg CO2 / kg air
80    IF (debutphy) THEN
81
82! Initialisation de module carbon_cycle_mod
83      IF (carbon_cycle_cpl) THEN
84        CALL carbon_cycle_init()
85      ENDIF
86
87! Initialisation de tr_seri(id_CO2) si pas initialise
88      IF (MAXVAL(tr_seri(:,:,id_CO2)).LT.1.e-15) THEN
89        tr_seri(:,:,id_CO2)=co2_ppm0*1.e-6/RMD*RMCO2 !--initialised from co2_ppm0 in rdem
90      ENDIF
91
92!--check if fCO2_nbp is in
93      check_fCO2_nbp_in_cfname=.FALSE.
94      DO nb=1, nbcf_in
95        IF (cfname_in(nb)=="fCO2_nbp") check_fCO2_nbp_in_cfname=.TRUE.
96      ENDDO
97
98    ENDIF
99
100!--calculate mass of air in every grid box in kg air
101    DO i=1, klon
102    DO k=1, klev
103      m_air(i,k)=(paprs(i,k)-paprs(i,k+1))/RG*cell_area(i)
104    ENDDO
105    ENDDO
106
107!--call CO2 emission routine
108!--co2bb is zero for now
109!--unit kg CO2 m-2 s-1
110    CALL co2_emissions(debutphy)
111
112!--retrieving land and ocean CO2 flux
113    fco2_land(:)=0.0
114    fco2_ocean(:)=0.0
115    fco2_land_nbp(:)=0.
116    fco2_land_nep(:)=0.
117    fco2_land_fLuc(:)=0.
118    fco2_land_fwoodharvest(:)=0.
119    fco2_land_fHarvest(:)=0.
120
121    DO nb=1, nbcf_in
122
123      SELECT CASE(cfname_in(nb))
124!--dealing with the different fluxes coming from ORCHIDEE
125!--fluxes come in unit of kg C m-2 s-1 is converted into kg CO2 m-2 s-1
126      CASE("fCO2_nep")
127          fco2_land_nep(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
128      CASE("fCO2_fLuc")
129          fco2_land_fLuc(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
130      CASE("fCO2_fwoodharvest")
131          fco2_land_fwoodharvest(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
132      CASE("fCO2_fHarvest")
133          fco2_land_fHarvest(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
134      CASE("fCO2_nbp")
135          fco2_land_nbp(:)=fields_in(:,nb)*RMCO2/RMC*pctsrf(:,is_ter)
136!--fCO2_fco2_ocn comes in unit of mol C02 m-2 s-1 is converted into kg CO2 m-2 s-1 + change sign
137      CASE("fCO2_fgco2")
138          fco2_ocean(:)=-1.*fco2_ocn_day(:)*RMCO2/1.e3*(pctsrf(:,is_oce)+pctsrf(:,is_sic))
139      END SELECT
140
141    ENDDO
142
143!--if fCO2_nbp is transferred we use it, otherwise we use the sum of what has been passed from ORCHIDEE
144    IF (check_fCO2_nbp_in_cfname)  THEN
145       fco2_land(:)=fco2_land_nbp(:)
146    ELSE
147       fco2_land(:)=fco2_land_nep(:)+fco2_land_fLuc(:)+fco2_land_fwoodharvest(:)+fco2_land_fHarvest(:)
148    ENDIF
149
150!!--preparing the net anthropogenic flux at the surface for mixing layer
151!!--unit kg CO2 / m2 / s
152!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ff) ',MAXVAL(fco2_ff)
153!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ff) ',MINVAL(fco2_ff)
154!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_bb) ',MAXVAL(fco2_bb)
155!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_bb) ',MINVAL(fco2_bb)
156!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_land) ',MAXVAL(fco2_land)
157!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_land) ',MINVAL(fco2_land)
158!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(fco2_ocean) ',MAXVAL(fco2_ocean)
159!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(fco2_ocean) ',MINVAL(fco2_ocean)
160!    PRINT *, 'tracco2i_mod.F90 --- MAXVAL(source(:,id_CO2)) ',MAXVAL(source(:,id_CO2))
161!    PRINT *, 'tracco2i_mod.F90 --- MINVAL(source(:,id_CO2)) ',MINVAL(source(:,id_CO2))
162!
163!--build final source term for CO2
164    source(:,id_CO2)=fco2_ff(:)+fco2_bb(:)+fco2_land(:)+fco2_ocean(:)
165
166!--computing global mean CO2 for radiation
167!--for every timestep comment out the IF ENDIF statements
168!--otherwise this is updated every day
169    IF (debutphy.OR.day_cur.NE.day_pre) THEN
170
171      CALL gather(tr_seri(:,:,id_CO2),co2_glo)
172      CALL gather(m_air,m_air_glo)
173
174!$OMP MASTER
175
176!--compute a global mean CO2 value and print its value in ppm
177       IF (is_mpi_root) THEN
178         RCO2_tot=SUM(co2_glo*m_air_glo)  !--unit kg CO2
179         RCO2_glo=RCO2_tot/SUM(m_air_glo) !--unit kg CO2 / kg air
180         PRINT *,'tracco2i: global CO2 in ppm =', RCO2_glo*1.e6*RMD/RMCO2
181         PRINT *,'tracco2i: total CO2 in kg =', RCO2_tot
182       ENDIF
183!$OMP END MASTER
184       CALL bcast(RCO2_glo)
185       day_pre=day_cur
186!--if not carbon_cycle_tr, then we reinitialize the CO2 each day to its global mean value
187       IF (.NOT.carbon_cycle_tr) THEN
188         tr_seri(:,:,id_CO2)=RCO2_glo
189       ENDIF
190    ENDIF
191
192  END SUBROUTINE tracco2i
193
194  SUBROUTINE co2_emissions(debutphy)
195
196    USE dimphy
197    USE infotrac_phy
198    USE geometry_mod, ONLY : cell_area
199    USE mod_grid_phy_lmdz
200    USE mod_phys_lmdz_mpi_data, ONLY: is_mpi_root
201    USE mod_phys_lmdz_para, ONLY: gather, scatter
202    USE phys_cal_mod
203
204    USE netcdf95, ONLY: nf95_close, nf95_gw_var, nf95_inq_varid, nf95_open
205    USE netcdf, ONLY: nf90_get_var, nf90_noerr, nf90_nowrite
206
207    USE carbon_cycle_mod, ONLY : fco2_ff, fco2_bb, fco2_land, fco2_ocean
208
209    IMPLICIT NONE
210
211    INCLUDE "YOMCST.h"
212    LOGICAL,INTENT(IN) :: debutphy
213
214! For NetCDF:
215    INTEGER ncid_in  ! IDs for input files
216    INTEGER varid, ncerr
217
218    INTEGER :: n_glo, n_month
219    REAL, POINTER:: vector(:), time(:)
220    REAL,ALLOCATABLE       :: flx_co2ff_glo(:,:) !  fossil-fuel CO2
221    REAL,ALLOCATABLE       :: flx_co2bb_glo(:,:) !  biomass-burning CO2
222    REAL,ALLOCATABLE, SAVE :: flx_co2ff(:,:)     !  fossil-fuel CO2
223    REAL,ALLOCATABLE, SAVE :: flx_co2bb(:,:)     !  biomass-burning CO2
224!$OMP THREADPRIVATE(flx_co2ff,flx_co2bb)
225
226!! may be controlled via the .def later on
227!! also co2bb for now comes from ORCHIDEE
228    LOGICAL, PARAMETER :: readco2ff=.TRUE.
229!! this should be left to FALSE for now
230    LOGICAL, PARAMETER :: readco2bb=.FALSE.
231
232    CHARACTER (len = 20) :: modname = 'tracco2i.co2_emissions'
233    CHARACTER (len = 80) :: abort_message
234
235    IF (debutphy) THEN
236
237    ALLOCATE(flx_co2ff(klon,12))
238    ALLOCATE(flx_co2bb(klon,12))
239
240!$OMP MASTER
241    IF (is_mpi_root) THEN
242   
243      IF (.NOT.ALLOCATED(flx_co2ff_glo)) ALLOCATE(flx_co2ff_glo(klon_glo,12))
244      IF (.NOT.ALLOCATED(flx_co2bb_glo)) ALLOCATE(flx_co2bb_glo(klon_glo,12))
245
246!--reading CO2 fossil fuel emissions
247      IF (readco2ff) THEN
248
249        ! ... Open the COZff file
250        CALL nf95_open("sflx_lmdz_co2_ff.nc", nf90_nowrite, ncid_in)
251
252        CALL nf95_inq_varid(ncid_in, "vector", varid)
253        CALL nf95_gw_var(ncid_in, varid, vector)
254        n_glo = size(vector)
255        IF (n_glo.NE.klon_glo) THEN
256           abort_message='sflx_lmdz_co2_ff: le nombre de points n est pas egal a klon_glo'
257           CALL abort_physic(modname,abort_message,1)
258        ENDIF
259
260        CALL nf95_inq_varid(ncid_in, "time", varid)
261        CALL nf95_gw_var(ncid_in, varid, time)
262        n_month = size(time)
263        IF (n_month.NE.12) THEN
264           abort_message='sflx_lmdz_co2_ff: le nombre de month n est pas egal a 12'
265           CALL abort_physic(modname,abort_message,1)
266        ENDIF
267
268!--reading flx_co2 for fossil fuel
269        CALL nf95_inq_varid(ncid_in, "flx_co2", varid)
270        ncerr = nf90_get_var(ncid_in, varid, flx_co2ff_glo)
271
272        CALL nf95_close(ncid_in)
273   
274      ELSE  !--co2ff not to be read
275        flx_co2ff_glo(:,:)=0.0
276      ENDIF
277
278!--reading CO2 biomass burning emissions
279!--using it will be inconsistent with treatment in ORCHIDEE
280      IF (readco2bb) THEN
281
282      ! ... Open the CO2bb file
283      CALL nf95_open("sflx_lmdz_co2_bb.nc", nf90_nowrite, ncid_in)
284
285      CALL nf95_inq_varid(ncid_in, "vector", varid)
286      CALL nf95_gw_var(ncid_in, varid, vector)
287      n_glo = size(vector)
288      IF (n_glo.NE.klon_glo) THEN
289         abort_message='sflx_lmdz_co2_bb: le nombre de points n est pas egal a klon_glo'
290         CALL abort_physic(modname,abort_message,1)
291      ENDIF
292
293      CALL nf95_inq_varid(ncid_in, "time", varid)
294      CALL nf95_gw_var(ncid_in, varid, time)
295      n_month = size(time)
296      IF (n_month.NE.12) THEN
297         abort_message='sflx_lmdz_co2_bb: le nombre de month n est pas egal a 12'
298         CALL abort_physic(modname,abort_message,1)
299      ENDIF
300
301!--reading flx_co2 for biomass burning
302      CALL nf95_inq_varid(ncid_in, "flx_co2", varid)
303      ncerr = nf90_get_var(ncid_in, varid, flx_co2bb_glo)
304
305      CALL nf95_close(ncid_in)
306   
307      ELSE  !--co2bb not to be read
308        flx_co2bb_glo(:,:)=0.0
309      ENDIF
310
311    ENDIF
312!$OMP END MASTER
313
314!--scatter on all proc
315    CALL scatter(flx_co2ff_glo,flx_co2ff)
316    CALL scatter(flx_co2bb_glo,flx_co2bb)
317
318!$OMP MASTER
319    IF (is_mpi_root) THEN
320       DEALLOCATE(flx_co2ff_glo)
321       DEALLOCATE(flx_co2bb_glo)
322    ENDIF
323!$OMP END MASTER
324
325  ENDIF !--end debuthy
326
327!---select the correct month
328  IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
329    PRINT *,'probleme avec le mois dans co2_ini =', mth_cur
330  ENDIF
331
332  fco2_ff(:) = flx_co2ff(:,mth_cur)
333  fco2_bb(:) = flx_co2bb(:,mth_cur)
334
335  END SUBROUTINE co2_emissions
336
337END MODULE tracco2i_mod
Note: See TracBrowser for help on using the repository browser.