Line data Source code
1 : module co2_cycle
2 :
3 : !-------------------------------------------------------------------------------
4 : !
5 : ! Purpose:
6 : ! Provides distributions of CO2_LND, CO2_OCN, CO2_FF, CO2
7 : ! Surface flux from CO2_LND and CO2_OCN can be provided by the flux coupler.
8 : ! Surface flux from CO2_FFF and CO2_OCN can be read from a file.
9 : !
10 : ! Author: Jeff Lee, Keith Lindsay
11 : !
12 : !-------------------------------------------------------------------------------
13 :
14 : use shr_kind_mod, only: r8 => shr_kind_r8, cl => shr_kind_cl
15 : use co2_data_flux, only: co2_data_flux_type
16 : use srf_field_check, only: active_Faoo_fco2_ocn
17 :
18 : implicit none
19 :
20 : private
21 :
22 : ! Public interfaces
23 : public co2_cycle_readnl ! read the namelist
24 : public co2_register ! register consituents
25 : public co2_transport ! turn on co2 tracers transport
26 : public co2_implements_cnst ! returns true if consituent is implemented by this package
27 : public co2_init_cnst ! initialize mixing ratios if not read from initial file
28 : public co2_init ! initialize (history) variables
29 : public co2_time_interp_ocn ! time interpolate co2 flux
30 : public co2_time_interp_fuel ! time interpolate co2 flux
31 : public co2_cycle_set_ptend ! set tendency from aircraft emissions
32 :
33 : ! Public data
34 : public data_flux_ocn ! data read in for co2 flux from ocn
35 : public data_flux_fuel ! data read in for co2 flux from fuel
36 :
37 : type(co2_data_flux_type) :: data_flux_ocn
38 : type(co2_data_flux_type) :: data_flux_fuel
39 :
40 : public c_i ! global index for new constituents
41 : public co2_readFlux_ocn ! read ocn co2 flux from data file
42 : public co2_readFlux_fuel ! read fuel co2 flux from data file
43 :
44 : ! Namelist variables
45 : logical :: co2_flag = .false. ! true => turn on co2 code, namelist variable
46 : logical :: co2_readFlux_ocn = .false. ! true => read ocn co2 flux from date file, namelist variable
47 : logical :: co2_readFlux_fuel = .false. ! true => read fuel co2 flux from date file, namelist variable
48 : logical :: co2_readFlux_aircraft = .false. ! true => read aircraft co2 flux from date file, namelist variable
49 : character(len=cl) :: co2flux_ocn_file = 'unset' ! co2 flux from ocn
50 : character(len=cl) :: co2flux_fuel_file = 'unset' ! co2 flux from fossil fuel
51 :
52 : !-------------------------------------------------------------------------------
53 : ! new constituents
54 : !-------------------------------------------------------------------------------
55 :
56 : integer, parameter :: ncnst=4 ! number of constituents implemented
57 :
58 : character(len=7), dimension(ncnst), parameter :: & ! constituent names
59 : c_names = (/'CO2_OCN', 'CO2_FFF', 'CO2_LND', 'CO2 '/)
60 :
61 : integer :: co2_ocn_glo_ind ! global index of 'CO2_OCN'
62 : integer :: co2_fff_glo_ind ! global index of 'CO2_FFF'
63 : integer :: co2_lnd_glo_ind ! global index of 'CO2_LND'
64 : integer :: co2_glo_ind ! global index of 'CO2'
65 :
66 : integer, dimension(ncnst) :: c_i ! global index
67 :
68 : !===============================================================================
69 : contains
70 : !===============================================================================
71 :
72 1490712 : subroutine co2_cycle_readnl(nlfile)
73 :
74 : !-------------------------------------------------------------------------------
75 : ! Purpose: Read co2_cycle_nl namelist group.
76 : !-------------------------------------------------------------------------------
77 :
78 : use namelist_utils, only: find_group_name
79 : use units, only: getunit, freeunit
80 : use spmd_utils, only: masterproc
81 : use spmd_utils, only: mpicom, mstrid=>masterprocid, mpi_logical, mpi_character
82 : use cam_logfile, only: iulog
83 : use cam_abortutils, only: endrun
84 :
85 : ! Arguments
86 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
87 :
88 : ! Local variables
89 : integer :: unitn, ierr
90 : character(len=256) :: msg
91 : character(len=*), parameter :: subname = 'co2_cycle_readnl'
92 :
93 : namelist /co2_cycle_nl/ co2_flag, co2_readFlux_ocn, co2_readFlux_fuel, co2_readFlux_aircraft, &
94 : co2flux_ocn_file, co2flux_fuel_file
95 : !----------------------------------------------------------------------------
96 :
97 1536 : if (masterproc) then
98 2 : unitn = getunit()
99 2 : open( unitn, file=trim(nlfile), status='old' )
100 2 : call find_group_name(unitn, 'co2_cycle_nl', status=ierr)
101 2 : if (ierr == 0) then
102 0 : read(unitn, co2_cycle_nl, iostat=ierr)
103 0 : if (ierr /= 0) then
104 0 : call endrun(subname // ':: ERROR reading namelist')
105 : end if
106 : end if
107 2 : close(unitn)
108 2 : call freeunit(unitn)
109 : end if
110 :
111 : ! Broadcast namelist variables
112 1536 : call mpi_bcast(co2_flag, 1, mpi_logical, mstrid, mpicom, ierr)
113 1536 : if (ierr /= 0) call endrun(subname//": FATAL: mpi_bcast: co2_flag")
114 1536 : call mpi_bcast(co2_readFlux_ocn, 1, mpi_logical, mstrid, mpicom, ierr)
115 1536 : if (ierr /= 0) call endrun(subname//": FATAL: mpi_bcast: co2_readFlux_ocn")
116 1536 : call mpi_bcast(co2_readFlux_fuel, 1, mpi_logical, mstrid, mpicom, ierr)
117 1536 : if (ierr /= 0) call endrun(subname//": FATAL: mpi_bcast: co2_readFlux_fuel")
118 1536 : call mpi_bcast(co2_readFlux_aircraft, 1, mpi_logical, mstrid, mpicom, ierr)
119 1536 : if (ierr /= 0) call endrun(subname//": FATAL: mpi_bcast: co2_readFlux_aircraft")
120 1536 : call mpi_bcast(co2flux_ocn_file, len(co2flux_ocn_file), mpi_character, mstrid, mpicom, ierr)
121 1536 : if (ierr /= 0) call endrun(subname//": FATAL: mpi_bcast: co2flux_ocn_file")
122 1536 : call mpi_bcast(co2flux_fuel_file, len(co2flux_fuel_file), mpi_character, mstrid, mpicom, ierr)
123 1536 : if (ierr /= 0) call endrun(subname//": FATAL: mpi_bcast: co2flux_fuel_file")
124 :
125 : ! Consistency check
126 1536 : if (co2_readFlux_ocn .and. active_Faoo_fco2_ocn) then
127 : msg = subname//': ERROR: reading ocn flux dataset is enabled, but coupler is setting'&
128 0 : //' the ocn co2 flux. Cannot do both.'
129 0 : write(iulog,*) trim(msg)
130 0 : call endrun(trim(msg))
131 : end if
132 :
133 1536 : end subroutine co2_cycle_readnl
134 :
135 : !===============================================================================
136 :
137 1536 : subroutine co2_register
138 :
139 : !-------------------------------------------------------------------------------
140 : ! Purpose: register advected constituents
141 : !-------------------------------------------------------------------------------
142 :
143 : use physconst, only: mwco2, cpair
144 : use constituents, only: cnst_add
145 :
146 : ! Local variables
147 : real(r8), dimension(ncnst) :: &
148 : c_mw, &! molecular weights
149 : c_cp, &! heat capacities
150 : c_qmin ! minimum mmr
151 :
152 : integer :: i
153 :
154 : !----------------------------------------------------------------------------
155 :
156 1536 : if (.not. co2_flag) return
157 :
158 0 : c_mw = (/ mwco2, mwco2, mwco2, mwco2 /)
159 0 : c_cp = (/ cpair, cpair, cpair, cpair /)
160 0 : c_qmin = (/ 1.e-20_r8, 1.e-20_r8, 1.e-20_r8, 1.e-20_r8 /)
161 :
162 : ! register CO2 constiuents as dry tracers, set indices
163 :
164 0 : do i = 1, ncnst
165 0 : call cnst_add(c_names(i), c_mw(i), c_cp(i), c_qmin(i), c_i(i), longname=c_names(i), mixtype='dry')
166 :
167 0 : select case (trim(c_names(i)))
168 : case ('CO2_OCN')
169 0 : co2_ocn_glo_ind = c_i(i)
170 : case ('CO2_FFF')
171 0 : co2_fff_glo_ind = c_i(i)
172 : case ('CO2_LND')
173 0 : co2_lnd_glo_ind = c_i(i)
174 : case ('CO2')
175 0 : co2_glo_ind = c_i(i)
176 : end select
177 : end do
178 :
179 : end subroutine co2_register
180 :
181 : !===============================================================================
182 :
183 4855464 : function co2_transport()
184 :
185 : !-------------------------------------------------------------------------------
186 : ! Purpose: return true if this package is active
187 : !-------------------------------------------------------------------------------
188 :
189 : ! Return value
190 : logical :: co2_transport
191 :
192 : !----------------------------------------------------------------------------
193 :
194 4855464 : co2_transport = co2_flag
195 :
196 4855464 : end function co2_transport
197 :
198 : !===============================================================================
199 :
200 0 : function co2_implements_cnst(name)
201 :
202 : !-------------------------------------------------------------------------------
203 : ! Purpose: return true if specified constituent is implemented by this package
204 : !-------------------------------------------------------------------------------
205 :
206 : ! Return value
207 : logical :: co2_implements_cnst
208 :
209 : ! Arguments
210 : character(len=*), intent(in) :: name ! constituent name
211 :
212 : ! Local variables
213 : integer :: m
214 :
215 : !----------------------------------------------------------------------------
216 :
217 0 : co2_implements_cnst = .false.
218 :
219 0 : if (.not. co2_flag) return
220 :
221 0 : do m = 1, ncnst
222 0 : if (name == c_names(m)) then
223 0 : co2_implements_cnst = .true.
224 : return
225 : end if
226 : end do
227 :
228 : end function co2_implements_cnst
229 :
230 : !===============================================================================
231 :
232 0 : subroutine co2_init_cnst(name, latvals, lonvals, mask, q)
233 :
234 : !-------------------------------------------------------------------------------
235 : ! Purpose:
236 : ! Set initial values of CO2_OCN, CO2_FFF, CO2_LND, CO2
237 : ! Need to be called from process_inidat in inidat.F90
238 : ! (or, initialize co2 in co2_timestep_init)
239 : !-------------------------------------------------------------------------------
240 :
241 : use chem_surfvals, only: chem_surfvals_get
242 :
243 : ! Arguments
244 : character(len=*), intent(in) :: name ! constituent name
245 : real(r8), intent(in) :: latvals(:) ! lat in degrees (ncol)
246 : real(r8), intent(in) :: lonvals(:) ! lon in degrees (ncol)
247 : logical, intent(in) :: mask(:) ! Only initialize where .true.
248 : real(r8), intent(out) :: q(:,:) ! kg tracer/kg dry air (gcol, plev)
249 :
250 : ! Local variables
251 : integer :: k
252 :
253 : !----------------------------------------------------------------------------
254 :
255 0 : if (.not. co2_flag) return
256 :
257 0 : do k = 1, size(q, 2)
258 0 : select case (name)
259 : case ('CO2_OCN')
260 0 : where(mask)
261 0 : q(:, k) = chem_surfvals_get('CO2MMR')
262 : end where
263 : case ('CO2_FFF')
264 0 : where(mask)
265 0 : q(:, k) = chem_surfvals_get('CO2MMR')
266 : end where
267 : case ('CO2_LND')
268 0 : where(mask)
269 0 : q(:, k) = chem_surfvals_get('CO2MMR')
270 : end where
271 : case ('CO2')
272 0 : where(mask)
273 0 : q(:, k) = chem_surfvals_get('CO2MMR')
274 : end where
275 : end select
276 : end do
277 :
278 0 : end subroutine co2_init_cnst
279 :
280 : !===============================================================================
281 :
282 0 : subroutine co2_init
283 :
284 : !-------------------------------------------------------------------------------
285 : ! Purpose: initialize co2,
286 : ! declare history variables,
287 : ! read co2 flux form ocn, as data_flux_ocn
288 : ! read co2 flux form fule, as data_flux_fuel
289 : !-------------------------------------------------------------------------------
290 :
291 0 : use cam_history, only: addfld, add_default, horiz_only
292 : use co2_data_flux, only: co2_data_flux_init
293 : use constituents, only: cnst_name, cnst_longname, sflxnam
294 :
295 : ! Local variables
296 : integer :: m, mm
297 :
298 : !----------------------------------------------------------------------------
299 :
300 0 : if (.not. co2_flag) return
301 :
302 : ! Add constituents and fluxes to history file
303 0 : do m = 1, ncnst
304 0 : mm = c_i(m)
305 :
306 0 : call addfld(trim(cnst_name(mm))//'_BOT', horiz_only, 'A', 'kg/kg', trim(cnst_longname(mm))//', Bottom Layer')
307 0 : call addfld(cnst_name(mm), (/ 'lev' /), 'A', 'kg/kg', cnst_longname(mm))
308 0 : call addfld(sflxnam(mm), horiz_only, 'A', 'kg/m2/s', trim(cnst_name(mm))//' surface flux')
309 :
310 0 : call add_default(cnst_name(mm), 1, ' ')
311 0 : call add_default(sflxnam(mm), 1, ' ')
312 :
313 : ! The addfld call for the 'TM*' fields are made by default in the
314 : ! constituent_burden module.
315 0 : call add_default('TM'//trim(cnst_name(mm)), 1, ' ')
316 : end do
317 :
318 : ! Read flux data
319 0 : if (co2_readFlux_ocn) then
320 0 : call co2_data_flux_init ( co2flux_ocn_file, 'CO2_flux', data_flux_ocn )
321 : end if
322 :
323 0 : if (co2_readFlux_fuel) then
324 0 : call co2_data_flux_init ( co2flux_fuel_file, 'CO2_flux', data_flux_fuel )
325 : end if
326 :
327 0 : end subroutine co2_init
328 :
329 : !===============================================================================
330 :
331 0 : subroutine co2_time_interp_ocn
332 :
333 : !-------------------------------------------------------------------------------
334 : ! Purpose: Time interpolate co2 flux to current time.
335 : ! Read in new monthly data if necessary
336 : !-------------------------------------------------------------------------------
337 :
338 0 : use time_manager, only: is_first_step
339 : use co2_data_flux, only: co2_data_flux_advance
340 :
341 : !----------------------------------------------------------------------------
342 :
343 0 : if (.not. co2_flag) return
344 :
345 0 : if (co2_readFlux_ocn) then
346 0 : call co2_data_flux_advance ( data_flux_ocn )
347 : endif
348 :
349 0 : end subroutine co2_time_interp_ocn
350 :
351 : !===============================================================================
352 :
353 0 : subroutine co2_time_interp_fuel
354 :
355 : !-------------------------------------------------------------------------------
356 : ! Purpose: Time interpolate co2 flux to current time.
357 : ! Read in new monthly data if necessary
358 : !-------------------------------------------------------------------------------
359 :
360 0 : use time_manager, only: is_first_step
361 : use co2_data_flux, only: co2_data_flux_advance
362 :
363 : !----------------------------------------------------------------------------
364 :
365 0 : if (.not. co2_flag) return
366 :
367 0 : if (co2_readFlux_fuel) then
368 0 : call co2_data_flux_advance ( data_flux_fuel )
369 : endif
370 :
371 0 : end subroutine co2_time_interp_fuel
372 :
373 : !===============================================================================
374 :
375 7445880 : subroutine co2_cycle_set_ptend(state, pbuf, ptend)
376 :
377 : !-------------------------------------------------------------------------------
378 : ! Purpose:
379 : ! Set ptend, using aircraft CO2 emissions in ac_CO2 from pbuf
380 : !-------------------------------------------------------------------------------
381 :
382 0 : use physics_types, only: physics_state, physics_ptend, physics_ptend_init
383 : use physics_buffer, only: physics_buffer_desc, pbuf_get_index, pbuf_get_field
384 : use constituents, only: pcnst
385 : use ppgrid, only: pver
386 : use physconst, only: gravit
387 :
388 : ! Arguments
389 : type(physics_state), intent(in) :: state
390 : type(physics_buffer_desc), pointer :: pbuf(:)
391 : type(physics_ptend), intent(out) :: ptend ! indivdual parameterization tendencies
392 :
393 : ! Local variables
394 : logical :: lq(pcnst)
395 : integer :: ifld, ncol, k
396 1489176 : real(r8), pointer :: ac_CO2(:,:)
397 :
398 : !----------------------------------------------------------------------------
399 :
400 1489176 : if (.not. co2_flag .or. .not. co2_readFlux_aircraft) then
401 1489176 : call physics_ptend_init(ptend, state%psetcols, 'none')
402 : return
403 : end if
404 :
405 : ! aircraft fluxes are added to 'CO2_FFF' and 'CO2' tendencies
406 0 : lq(:) = .false.
407 0 : lq(co2_fff_glo_ind) = .true.
408 0 : lq(co2_glo_ind) = .true.
409 :
410 0 : call physics_ptend_init(ptend, state%psetcols, 'co2_cycle_ac', lq=lq)
411 :
412 0 : ifld = pbuf_get_index('ac_CO2')
413 0 : call pbuf_get_field(pbuf, ifld, ac_CO2)
414 :
415 : ! [ac_CO2] = 'kg m-2 s-1'
416 : ! [ptend%q] = 'kg kg-1 s-1'
417 0 : ncol = state%ncol
418 0 : do k = 1, pver
419 0 : ptend%q(:ncol,k,co2_fff_glo_ind) = gravit * state%rpdeldry(:ncol,k) * ac_CO2(:ncol,k)
420 0 : ptend%q(:ncol,k,co2_glo_ind) = gravit * state%rpdeldry(:ncol,k) * ac_CO2(:ncol,k)
421 : end do
422 :
423 2978352 : end subroutine co2_cycle_set_ptend
424 :
425 : !===============================================================================
426 :
427 : end module co2_cycle
|