Line data Source code
1 : module phys_control
2 : !-----------------------------------------------------------------------
3 : ! Purpose:
4 : !
5 : ! Provides a control interface to CAM physics packages
6 : !
7 : ! Revision history:
8 : ! 2006-05-01 D. B. Coleman, Creation of module
9 : ! 2009-02-13 Eaton Replace *_{default,set}opts methods with module namelist.
10 : ! Add vars to indicate physics version and chemistry type.
11 : !-----------------------------------------------------------------------
12 :
13 : use spmd_utils, only: masterproc
14 : use cam_logfile, only: iulog
15 : use cam_abortutils, only: endrun
16 : use shr_kind_mod, only: r8 => shr_kind_r8, cl=>shr_kind_cl
17 :
18 : implicit none
19 : private
20 : save
21 :
22 : public :: &
23 : phys_ctl_readnl, &! read namelist from file
24 : phys_getopts, &! generic query method
25 : phys_setopts, &! generic set method
26 : phys_deepconv_pbl, &! return true if deep convection is allowed in the PBL
27 : phys_do_flux_avg, &! return true to average surface fluxes
28 : cam_physpkg_is, &! query for the name of the physics package
29 : cam_chempkg_is, &! query for the name of the chemistry package
30 : waccmx_is
31 :
32 : ! Private module data
33 :
34 : character(len=16), parameter :: unset_str = 'UNSET'
35 : integer, parameter :: unset_int = huge(1)
36 :
37 : ! Namelist variables:
38 : character(len=16) :: cam_physpkg = unset_str ! CAM physics package
39 : character(len=32) :: cam_chempkg = unset_str ! CAM chemistry package
40 : character(len=16) :: waccmx_opt = unset_str ! WACCMX run option [ionosphere | neutral | off
41 : character(len=16) :: deep_scheme = unset_str ! deep convection package
42 : character(len=16) :: shallow_scheme = unset_str ! shallow convection package
43 : character(len=16) :: eddy_scheme = unset_str ! vertical diffusion package
44 : character(len=16) :: microp_scheme = unset_str ! microphysics package
45 : character(len=16) :: macrop_scheme = unset_str ! macrophysics package
46 : character(len=16) :: radiation_scheme = unset_str ! radiation package
47 : character(len=cl) :: cam_physics_mesh = unset_str ! SCRIP file for phys
48 : integer :: srf_flux_avg = unset_int ! 1 => smooth surface fluxes, 0 otherwise
49 :
50 : logical :: use_subcol_microp = .false. ! if .true. then use sub-columns in microphysics
51 :
52 : logical :: atm_dep_flux = .true. ! true => deposition fluxes will be provided
53 : ! to the coupler
54 : logical :: history_amwg = .true. ! output the variables used by the AMWG diag package
55 : logical :: history_vdiag = .false. ! output the variables used by the AMWG variability diag package
56 : logical :: history_aerosol = .false. ! output the MAM aerosol variables and tendencies
57 : logical :: history_aero_optics = .false. ! output the aerosol
58 : logical :: history_eddy = .false. ! output the eddy variables
59 : logical :: history_budget = .false. ! output tendencies and state variables for T, water vapor,
60 : ! cloud ice and cloud liquid budgets
61 : logical :: convproc_do_aer = .false. ! switch for new convective scavenging treatment for modal aerosols
62 :
63 : integer :: history_budget_histfile_num = 1 ! output history file number for budget fields
64 : logical :: history_waccm = .false. ! output variables of interest for WACCM runs
65 : logical :: history_waccmx = .false. ! output variables of interest for WACCM-X runs
66 : logical :: history_chemistry = .true. ! output default chemistry-related variables
67 : logical :: history_carma = .false. ! output default CARMA-related variables
68 : logical :: history_carma_srf_flx= .false. ! output default CARMA-related variables
69 : logical :: history_clubb = .true. ! output default CLUBB-related variables
70 : logical :: history_cesm_forcing = .false.
71 : logical :: history_dust = .false.
72 : logical :: history_scwaccm_forcing = .false.
73 : logical :: history_chemspecies_srf = .false.
74 :
75 : logical :: do_clubb_sgs
76 : logical :: do_hb_above_clubb = .false. ! enable HB vertical mixing above clubb top
77 :
78 : ! Check validity of physics_state objects in physics_update.
79 : logical :: state_debug_checks = .false.
80 :
81 : ! Macro/micro-physics co-substeps
82 : integer :: cld_macmic_num_steps = 1
83 :
84 : logical :: offline_driver = .false. ! true => offline driver is being used
85 :
86 :
87 : logical, public, protected :: use_simple_phys = .false. ! true => simple physics configuration
88 :
89 : logical :: prog_modal_aero ! determines whether prognostic modal aerosols are present in the run.
90 :
91 : ! Option to use heterogeneous freezing
92 : logical, public, protected :: use_hetfrz_classnuc = .false.
93 :
94 : ! Which gravity wave sources are used?
95 : logical, public, protected :: use_gw_oro = .true. ! Orography.
96 : logical, public, protected :: use_gw_front = .false. ! Frontogenesis.
97 : logical, public, protected :: use_gw_front_igw = .false. ! Frontogenesis to inertial spectrum.
98 : logical, public, protected :: use_gw_convect_dp = .false. ! Deep convection.
99 : logical, public, protected :: use_gw_convect_sh = .false. ! Shallow convection.
100 : logical, public, protected :: use_gw_movmtn_pbl = .false. ! moving mountain
101 :
102 : ! FV dycore angular momentum correction
103 : logical, public, protected :: fv_am_correction = .false.
104 :
105 : ! Option for Harmonized Emissions Component (HEMCO)
106 : logical, public, protected :: use_hemco = .false.
107 :
108 : ! CAM snapshot before/after file numbers and control
109 : character(len=32) :: cam_take_snapshot_before = '' ! Physics routine to take a snopshot "before"
110 : character(len=32) :: cam_take_snapshot_after = '' ! Physics routine to take a snopshot "after"
111 : integer :: cam_snapshot_before_num = -1 ! output history file number for CAM "before" snapshot
112 : integer :: cam_snapshot_after_num = -1 ! output history file number for CAM "after" snapshot
113 :
114 : !=======================================================================
115 : contains
116 : !=======================================================================
117 :
118 2304 : subroutine phys_ctl_readnl(nlfile)
119 :
120 : use namelist_utils, only: find_group_name
121 : use units, only: getunit, freeunit
122 : use spmd_utils, only: mpi_character, mpi_integer, mpi_logical, masterprocid, mpicom
123 : use cam_control_mod, only: cam_ctrl_set_physics_type
124 :
125 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
126 :
127 : ! Local variables
128 : integer :: unitn, ierr
129 : character(len=*), parameter :: subname = 'phys_ctl_readnl'
130 :
131 : namelist /phys_ctl_nl/ cam_physpkg, use_simple_phys, cam_chempkg, waccmx_opt, &
132 : deep_scheme, shallow_scheme, &
133 : eddy_scheme, microp_scheme, macrop_scheme, radiation_scheme, srf_flux_avg, &
134 : use_subcol_microp, atm_dep_flux, history_amwg, history_vdiag, history_aerosol, history_aero_optics, &
135 : history_eddy, history_budget, history_budget_histfile_num, history_waccm, &
136 : history_waccmx, history_chemistry, history_carma, history_carma_srf_flx, &
137 : history_clubb, history_dust, &
138 : history_cesm_forcing, history_scwaccm_forcing, history_chemspecies_srf, &
139 : do_clubb_sgs, state_debug_checks, use_hetfrz_classnuc, use_gw_oro, use_gw_front, &
140 : use_gw_front_igw, use_gw_convect_dp, use_gw_convect_sh, use_gw_movmtn_pbl, cld_macmic_num_steps, &
141 : offline_driver, convproc_do_aer, cam_snapshot_before_num, cam_snapshot_after_num, &
142 : cam_take_snapshot_before, cam_take_snapshot_after, cam_physics_mesh, use_hemco, do_hb_above_clubb
143 : !-----------------------------------------------------------------------------
144 :
145 2304 : if (masterproc) then
146 3 : unitn = getunit()
147 3 : open( unitn, file=trim(nlfile), status='old' )
148 3 : call find_group_name(unitn, 'phys_ctl_nl', status=ierr)
149 3 : if (ierr == 0) then
150 3 : read(unitn, phys_ctl_nl, iostat=ierr)
151 3 : if (ierr /= 0) then
152 0 : call endrun(subname // ':: ERROR reading namelist')
153 : end if
154 : end if
155 3 : close(unitn)
156 3 : call freeunit(unitn)
157 : end if
158 :
159 : ! Broadcast namelist variables
160 2304 : call mpi_bcast(deep_scheme, len(deep_scheme), mpi_character, masterprocid, mpicom, ierr)
161 2304 : call mpi_bcast(cam_physpkg, len(cam_physpkg), mpi_character, masterprocid, mpicom, ierr)
162 2304 : call mpi_bcast(use_simple_phys, 1, mpi_logical, masterprocid, mpicom, ierr)
163 2304 : call mpi_bcast(cam_chempkg, len(cam_chempkg), mpi_character, masterprocid, mpicom, ierr)
164 2304 : call mpi_bcast(waccmx_opt, len(waccmx_opt), mpi_character, masterprocid, mpicom, ierr)
165 2304 : call mpi_bcast(shallow_scheme, len(shallow_scheme), mpi_character, masterprocid, mpicom, ierr)
166 2304 : call mpi_bcast(eddy_scheme, len(eddy_scheme), mpi_character, masterprocid, mpicom, ierr)
167 2304 : call mpi_bcast(microp_scheme, len(microp_scheme), mpi_character, masterprocid, mpicom, ierr)
168 2304 : call mpi_bcast(radiation_scheme, len(radiation_scheme), mpi_character, masterprocid, mpicom, ierr)
169 2304 : call mpi_bcast(macrop_scheme, len(macrop_scheme), mpi_character, masterprocid, mpicom, ierr)
170 2304 : call mpi_bcast(srf_flux_avg, 1, mpi_integer, masterprocid, mpicom, ierr)
171 2304 : call mpi_bcast(use_subcol_microp, 1, mpi_logical, masterprocid, mpicom, ierr)
172 2304 : call mpi_bcast(atm_dep_flux, 1, mpi_logical, masterprocid, mpicom, ierr)
173 2304 : call mpi_bcast(history_amwg, 1, mpi_logical, masterprocid, mpicom, ierr)
174 2304 : call mpi_bcast(history_vdiag, 1, mpi_logical, masterprocid, mpicom, ierr)
175 2304 : call mpi_bcast(history_eddy, 1, mpi_logical, masterprocid, mpicom, ierr)
176 2304 : call mpi_bcast(history_aerosol, 1, mpi_logical, masterprocid, mpicom, ierr)
177 2304 : call mpi_bcast(history_aero_optics, 1, mpi_logical, masterprocid, mpicom, ierr)
178 2304 : call mpi_bcast(history_budget, 1, mpi_logical, masterprocid, mpicom, ierr)
179 2304 : call mpi_bcast(history_budget_histfile_num, 1, mpi_integer, masterprocid, mpicom, ierr)
180 2304 : call mpi_bcast(history_waccm, 1, mpi_logical, masterprocid, mpicom, ierr)
181 2304 : call mpi_bcast(history_waccmx, 1, mpi_logical, masterprocid, mpicom, ierr)
182 2304 : call mpi_bcast(history_chemistry, 1, mpi_logical, masterprocid, mpicom, ierr)
183 2304 : call mpi_bcast(history_carma, 1, mpi_logical, masterprocid, mpicom, ierr)
184 2304 : call mpi_bcast(history_carma_srf_flx, 1, mpi_logical, masterprocid, mpicom, ierr)
185 2304 : call mpi_bcast(history_clubb, 1, mpi_logical, masterprocid, mpicom, ierr)
186 2304 : call mpi_bcast(history_cesm_forcing, 1, mpi_logical, masterprocid, mpicom, ierr)
187 2304 : call mpi_bcast(history_chemspecies_srf, 1, mpi_logical, masterprocid, mpicom, ierr)
188 2304 : call mpi_bcast(history_dust, 1, mpi_logical, masterprocid, mpicom, ierr)
189 2304 : call mpi_bcast(history_scwaccm_forcing, 1, mpi_logical, masterprocid, mpicom, ierr)
190 2304 : call mpi_bcast(do_clubb_sgs, 1, mpi_logical, masterprocid, mpicom, ierr)
191 2304 : call mpi_bcast(state_debug_checks, 1, mpi_logical, masterprocid, mpicom, ierr)
192 2304 : call mpi_bcast(use_hetfrz_classnuc, 1, mpi_logical, masterprocid, mpicom, ierr)
193 2304 : call mpi_bcast(use_gw_oro, 1, mpi_logical, masterprocid, mpicom, ierr)
194 2304 : call mpi_bcast(use_gw_front, 1, mpi_logical, masterprocid, mpicom, ierr)
195 2304 : call mpi_bcast(use_gw_front_igw, 1, mpi_logical, masterprocid, mpicom, ierr)
196 2304 : call mpi_bcast(use_gw_convect_dp, 1, mpi_logical, masterprocid, mpicom, ierr)
197 2304 : call mpi_bcast(use_gw_convect_sh, 1, mpi_logical, masterprocid, mpicom, ierr)
198 2304 : call mpi_bcast(use_gw_movmtn_pbl, 1, mpi_logical, masterprocid, mpicom, ierr)
199 2304 : call mpi_bcast(cld_macmic_num_steps, 1, mpi_integer, masterprocid, mpicom, ierr)
200 2304 : call mpi_bcast(offline_driver, 1, mpi_logical, masterprocid, mpicom, ierr)
201 2304 : call mpi_bcast(convproc_do_aer, 1, mpi_logical, masterprocid, mpicom, ierr)
202 2304 : call mpi_bcast(cam_snapshot_before_num, 1, mpi_integer, masterprocid, mpicom, ierr)
203 2304 : call mpi_bcast(cam_snapshot_after_num, 1, mpi_integer, masterprocid, mpicom, ierr)
204 2304 : call mpi_bcast(cam_take_snapshot_before, len(cam_take_snapshot_before), mpi_character, masterprocid, mpicom, ierr)
205 2304 : call mpi_bcast(cam_take_snapshot_after, len(cam_take_snapshot_after), mpi_character, masterprocid, mpicom, ierr)
206 2304 : call mpi_bcast(cam_physics_mesh, len(cam_physics_mesh), mpi_character, masterprocid, mpicom, ierr)
207 2304 : call mpi_bcast(do_hb_above_clubb, 1, mpi_logical, masterprocid, mpicom, ierr)
208 2304 : call mpi_bcast(use_hemco, 1, mpi_logical, masterprocid, mpicom, ierr)
209 :
210 2304 : call cam_ctrl_set_physics_type(cam_physpkg)
211 :
212 : ! Error checking:
213 :
214 : ! Check compatibility of eddy & shallow schemes
215 2304 : if (( shallow_scheme .eq. 'UW' ) .and. ( eddy_scheme .ne. 'diag_TKE' )) then
216 0 : write(iulog,*)'Do you really want to run UW shallow scheme without diagnostic TKE eddy scheme? Quiting'
217 0 : call endrun('shallow convection and eddy scheme may be incompatible')
218 : endif
219 :
220 2304 : if (( shallow_scheme .eq. 'Hack' ) .and. ( ( eddy_scheme .ne. 'HB' ) .and. ( eddy_scheme .ne. 'HBR' ))) then
221 0 : write(iulog,*)'Do you really want to run Hack shallow scheme with a non-standard eddy scheme? Quiting.'
222 0 : call endrun('shallow convection and eddy scheme may be incompatible')
223 : endif
224 :
225 : ! Check compatibility of PBL and Microphysics schemes
226 2304 : if (( eddy_scheme .eq. 'diag_TKE' ) .and. ( microp_scheme .eq. 'RK' )) then
227 0 : write(iulog,*)'UW PBL is not compatible with RK microphysics. Quiting'
228 0 : call endrun('PBL and Microphysics schemes incompatible')
229 : endif
230 :
231 : ! Add a check to make sure CLUBB and MG are used together
232 2304 : if ( do_clubb_sgs .and. microp_scheme .ne. 'MG') then
233 0 : write(iulog,*)'CLUBB is only compatible with MG microphysics. Quiting'
234 0 : call endrun('CLUBB and microphysics schemes incompatible')
235 : endif
236 :
237 : ! Check that eddy_scheme, macrop_scheme, shallow_scheme are all set to CLUBB_SGS if do_clubb_sgs is true
238 2304 : if (do_clubb_sgs) then
239 2304 : if (eddy_scheme .ne. 'CLUBB_SGS' .or. macrop_scheme .ne. 'CLUBB_SGS' .or. shallow_scheme .ne. 'CLUBB_SGS') then
240 0 : write(iulog,*)'eddy_scheme, macrop_scheme and shallow_scheme must all be CLUBB_SGS. Quiting'
241 0 : call endrun('CLUBB and eddy, macrop or shallow schemes incompatible')
242 : endif
243 : endif
244 :
245 2304 : if (cam_physpkg_is("cam7")) then
246 : ! Check that eddy_scheme, macrop_scheme, shallow_scheme are all set to CLUBB
247 2304 : if (eddy_scheme /= 'CLUBB_SGS' .or. macrop_scheme /= 'CLUBB_SGS' .or. shallow_scheme /= 'CLUBB_SGS') then
248 0 : write(iulog,*) 'cam7 is only compatible with CLUBB. Quitting'
249 0 : call endrun('cam7 is only compatible with eddy, macrop, and shallow schemes = CLUBB_SGS')
250 : end if
251 : ! Add check to make sure we are not trying to use `camrt`
252 2304 : if (trim(radiation_scheme) == 'camrt') then
253 0 : write(iulog,*) ' camrt specified and it is not compatible with cam7'
254 0 : call endrun('cam7 is not compatible with camrt radiation scheme')
255 : end if
256 : end if
257 :
258 : ! do_hb_above_clubb requires that CLUBB is being used
259 2304 : if (do_hb_above_clubb .and. .not. do_clubb_sgs) then
260 0 : write(iulog,*)'do_hb_above_clubb requires CLUBB to be active'
261 0 : call endrun('do_hb_above_clubb incompatible with do_clubb_sgs = .false.')
262 : endif
263 :
264 : ! Macro/micro co-substepping support.
265 2304 : if (cld_macmic_num_steps > 1) then
266 2304 : if (microp_scheme /= "MG" .or. (macrop_scheme /= "park" .and. macrop_scheme /= "CLUBB_SGS")) then
267 : call endrun ("Setting cld_macmic_num_steps > 1 is only &
268 0 : &supported with Park or CLUBB macrophysics and MG microphysics.")
269 : end if
270 : end if
271 :
272 : ! prog_modal_aero determines whether prognostic modal aerosols are present in the run.
273 2304 : prog_modal_aero = index(cam_chempkg,'_mam')>0
274 :
275 2304 : end subroutine phys_ctl_readnl
276 :
277 : !===============================================================================
278 :
279 551020268 : logical function cam_physpkg_is(name)
280 :
281 : ! query for the name of the physics package
282 :
283 : character(len=*) :: name
284 :
285 551020268 : cam_physpkg_is = (trim(name) == trim(cam_physpkg))
286 551020268 : end function cam_physpkg_is
287 :
288 : !===============================================================================
289 :
290 191088 : logical function cam_chempkg_is(name)
291 :
292 : ! query for the name of the chemics package
293 :
294 : character(len=*) :: name
295 :
296 191088 : cam_chempkg_is = (trim(name) == trim(cam_chempkg))
297 191088 : end function cam_chempkg_is
298 :
299 : !===============================================================================
300 :
301 14682480 : logical function waccmx_is(name)
302 :
303 : ! query for the name of the waccmx run option
304 :
305 : character(len=*) :: name
306 :
307 14682480 : waccmx_is = (trim(name) == trim(waccmx_opt))
308 14682480 : end function waccmx_is
309 :
310 : !===============================================================================
311 :
312 0 : subroutine phys_getopts(deep_scheme_out, shallow_scheme_out, eddy_scheme_out, microp_scheme_out, &
313 0 : radiation_scheme_out, use_subcol_microp_out, atm_dep_flux_out, &
314 : history_amwg_out, history_vdiag_out, history_aerosol_out, history_aero_optics_out, history_eddy_out, &
315 : history_budget_out, history_budget_histfile_num_out, &
316 : history_waccm_out, history_waccmx_out, history_chemistry_out, &
317 : history_carma_out, history_carma_srf_flx_out, history_clubb_out, history_dust_out, &
318 : history_cesm_forcing_out, history_scwaccm_forcing_out, history_chemspecies_srf_out, &
319 0 : cam_chempkg_out, prog_modal_aero_out, macrop_scheme_out, &
320 : do_clubb_sgs_out, state_debug_checks_out, cld_macmic_num_steps_out, &
321 : offline_driver_out, convproc_do_aer_out, cam_snapshot_before_num_out, cam_snapshot_after_num_out,&
322 0 : cam_take_snapshot_before_out, cam_take_snapshot_after_out, physics_grid_out, do_hb_above_clubb_out)
323 : !-----------------------------------------------------------------------
324 : ! Purpose: Return runtime settings
325 : ! deep_scheme_out : deep convection scheme
326 : ! shallow_scheme_out: shallow convection scheme
327 : ! eddy_scheme_out : vertical diffusion scheme
328 : ! microp_scheme_out : microphysics scheme
329 : ! radiation_scheme_out : radiation_scheme
330 : !-----------------------------------------------------------------------
331 :
332 : character(len=16), intent(out), optional :: deep_scheme_out
333 : character(len=16), intent(out), optional :: shallow_scheme_out
334 : character(len=16), intent(out), optional :: eddy_scheme_out
335 : character(len=16), intent(out), optional :: microp_scheme_out
336 : character(len=16), intent(out), optional :: radiation_scheme_out
337 : character(len=16), intent(out), optional :: macrop_scheme_out
338 : logical, intent(out), optional :: use_subcol_microp_out
339 : logical, intent(out), optional :: atm_dep_flux_out
340 : logical, intent(out), optional :: history_amwg_out
341 : logical, intent(out), optional :: history_vdiag_out
342 : logical, intent(out), optional :: history_eddy_out
343 : logical, intent(out), optional :: history_aerosol_out
344 : logical, intent(out), optional :: history_aero_optics_out
345 : logical, intent(out), optional :: history_budget_out
346 : integer, intent(out), optional :: history_budget_histfile_num_out
347 : logical, intent(out), optional :: history_waccm_out
348 : logical, intent(out), optional :: history_waccmx_out
349 : logical, intent(out), optional :: history_chemistry_out
350 : logical, intent(out), optional :: history_carma_out
351 : logical, intent(out), optional :: history_carma_srf_flx_out
352 : logical, intent(out), optional :: history_clubb_out
353 : logical, intent(out), optional :: history_cesm_forcing_out
354 : logical, intent(out), optional :: history_chemspecies_srf_out
355 : logical, intent(out), optional :: history_dust_out
356 : logical, intent(out), optional :: history_scwaccm_forcing_out
357 : logical, intent(out), optional :: do_clubb_sgs_out
358 : character(len=32), intent(out), optional :: cam_chempkg_out
359 : logical, intent(out), optional :: prog_modal_aero_out
360 : logical, intent(out), optional :: state_debug_checks_out
361 : integer, intent(out), optional :: cld_macmic_num_steps_out
362 : logical, intent(out), optional :: offline_driver_out
363 : logical, intent(out), optional :: convproc_do_aer_out
364 : integer, intent(out), optional :: cam_snapshot_before_num_out
365 : integer, intent(out), optional :: cam_snapshot_after_num_out
366 : character(len=32), intent(out), optional :: cam_take_snapshot_before_out
367 : character(len=32), intent(out), optional :: cam_take_snapshot_after_out
368 : character(len=cl), intent(out), optional :: physics_grid_out
369 : logical, intent(out), optional :: do_hb_above_clubb_out
370 :
371 4219560 : if ( present(deep_scheme_out ) ) deep_scheme_out = deep_scheme
372 4219560 : if ( present(shallow_scheme_out ) ) shallow_scheme_out = shallow_scheme
373 4219560 : if ( present(eddy_scheme_out ) ) eddy_scheme_out = eddy_scheme
374 4219560 : if ( present(microp_scheme_out ) ) microp_scheme_out = microp_scheme
375 4219560 : if ( present(radiation_scheme_out ) ) radiation_scheme_out = radiation_scheme
376 4219560 : if ( present(use_subcol_microp_out ) ) use_subcol_microp_out = use_subcol_microp
377 :
378 4219560 : if ( present(macrop_scheme_out ) ) macrop_scheme_out = macrop_scheme
379 4219560 : if ( present(atm_dep_flux_out ) ) atm_dep_flux_out = atm_dep_flux
380 4219560 : if ( present(history_aerosol_out ) ) history_aerosol_out = history_aerosol
381 4219560 : if ( present(history_aero_optics_out ) ) history_aero_optics_out = history_aero_optics
382 4219560 : if ( present(history_budget_out ) ) history_budget_out = history_budget
383 4219560 : if ( present(history_amwg_out ) ) history_amwg_out = history_amwg
384 4219560 : if ( present(history_vdiag_out ) ) history_vdiag_out = history_vdiag
385 4219560 : if ( present(history_eddy_out ) ) history_eddy_out = history_eddy
386 4219560 : if ( present(history_budget_histfile_num_out ) ) history_budget_histfile_num_out = history_budget_histfile_num
387 4219560 : if ( present(history_waccm_out ) ) history_waccm_out = history_waccm
388 4219560 : if ( present(history_waccmx_out ) ) history_waccmx_out = history_waccmx
389 4219560 : if ( present(history_chemistry_out ) ) history_chemistry_out = history_chemistry
390 4219560 : if ( present(history_cesm_forcing_out) ) history_cesm_forcing_out = history_cesm_forcing
391 4219560 : if ( present(history_chemspecies_srf_out) ) history_chemspecies_srf_out = history_chemspecies_srf
392 4219560 : if ( present(history_scwaccm_forcing_out) ) history_scwaccm_forcing_out = history_scwaccm_forcing
393 4219560 : if ( present(history_carma_out ) ) history_carma_out = history_carma
394 4219560 : if ( present(history_carma_srf_flx_out) ) history_carma_srf_flx_out= history_carma_srf_flx
395 4219560 : if ( present(history_clubb_out ) ) history_clubb_out = history_clubb
396 4219560 : if ( present(history_dust_out ) ) history_dust_out = history_dust
397 4219560 : if ( present(do_clubb_sgs_out ) ) do_clubb_sgs_out = do_clubb_sgs
398 4219560 : if ( present(cam_chempkg_out ) ) cam_chempkg_out = cam_chempkg
399 4219560 : if ( present(prog_modal_aero_out ) ) prog_modal_aero_out = prog_modal_aero
400 4219560 : if ( present(state_debug_checks_out ) ) state_debug_checks_out = state_debug_checks
401 4219560 : if ( present(cld_macmic_num_steps_out) ) cld_macmic_num_steps_out = cld_macmic_num_steps
402 4219560 : if ( present(offline_driver_out ) ) offline_driver_out = offline_driver
403 4219560 : if ( present(convproc_do_aer_out ) ) convproc_do_aer_out = convproc_do_aer
404 4219560 : if ( present(cam_snapshot_before_num_out ) ) cam_snapshot_before_num_out = cam_snapshot_before_num
405 4219560 : if ( present(cam_snapshot_after_num_out ) ) cam_snapshot_after_num_out = cam_snapshot_after_num
406 4219560 : if ( present(cam_take_snapshot_before_out) ) cam_take_snapshot_before_out = cam_take_snapshot_before
407 4219560 : if ( present(cam_take_snapshot_after_out ) ) cam_take_snapshot_after_out = cam_take_snapshot_after
408 4219560 : if ( present(physics_grid_out ) ) physics_grid_out = cam_physics_mesh
409 4219560 : if ( present(do_hb_above_clubb_out ) ) do_hb_above_clubb_out = do_hb_above_clubb
410 :
411 4219560 : end subroutine phys_getopts
412 :
413 : !===============================================================================
414 :
415 0 : subroutine phys_setopts(fv_am_correction_in)
416 :
417 : logical, intent(in), optional :: fv_am_correction_in
418 :
419 0 : if ( present(fv_am_correction_in) ) fv_am_correction = fv_am_correction_in
420 :
421 4219560 : end subroutine phys_setopts
422 :
423 : !===============================================================================
424 :
425 2304 : function phys_deepconv_pbl()
426 :
427 : logical phys_deepconv_pbl
428 :
429 : ! Don't allow deep convection in PBL if running UW PBL scheme
430 2304 : if ( (eddy_scheme .eq. 'diag_TKE' ) .or. (shallow_scheme .eq. 'UW' ) ) then
431 : phys_deepconv_pbl = .true.
432 : else
433 2304 : phys_deepconv_pbl = .false.
434 : endif
435 :
436 : return
437 :
438 : end function phys_deepconv_pbl
439 :
440 : !===============================================================================
441 :
442 116664 : function phys_do_flux_avg()
443 :
444 : logical :: phys_do_flux_avg
445 : !----------------------------------------------------------------------
446 :
447 116664 : phys_do_flux_avg = .false.
448 116664 : if (srf_flux_avg == 1) phys_do_flux_avg = .true.
449 :
450 116664 : end function phys_do_flux_avg
451 :
452 : !===============================================================================
453 : end module phys_control
|