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