source: LMDZ6/branches/Amaury_dev/libf/phylmd/tracco2i_mod.F90 @ 5157

Last change on this file since 5157 was 5144, checked in by abarral, 7 weeks ago

Put YOMCST.h into modules

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