Line data Source code
1 : !! This module is stub for a coupler between the CAM model and the Community Aerosol
2 : !! and Radiation Model for Atmospheres (CARMA) microphysics model. It is used when
3 : !! CARMA is not being used, so that the CAM code that calls CARMA does not need to
4 : !! be changed. The real version of this routine exists in the directory
5 : !! physics/carma/cam. A CARMA model can be activated by using configure with the
6 : !! option:
7 : !!
8 : !! -carma <carma_pkg>
9 : !!
10 : !! where carma_pkg is the name for a particular microphysical model.
11 : !!
12 : !! @author Chuck Bardeen
13 : !! @version May 2009
14 : module carma_intr
15 :
16 : use shr_kind_mod, only: r8 => shr_kind_r8
17 : use pmgrid, only: plat, plev, plevp, plon
18 : use ppgrid, only: pcols, pver, pverp
19 : use constituents, only: pcnst
20 : use physics_types, only: physics_state, physics_ptend, physics_ptend_init
21 : use physics_buffer, only: physics_buffer_desc
22 :
23 :
24 : implicit none
25 :
26 : private
27 : save
28 :
29 : ! Public interfaces
30 :
31 : ! CAM Physics Interface
32 : public carma_register ! register consituents
33 : public carma_is_active ! retrns true if this package is active (microphysics = .true.)
34 : public carma_implements_cnst ! returns true if consituent is implemented by this package
35 : public carma_init_cnst ! initialize constituent mixing ratios, if not read from initial file
36 : public carma_init ! initialize timestep independent variables
37 : public carma_final ! finalize the CARMA module
38 : public carma_timestep_init ! initialize timestep dependent variables
39 : public carma_timestep_tend ! interface to tendency computation
40 : public carma_accumulate_stats ! collect stats from all MPI tasks
41 :
42 : ! Other Microphysics
43 : public carma_emission_tend ! calculate tendency from emission source function
44 : public carma_calculate_cloudborne_diagnostics ! calculate model specific budget diagnostics for cloudborne aerosols
45 : public carma_output_cloudborne_diagnostics ! output model specific budget diagnostics for cloudborne aerosols
46 : public carma_output_budget_diagnostics ! calculate and output model specific aerosol budget terms
47 : public carma_wetdep_tend ! calculate tendency from wet deposition
48 :
49 : public :: carma_restart_init
50 : public :: carma_restart_write
51 : public :: carma_restart_read
52 :
53 : public carma_get_bin
54 : public carma_get_bin_cld
55 : public carma_get_dry_radius
56 : public carma_get_elem_for_group
57 : public carma_get_group_by_name
58 : public carma_get_kappa
59 : public carma_get_number
60 : public carma_get_number_cld
61 : public carma_get_total_mmr
62 : public carma_get_total_mmr_cld
63 : public carma_get_wet_radius
64 : public carma_get_bin_rmass
65 : public carma_set_bin
66 : public carma_get_sad
67 : public :: carma_get_wght_pct
68 : public :: carma_effecitive_radius
69 :
70 : public :: carma_get_bin_radius
71 :
72 : integer, parameter, public :: MAXCLDAERDIAG = 16
73 :
74 : contains
75 :
76 :
77 1536 : subroutine carma_register
78 : implicit none
79 :
80 1536 : return
81 : end subroutine carma_register
82 :
83 :
84 0 : function carma_is_active()
85 : implicit none
86 :
87 : logical :: carma_is_active
88 :
89 0 : carma_is_active = .false.
90 :
91 : return
92 : end function carma_is_active
93 :
94 :
95 27648 : function carma_implements_cnst(name)
96 : implicit none
97 :
98 : character(len=*), intent(in) :: name !! constituent name
99 : logical :: carma_implements_cnst ! return value
100 :
101 27648 : carma_implements_cnst = .false.
102 :
103 : return
104 : end function carma_implements_cnst
105 :
106 :
107 1536 : subroutine carma_init(pbuf2d)
108 : implicit none
109 : type(physics_buffer_desc), pointer :: pbuf2d(:,:)
110 :
111 1536 : return
112 : end subroutine carma_init
113 :
114 :
115 1536 : subroutine carma_final
116 : implicit none
117 :
118 1536 : return
119 : end subroutine carma_final
120 :
121 :
122 16128 : subroutine carma_timestep_init
123 : implicit none
124 :
125 16128 : return
126 : end subroutine carma_timestep_init
127 :
128 :
129 17583360 : subroutine carma_timestep_tend(state, cam_in, cam_out, ptend, dt, pbuf, dlf, rliq, prec_str, snow_str, &
130 : prec_sed, snow_sed, ustar, obklen)
131 : use hycoef, only: hyai, hybi, hyam, hybm
132 : use time_manager, only: get_nstep, get_step_size, is_first_step
133 : use camsrfexch, only: cam_in_t, cam_out_t
134 : use scamMod, only: single_column
135 :
136 : implicit none
137 :
138 : type(physics_state), intent(inout) :: state !! physics state variables
139 : type(cam_in_t), intent(in) :: cam_in !! surface inputs
140 : type(cam_out_t), intent(inout) :: cam_out !! cam output to surface models
141 : type(physics_ptend), intent(out) :: ptend !! constituent tendencies
142 : real(r8), intent(in) :: dt !! time step (s)
143 : type(physics_buffer_desc), pointer :: pbuf(:) !! physics buffer
144 : real(r8), intent(in), optional :: dlf(pcols,pver) !! Detraining cld H20 from convection (kg/kg/s)
145 : real(r8), intent(inout), optional :: rliq(pcols) !! vertical integral of liquid not yet in q(ixcldliq)
146 : real(r8), intent(out), optional :: prec_str(pcols) !! [Total] sfc flux of precip from stratiform (m/s)
147 : real(r8), intent(out), optional :: snow_str(pcols) !! [Total] sfc flux of snow from stratiform (m/s)
148 : real(r8), intent(out), optional :: prec_sed(pcols) !! total precip from cloud sedimentation (m/s)
149 : real(r8), intent(out), optional :: snow_sed(pcols) !! snow from cloud ice sedimentation (m/s)
150 : real(r8), intent(in), optional :: ustar(pcols) !! friction velocity (m/s)
151 : real(r8), intent(in), optional :: obklen(pcols) !! Obukhov length [ m ]
152 :
153 72960 : call physics_ptend_init(ptend,state%psetcols,'none') !Initialize an empty ptend for use with physics_update
154 :
155 72960 : if (present(prec_str)) prec_str(:) = 0._r8
156 72960 : if (present(snow_str)) snow_str(:) = 0._r8
157 72960 : if (present(prec_sed)) prec_sed(:) = 0._r8
158 72960 : if (present(snow_sed)) snow_sed(:) = 0._r8
159 :
160 72960 : return
161 72960 : end subroutine carma_timestep_tend
162 :
163 :
164 0 : subroutine carma_init_cnst(name, latvals, lonvals, mask, q)
165 : implicit none
166 :
167 : character(len=*), intent(in) :: name !! constituent name
168 : real(r8), intent(in) :: latvals(:) !! lat in degrees (ncol)
169 : real(r8), intent(in) :: lonvals(:) !! lon in degrees (ncol)
170 : logical, intent(in) :: mask(:) !! Only initialize where .true.
171 : real(r8), intent(out) :: q(:,:) !! mass mixing ratio
172 :
173 0 : if (name == "carma") then
174 0 : q = 0._r8
175 : end if
176 :
177 0 : return
178 72960 : end subroutine carma_init_cnst
179 :
180 0 : subroutine carma_calculate_cloudborne_diagnostics(state, pbuf, aerclddiag)
181 :
182 : implicit none
183 :
184 : type(physics_state), intent(in) :: state !! Physics state variables - before CARMA
185 : type(physics_buffer_desc), pointer :: pbuf(:) !! physics buffer
186 : real(r8), intent(out) :: aerclddiag(pcols, MAXCLDAERDIAG) !! previous cloudborne diagnostics
187 :
188 0 : return
189 : end subroutine carma_calculate_cloudborne_diagnostics
190 :
191 :
192 0 : subroutine carma_output_cloudborne_diagnostics(state, pbuf, pname, dt, oldaerclddiag)
193 :
194 : implicit none
195 :
196 : type(physics_state), intent(in) :: state !! Physics state variables - before CARMA
197 : type(physics_buffer_desc), pointer :: pbuf(:) !! physics buffer
198 : character(*), intent(in) :: pname !! short name of the physics package
199 : real(r8), intent(in) :: dt !! timestep (s)
200 : real(r8), intent(in) :: oldaerclddiag(pcols, MAXCLDAERDIAG) !! previous cloudborne diagnostics
201 :
202 0 : return
203 : end subroutine carma_output_cloudborne_diagnostics
204 :
205 :
206 0 : subroutine carma_output_budget_diagnostics(state, ptend, old_cflux, cflux, dt, pname)
207 :
208 : implicit none
209 :
210 : type(physics_state), intent(in) :: state !! Physics state variables - before CARMA
211 : type(physics_ptend), intent(in) :: ptend !! indivdual parameterization tendencies
212 : real(r8) :: old_cflux(pcols,pcnst) !! cam_in%clfux from before the timestep_tend
213 : real(r8) :: cflux(pcols,pcnst) !! cam_in%clfux from after the timestep_tend
214 : real(r8), intent(in) :: dt !! timestep (s)
215 : character(*), intent(in) :: pname !! short name of the physics package
216 :
217 :
218 0 : return
219 : end subroutine carma_output_budget_diagnostics
220 :
221 0 : subroutine carma_emission_tend(state, ptend, cam_in, dt, pbuf)
222 : use camsrfexch, only: cam_in_t
223 :
224 : implicit none
225 :
226 : type(physics_state), intent(in ) :: state !! physics state
227 : type(physics_ptend), intent(inout) :: ptend !! physics state tendencies
228 : type(cam_in_t), intent(inout) :: cam_in !! surface inputs
229 : real(r8), intent(in) :: dt !! time step (s)
230 : type(physics_buffer_desc), pointer :: pbuf(:) !! physics buffer
231 :
232 0 : return
233 0 : end subroutine carma_emission_tend
234 :
235 :
236 0 : subroutine carma_wetdep_tend(state, ptend, dt, pbuf, dlf, cam_out)
237 0 : use camsrfexch, only: cam_out_t
238 :
239 : implicit none
240 :
241 : real(r8), intent(in) :: dt !! time step (s)
242 : type(physics_state), intent(in ) :: state !! physics state
243 : type(physics_ptend), intent(inout) :: ptend !! physics state tendencies
244 : type(physics_buffer_desc), pointer :: pbuf(:) !! physics buffer
245 : real(r8), intent(in) :: dlf(pcols,pver) !! Detraining cld H20 from convection (kg/kg/s)
246 : type(cam_out_t), intent(inout) :: cam_out !! cam output to surface models
247 :
248 0 : return
249 0 : end subroutine carma_wetdep_tend
250 :
251 :
252 14592 : subroutine carma_accumulate_stats()
253 : implicit none
254 :
255 0 : end subroutine carma_accumulate_stats
256 :
257 : !---------------------------------------------------------------------------
258 : ! define fields for reference profiles in cam restart file
259 : !---------------------------------------------------------------------------
260 1536 : subroutine CARMA_restart_init( File )
261 : use pio, only: file_desc_t
262 :
263 : ! arguments
264 : type(file_desc_t),intent(inout) :: File ! pio File pointer
265 :
266 1536 : end subroutine CARMA_restart_init
267 :
268 : !---------------------------------------------------------------------------
269 : ! write reference profiles to restart file
270 : !---------------------------------------------------------------------------
271 1536 : subroutine CARMA_restart_write(File)
272 : use pio, only: file_desc_t
273 :
274 : ! arguments
275 : type(file_desc_t), intent(inout) :: File
276 :
277 1536 : end subroutine CARMA_restart_write
278 :
279 : !---------------------------------------------------------------------------
280 : ! read reference profiles from restart file
281 : !---------------------------------------------------------------------------
282 768 : subroutine CARMA_restart_read(File)
283 : use pio, only: file_desc_t
284 :
285 : ! arguments
286 : type(file_desc_t),intent(inout) :: File ! pio File pointer
287 :
288 768 : end subroutine CARMA_restart_read
289 :
290 :
291 : !! Get the mixing ratio for the specified element and bin.
292 0 : subroutine carma_get_bin(state, ielem, ibin, mmr, rc)
293 : type(physics_state), intent(in) :: state !! physics state variables
294 : integer, intent(in) :: ielem !! element index
295 : integer, intent(in) :: ibin !! bin index
296 : real(r8), intent(out) :: mmr(pcols,pver) !! mass mixing ratio (kg/kg)
297 : integer, intent(out) :: rc !! return code
298 :
299 0 : end subroutine carma_get_bin
300 : !! Get the mixing ratio for the specified element and bin.
301 0 : subroutine carma_get_bin_cld(pbuf, ielem, ibin, ncol, nlev, mmr, rc)
302 : type(physics_buffer_desc), pointer :: pbuf(:) !! physics buffer
303 : integer, intent(in) :: ielem !! element index
304 : integer, intent(in) :: ibin !! bin index
305 : integer, intent(in) :: ncol,nlev !! dimensions
306 : real(r8), intent(out) :: mmr(:,:) !! mass mixing ratio (kg/kg)
307 : integer, intent(out) :: rc !! return code
308 :
309 0 : end subroutine carma_get_bin_cld
310 : !! Determine the dry radius and dry density for the particular bin.
311 0 : subroutine carma_get_dry_radius(state, igroup, ibin, rdry, rhopdry, rc)
312 : type(physics_state), intent(in) :: state !! physics state variables
313 : integer, intent(in) :: igroup !! group index
314 : integer, intent(in) :: ibin !! bin index
315 : real(r8), intent(out) :: rdry(:,:) !! dry radius (m)
316 : real(r8), intent(out) :: rhopdry(:,:) !! dry density (kg/m3)
317 : integer, intent(out) :: rc !! return code
318 :
319 0 : end subroutine carma_get_dry_radius
320 : !! Get the number of elements and list of element ids for a group. This includes
321 0 : subroutine carma_get_elem_for_group(igroup, nelems, ielems, rc)
322 : integer, intent(in) :: igroup !! group index
323 : integer, intent(out) :: nelems !! number of elements in group
324 : integer, intent(out) :: ielems(:) !! indexes of elements in group
325 : integer, intent(out) :: rc !! return code
326 0 : end subroutine carma_get_elem_for_group
327 : !! Get the CARMA group id a group name.
328 0 : subroutine carma_get_group_by_name(shortname, igroup, rc)
329 : character(len=*), intent(in) :: shortname !! the group short name
330 : integer, intent(out) :: igroup !! group index
331 : integer, intent(out) :: rc !! return code
332 :
333 0 : end subroutine carma_get_group_by_name
334 : !! Get the CARMA group id and bin id from a compound name xxxxxxnn, where xxxxxx is the
335 : subroutine carma_get_group_and_bin_by_name(shortname, igroup, ibin, rc)
336 : character(len=*), intent(out) :: shortname !! the group short name
337 : integer, intent(out) :: igroup !! group index
338 : integer, intent(out) :: ibin !! bin index
339 : integer, intent(out) :: rc !! return code
340 :
341 : end subroutine carma_get_group_and_bin_by_name
342 : !! Determine a mass weighted kappa for the entire particle.
343 0 : subroutine carma_get_kappa(state, igroup, ibin, kappa, rc)
344 : type(physics_state), intent(in) :: state !! physics state variables
345 : integer, intent(in) :: igroup !! group index
346 : integer, intent(in) :: ibin !! bin index
347 : real(r8), intent(out) :: kappa(:,:) !! kappa value for the entire particle
348 : integer, intent(out) :: rc !! return code
349 0 : end subroutine carma_get_kappa
350 : !! Get the number mixing ratio for the group. This is the number of particles per
351 0 : subroutine carma_get_number(state, igroup, ibin, nmr, rc)
352 : type(physics_state), intent(in) :: state !! physics state variables
353 : integer, intent(in) :: igroup !! group index
354 : integer, intent(in) :: ibin !! bin index
355 : real(r8), intent(out) :: nmr(pcols,pver) !! number mixing ratio (#/kg)
356 : integer, intent(out) :: rc !! return code
357 0 : end subroutine carma_get_number
358 :
359 0 : subroutine carma_get_number_cld(pbuf, igroup, ibin, ncol, nlev, nmr, rc)
360 : type(physics_buffer_desc),pointer :: pbuf(:) !! physics buffer
361 : integer, intent(in) :: igroup !! group index
362 : integer, intent(in) :: ibin !! bin index
363 : integer, intent(in) :: ncol,nlev !! dimensions
364 : real(r8), intent(out) :: nmr(pcols,pver) !! number mixing ratio (#/kg)
365 : integer, intent(out) :: rc !! return code
366 0 : end subroutine carma_get_number_cld
367 : !! Get the mixing ratio for the group. This is the total of all the elements that
368 0 : subroutine carma_get_total_mmr(state, igroup, ibin, totmmr, rc)
369 : type(physics_state), intent(in) :: state !! physics state variables
370 : integer, intent(in) :: igroup !! group index
371 : integer, intent(in) :: ibin !! bin index
372 : real(r8), intent(out) :: totmmr(pcols,pver) !! total mmr (kg/kg)
373 : integer, intent(out) :: rc !! return code
374 0 : end subroutine carma_get_total_mmr
375 :
376 0 : subroutine carma_get_total_mmr_cld(pbuf, igroup, ibin, ncol, nlev, totmmr, rc)
377 : type(physics_buffer_desc),pointer :: pbuf(:) !! physics buffer
378 : integer, intent(in) :: igroup !! group index
379 : integer, intent(in) :: ibin !! bin index
380 : integer, intent(in) :: ncol,nlev !! dimensions
381 : real(r8), intent(out) :: totmmr(pcols,pver) !! total mmr (kg/kg)
382 : integer, intent(out) :: rc !! return code
383 :
384 0 : end subroutine carma_get_total_mmr_cld
385 :
386 0 : subroutine carma_get_sad(state, igroup, ibin, sad, rc)
387 : type(physics_state), intent(in) :: state !! physics state variables
388 : integer, intent(in) :: igroup !! group index
389 : integer, intent(in) :: ibin !! bin index
390 : real(r8), intent(out) :: sad(pcols,pver) !! surface area dens (cm2/cm3)
391 : integer, intent(out) :: rc !! return code
392 0 : end subroutine carma_get_sad
393 :
394 : !! Find the wet radius and wet density for the group and bin specified.
395 0 : subroutine carma_get_wet_radius(state, igroup, ibin, rwet, rhopwet, rc)
396 : type(physics_state), intent(in) :: state !! physics state variables
397 : integer, intent(in) :: igroup !! group index
398 : integer, intent(in) :: ibin !! bin index
399 : real(r8), intent(out) :: rwet(pcols,pver) !! wet radius (m)
400 : real(r8), intent(out) :: rhopwet(pcols,pver) !! wet density (kg/m3)
401 : integer, intent(inout) :: rc !! return code
402 :
403 0 : end subroutine carma_get_wet_radius
404 : !! Provides the tendency (in kg/kg/s) required to change the element and bin from
405 : !! the current state to the desired mmr.
406 0 : subroutine carma_set_bin(state, ielem, ibin, mmr, dt, ptend, rc)
407 : type(physics_state), intent(in) :: state !! physics state variables
408 : integer, intent(in) :: ielem !! element index
409 : integer, intent(in) :: ibin !! bin index
410 : real(r8), intent(in) :: mmr(pcols,pver) !! mass mixing ratio (kg/kg)
411 : integer :: dt !! timestep size (sec)
412 : type(physics_ptend), intent(inout) :: ptend !! constituent tendencies
413 : integer, intent(out) :: rc !! return code
414 0 : end subroutine carma_set_bin
415 :
416 0 : subroutine carma_get_bin_rmass(igroup, ibin, mass, rc)
417 :
418 : integer, intent(in) :: igroup !! group index
419 : integer, intent(in) :: ibin !! bin index
420 : real(r8),intent(out) :: mass ! grams ???
421 : integer, intent(out) :: rc !! return code
422 :
423 0 : end subroutine carma_get_bin_rmass
424 :
425 0 : function carma_get_wght_pct(icol,ilev,state) result(wtpct)
426 :
427 : integer, intent(in) :: icol,ilev
428 : type(physics_state), intent(in) :: state !! Physics state variables - before CARMA
429 :
430 : real(r8) :: wtpct
431 :
432 0 : end function carma_get_wght_pct
433 :
434 :
435 0 : function carma_effecitive_radius(state) result(rad)
436 :
437 : type(physics_state), intent(in) :: state !! physics state variables
438 : real(r8) :: rad(pcols,pver) ! effective radius (cm)
439 0 : end function carma_effecitive_radius
440 :
441 : !-----------------------------------------------------------------------------
442 : !-----------------------------------------------------------------------------
443 0 : subroutine carma_get_bin_radius(igroup, ibin, radius, rc)
444 : integer, intent(in) :: igroup !! group index
445 : integer, intent(in) :: ibin !! bin index
446 : real(r8),intent(out) :: radius ! cm ???
447 : integer, intent(out) :: rc !! return code
448 0 : end subroutine carma_get_bin_radius
449 :
450 : end module carma_intr
|