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_clubb = .true. ! output default CLUBB-related variables
69 : logical :: history_cesm_forcing = .false.
70 : logical :: history_dust = .false.
71 : logical :: history_scwaccm_forcing = .false.
72 : logical :: history_chemspecies_srf = .false.
73 :
74 : logical :: do_clubb_sgs
75 : logical :: do_hb_above_clubb = .false. ! enable HB vertical mixing above clubb top
76 :
77 : ! Check validity of physics_state objects in physics_update.
78 : logical :: state_debug_checks = .false.
79 :
80 : ! Macro/micro-physics co-substeps
81 : integer :: cld_macmic_num_steps = 1
82 :
83 : logical :: offline_driver = .false. ! true => offline driver is being used
84 :
85 :
86 : logical, public, protected :: use_simple_phys = .false. ! true => simple physics configuration
87 :
88 : logical :: use_spcam ! true => use super parameterized CAM
89 :
90 : logical :: prog_modal_aero ! determines whether prognostic modal aerosols are present in the run.
91 :
92 : ! Option to use heterogeneous freezing
93 : logical, public, protected :: use_hetfrz_classnuc = .false.
94 :
95 : ! Which gravity wave sources are used?
96 : logical, public, protected :: use_gw_oro = .true. ! Orography.
97 : logical, public, protected :: use_gw_front = .false. ! Frontogenesis.
98 : logical, public, protected :: use_gw_front_igw = .false. ! Frontogenesis to inertial spectrum.
99 : logical, public, protected :: use_gw_convect_dp = .false. ! Deep convection.
100 : logical, public, protected :: use_gw_convect_sh = .false. ! Shallow convection.
101 : logical, public, protected :: use_gw_movmtn_pbl = .false. ! moving mountain
102 :
103 : ! FV dycore angular momentum correction
104 : logical, public, protected :: fv_am_correction = .false.
105 :
106 : ! Option for Harmonized Emissions Component (HEMCO)
107 : logical, public, protected :: use_hemco = .false.
108 :
109 : ! CAM snapshot before/after file numbers and control
110 : character(len=32) :: cam_take_snapshot_before = '' ! Physics routine to take a snopshot "before"
111 : character(len=32) :: cam_take_snapshot_after = '' ! Physics routine to take a snopshot "after"
112 : integer :: cam_snapshot_before_num = -1 ! output history file number for CAM "before" snapshot
113 : integer :: cam_snapshot_after_num = -1 ! output history file number for CAM "after" snapshot
114 :
115 : !=======================================================================
116 : contains
117 : !=======================================================================
118 :
119 1536 : subroutine phys_ctl_readnl(nlfile)
120 :
121 : use namelist_utils, only: find_group_name
122 : use units, only: getunit, freeunit
123 : use spmd_utils, only: mpi_character, mpi_integer, mpi_logical, masterprocid, mpicom
124 : use cam_control_mod, only: cam_ctrl_set_physics_type
125 :
126 : character(len=*), intent(in) :: nlfile ! filepath for file containing namelist input
127 :
128 : ! Local variables
129 : integer :: unitn, ierr
130 : character(len=*), parameter :: subname = 'phys_ctl_readnl'
131 :
132 : namelist /phys_ctl_nl/ cam_physpkg, use_simple_phys, cam_chempkg, waccmx_opt, &
133 : deep_scheme, shallow_scheme, &
134 : eddy_scheme, microp_scheme, macrop_scheme, radiation_scheme, srf_flux_avg, &
135 : use_subcol_microp, atm_dep_flux, history_amwg, history_vdiag, history_aerosol, history_aero_optics, &
136 : history_eddy, history_budget, history_budget_histfile_num, history_waccm, &
137 : history_waccmx, history_chemistry, history_carma, 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 1536 : if (masterproc) then
146 2 : unitn = getunit()
147 2 : open( unitn, file=trim(nlfile), status='old' )
148 2 : call find_group_name(unitn, 'phys_ctl_nl', status=ierr)
149 2 : if (ierr == 0) then
150 2 : read(unitn, phys_ctl_nl, iostat=ierr)
151 2 : if (ierr /= 0) then
152 0 : call endrun(subname // ':: ERROR reading namelist')
153 : end if
154 : end if
155 2 : close(unitn)
156 2 : call freeunit(unitn)
157 : end if
158 :
159 : ! Broadcast namelist variables
160 1536 : call mpi_bcast(deep_scheme, len(deep_scheme), mpi_character, masterprocid, mpicom, ierr)
161 1536 : call mpi_bcast(cam_physpkg, len(cam_physpkg), mpi_character, masterprocid, mpicom, ierr)
162 1536 : call mpi_bcast(use_simple_phys, 1, mpi_logical, masterprocid, mpicom, ierr)
163 1536 : call mpi_bcast(cam_chempkg, len(cam_chempkg), mpi_character, masterprocid, mpicom, ierr)
164 1536 : call mpi_bcast(waccmx_opt, len(waccmx_opt), mpi_character, masterprocid, mpicom, ierr)
165 1536 : call mpi_bcast(shallow_scheme, len(shallow_scheme), mpi_character, masterprocid, mpicom, ierr)
166 1536 : call mpi_bcast(eddy_scheme, len(eddy_scheme), mpi_character, masterprocid, mpicom, ierr)
167 1536 : call mpi_bcast(microp_scheme, len(microp_scheme), mpi_character, masterprocid, mpicom, ierr)
168 1536 : call mpi_bcast(radiation_scheme, len(radiation_scheme), mpi_character, masterprocid, mpicom, ierr)
169 1536 : call mpi_bcast(macrop_scheme, len(macrop_scheme), mpi_character, masterprocid, mpicom, ierr)
170 1536 : call mpi_bcast(srf_flux_avg, 1, mpi_integer, masterprocid, mpicom, ierr)
171 1536 : call mpi_bcast(use_subcol_microp, 1, mpi_logical, masterprocid, mpicom, ierr)
172 1536 : call mpi_bcast(atm_dep_flux, 1, mpi_logical, masterprocid, mpicom, ierr)
173 1536 : call mpi_bcast(history_amwg, 1, mpi_logical, masterprocid, mpicom, ierr)
174 1536 : call mpi_bcast(history_vdiag, 1, mpi_logical, masterprocid, mpicom, ierr)
175 1536 : call mpi_bcast(history_eddy, 1, mpi_logical, masterprocid, mpicom, ierr)
176 1536 : call mpi_bcast(history_aerosol, 1, mpi_logical, masterprocid, mpicom, ierr)
177 1536 : call mpi_bcast(history_aero_optics, 1, mpi_logical, masterprocid, mpicom, ierr)
178 1536 : call mpi_bcast(history_budget, 1, mpi_logical, masterprocid, mpicom, ierr)
179 1536 : call mpi_bcast(history_budget_histfile_num, 1, mpi_integer, masterprocid, mpicom, ierr)
180 1536 : call mpi_bcast(history_waccm, 1, mpi_logical, masterprocid, mpicom, ierr)
181 1536 : call mpi_bcast(history_waccmx, 1, mpi_logical, masterprocid, mpicom, ierr)
182 1536 : call mpi_bcast(history_chemistry, 1, mpi_logical, masterprocid, mpicom, ierr)
183 1536 : call mpi_bcast(history_carma, 1, mpi_logical, masterprocid, mpicom, ierr)
184 1536 : call mpi_bcast(history_clubb, 1, mpi_logical, masterprocid, mpicom, ierr)
185 1536 : call mpi_bcast(history_cesm_forcing, 1, mpi_logical, masterprocid, mpicom, ierr)
186 1536 : call mpi_bcast(history_chemspecies_srf, 1, mpi_logical, masterprocid, mpicom, ierr)
187 1536 : call mpi_bcast(history_dust, 1, mpi_logical, masterprocid, mpicom, ierr)
188 1536 : call mpi_bcast(history_scwaccm_forcing, 1, mpi_logical, masterprocid, mpicom, ierr)
189 1536 : call mpi_bcast(do_clubb_sgs, 1, mpi_logical, masterprocid, mpicom, ierr)
190 1536 : call mpi_bcast(state_debug_checks, 1, mpi_logical, masterprocid, mpicom, ierr)
191 1536 : call mpi_bcast(use_hetfrz_classnuc, 1, mpi_logical, masterprocid, mpicom, ierr)
192 1536 : call mpi_bcast(use_gw_oro, 1, mpi_logical, masterprocid, mpicom, ierr)
193 1536 : call mpi_bcast(use_gw_front, 1, mpi_logical, masterprocid, mpicom, ierr)
194 1536 : call mpi_bcast(use_gw_front_igw, 1, mpi_logical, masterprocid, mpicom, ierr)
195 1536 : call mpi_bcast(use_gw_convect_dp, 1, mpi_logical, masterprocid, mpicom, ierr)
196 1536 : call mpi_bcast(use_gw_convect_sh, 1, mpi_logical, masterprocid, mpicom, ierr)
197 1536 : call mpi_bcast(use_gw_movmtn_pbl, 1, mpi_logical, masterprocid, mpicom, ierr)
198 1536 : call mpi_bcast(cld_macmic_num_steps, 1, mpi_integer, masterprocid, mpicom, ierr)
199 1536 : call mpi_bcast(offline_driver, 1, mpi_logical, masterprocid, mpicom, ierr)
200 1536 : call mpi_bcast(convproc_do_aer, 1, mpi_logical, masterprocid, mpicom, ierr)
201 1536 : call mpi_bcast(cam_snapshot_before_num, 1, mpi_integer, masterprocid, mpicom, ierr)
202 1536 : call mpi_bcast(cam_snapshot_after_num, 1, mpi_integer, masterprocid, mpicom, ierr)
203 1536 : call mpi_bcast(cam_take_snapshot_before, len(cam_take_snapshot_before), mpi_character, masterprocid, mpicom, ierr)
204 1536 : call mpi_bcast(cam_take_snapshot_after, len(cam_take_snapshot_after), mpi_character, masterprocid, mpicom, ierr)
205 1536 : call mpi_bcast(cam_physics_mesh, len(cam_physics_mesh), mpi_character, masterprocid, mpicom, ierr)
206 1536 : call mpi_bcast(do_hb_above_clubb, 1, mpi_logical, masterprocid, mpicom, ierr)
207 1536 : call mpi_bcast(use_hemco, 1, mpi_logical, masterprocid, mpicom, ierr)
208 :
209 : use_spcam = ( cam_physpkg_is('spcam_sam1mom') &
210 1536 : .or. cam_physpkg_is('spcam_m2005'))
211 :
212 1536 : call cam_ctrl_set_physics_type(cam_physpkg)
213 :
214 : ! Error checking:
215 :
216 : ! Check compatibility of eddy & shallow schemes
217 1536 : if (( shallow_scheme .eq. 'UW' ) .and. ( eddy_scheme .ne. 'diag_TKE' )) then
218 0 : write(iulog,*)'Do you really want to run UW shallow scheme without diagnostic TKE eddy scheme? Quiting'
219 0 : call endrun('shallow convection and eddy scheme may be incompatible')
220 : endif
221 :
222 1536 : if (( shallow_scheme .eq. 'Hack' ) .and. ( ( eddy_scheme .ne. 'HB' ) .and. ( eddy_scheme .ne. 'HBR' ))) then
223 0 : write(iulog,*)'Do you really want to run Hack shallow scheme with a non-standard eddy scheme? Quiting.'
224 0 : call endrun('shallow convection and eddy scheme may be incompatible')
225 : endif
226 :
227 : ! Check compatibility of PBL and Microphysics schemes
228 1536 : if (( eddy_scheme .eq. 'diag_TKE' ) .and. ( microp_scheme .eq. 'RK' )) then
229 0 : write(iulog,*)'UW PBL is not compatible with RK microphysics. Quiting'
230 0 : call endrun('PBL and Microphysics schemes incompatible')
231 : endif
232 :
233 : ! Add a check to make sure CLUBB and MG are used together
234 1536 : if ( do_clubb_sgs .and. ( microp_scheme .ne. 'MG') .and. .not. use_spcam) then
235 0 : write(iulog,*)'CLUBB is only compatible with MG microphysics. Quiting'
236 0 : call endrun('CLUBB and microphysics schemes incompatible')
237 : endif
238 :
239 : ! Check that eddy_scheme, macrop_scheme, shallow_scheme are all set to CLUBB_SGS if do_clubb_sgs is true
240 1536 : if (do_clubb_sgs .and. .not. use_spcam) then
241 0 : if (eddy_scheme .ne. 'CLUBB_SGS' .or. macrop_scheme .ne. 'CLUBB_SGS' .or. shallow_scheme .ne. 'CLUBB_SGS') then
242 0 : write(iulog,*)'eddy_scheme, macrop_scheme and shallow_scheme must all be CLUBB_SGS. Quiting'
243 0 : call endrun('CLUBB and eddy, macrop or shallow schemes incompatible')
244 : endif
245 : endif
246 :
247 1536 : if (cam_physpkg_is("cam7")) then
248 : ! Check that eddy_scheme, macrop_scheme, shallow_scheme are all set to CLUBB
249 0 : if (eddy_scheme /= 'CLUBB_SGS' .or. macrop_scheme /= 'CLUBB_SGS' .or. shallow_scheme /= 'CLUBB_SGS') then
250 0 : write(iulog,*) 'cam7 is only compatible with CLUBB. Quitting'
251 0 : call endrun('cam7 is only compatible with eddy, macrop, and shallow schemes = CLUBB_SGS')
252 : end if
253 : ! Add a check to make sure SPCAM is not used
254 0 : if (use_spcam) then
255 0 : write(iulog,*)'SPCAM not compatible with cam7 physics. Quitting'
256 0 : call endrun('SPCAM and cam7 incompatible')
257 : end if
258 : ! Add check to make sure we are not trying to use `camrt`
259 0 : if (trim(radiation_scheme) == 'camrt') then
260 0 : write(iulog,*) ' camrt specified and it is not compatible with cam7'
261 0 : call endrun('cam7 is not compatible with camrt radiation scheme')
262 : end if
263 : end if
264 :
265 : ! do_hb_above_clubb requires that CLUBB is being used
266 1536 : if (do_hb_above_clubb .and. .not. do_clubb_sgs) then
267 0 : write(iulog,*)'do_hb_above_clubb requires CLUBB to be active'
268 0 : call endrun('do_hb_above_clubb incompatible with do_clubb_sgs = .false.')
269 : endif
270 :
271 : ! Macro/micro co-substepping support.
272 1536 : if (cld_macmic_num_steps > 1) then
273 0 : if (microp_scheme /= "MG" .or. (macrop_scheme /= "park" .and. macrop_scheme /= "CLUBB_SGS")) then
274 : call endrun ("Setting cld_macmic_num_steps > 1 is only &
275 0 : &supported with Park or CLUBB macrophysics and MG microphysics.")
276 : end if
277 : end if
278 :
279 : ! prog_modal_aero determines whether prognostic modal aerosols are present in the run.
280 1536 : prog_modal_aero = index(cam_chempkg,'_mam')>0
281 :
282 1536 : end subroutine phys_ctl_readnl
283 :
284 : !===============================================================================
285 :
286 4608 : logical function cam_physpkg_is(name)
287 :
288 : ! query for the name of the physics package
289 :
290 : character(len=*) :: name
291 :
292 4608 : cam_physpkg_is = (trim(name) == trim(cam_physpkg))
293 4608 : end function cam_physpkg_is
294 :
295 : !===============================================================================
296 :
297 0 : logical function cam_chempkg_is(name)
298 :
299 : ! query for the name of the chemics package
300 :
301 : character(len=*) :: name
302 :
303 0 : cam_chempkg_is = (trim(name) == trim(cam_chempkg))
304 0 : end function cam_chempkg_is
305 :
306 : !===============================================================================
307 :
308 107946048 : logical function waccmx_is(name)
309 :
310 : ! query for the name of the waccmx run option
311 :
312 : character(len=*) :: name
313 :
314 107946048 : waccmx_is = (trim(name) == trim(waccmx_opt))
315 107946048 : end function waccmx_is
316 :
317 : !===============================================================================
318 :
319 0 : subroutine phys_getopts(deep_scheme_out, shallow_scheme_out, eddy_scheme_out, microp_scheme_out, &
320 0 : radiation_scheme_out, use_subcol_microp_out, atm_dep_flux_out, &
321 : history_amwg_out, history_vdiag_out, history_aerosol_out, history_aero_optics_out, history_eddy_out, &
322 : history_budget_out, history_budget_histfile_num_out, &
323 : history_waccm_out, history_waccmx_out, history_chemistry_out, &
324 : history_carma_out, history_clubb_out, history_dust_out, &
325 : history_cesm_forcing_out, history_scwaccm_forcing_out, history_chemspecies_srf_out, &
326 0 : cam_chempkg_out, prog_modal_aero_out, macrop_scheme_out, &
327 : do_clubb_sgs_out, use_spcam_out, state_debug_checks_out, cld_macmic_num_steps_out, &
328 : offline_driver_out, convproc_do_aer_out, cam_snapshot_before_num_out, cam_snapshot_after_num_out,&
329 0 : cam_take_snapshot_before_out, cam_take_snapshot_after_out, physics_grid_out, do_hb_above_clubb_out)
330 : !-----------------------------------------------------------------------
331 : ! Purpose: Return runtime settings
332 : ! deep_scheme_out : deep convection scheme
333 : ! shallow_scheme_out: shallow convection scheme
334 : ! eddy_scheme_out : vertical diffusion scheme
335 : ! microp_scheme_out : microphysics scheme
336 : ! radiation_scheme_out : radiation_scheme
337 : ! SPCAM_microp_scheme_out : SPCAM microphysics scheme
338 : !-----------------------------------------------------------------------
339 :
340 : character(len=16), intent(out), optional :: deep_scheme_out
341 : character(len=16), intent(out), optional :: shallow_scheme_out
342 : character(len=16), intent(out), optional :: eddy_scheme_out
343 : character(len=16), intent(out), optional :: microp_scheme_out
344 : character(len=16), intent(out), optional :: radiation_scheme_out
345 : character(len=16), intent(out), optional :: macrop_scheme_out
346 : logical, intent(out), optional :: use_subcol_microp_out
347 : logical, intent(out), optional :: use_spcam_out
348 : logical, intent(out), optional :: atm_dep_flux_out
349 : logical, intent(out), optional :: history_amwg_out
350 : logical, intent(out), optional :: history_vdiag_out
351 : logical, intent(out), optional :: history_eddy_out
352 : logical, intent(out), optional :: history_aerosol_out
353 : logical, intent(out), optional :: history_aero_optics_out
354 : logical, intent(out), optional :: history_budget_out
355 : integer, intent(out), optional :: history_budget_histfile_num_out
356 : logical, intent(out), optional :: history_waccm_out
357 : logical, intent(out), optional :: history_waccmx_out
358 : logical, intent(out), optional :: history_chemistry_out
359 : logical, intent(out), optional :: history_carma_out
360 : logical, intent(out), optional :: history_clubb_out
361 : logical, intent(out), optional :: history_cesm_forcing_out
362 : logical, intent(out), optional :: history_chemspecies_srf_out
363 : logical, intent(out), optional :: history_dust_out
364 : logical, intent(out), optional :: history_scwaccm_forcing_out
365 : logical, intent(out), optional :: do_clubb_sgs_out
366 : character(len=32), intent(out), optional :: cam_chempkg_out
367 : logical, intent(out), optional :: prog_modal_aero_out
368 : logical, intent(out), optional :: state_debug_checks_out
369 : integer, intent(out), optional :: cld_macmic_num_steps_out
370 : logical, intent(out), optional :: offline_driver_out
371 : logical, intent(out), optional :: convproc_do_aer_out
372 : integer, intent(out), optional :: cam_snapshot_before_num_out
373 : integer, intent(out), optional :: cam_snapshot_after_num_out
374 : character(len=32), intent(out), optional :: cam_take_snapshot_before_out
375 : character(len=32), intent(out), optional :: cam_take_snapshot_after_out
376 : character(len=cl), intent(out), optional :: physics_grid_out
377 : logical, intent(out), optional :: do_hb_above_clubb_out
378 :
379 30424056 : if ( present(deep_scheme_out ) ) deep_scheme_out = deep_scheme
380 30424056 : if ( present(shallow_scheme_out ) ) shallow_scheme_out = shallow_scheme
381 30424056 : if ( present(eddy_scheme_out ) ) eddy_scheme_out = eddy_scheme
382 30424056 : if ( present(microp_scheme_out ) ) microp_scheme_out = microp_scheme
383 30424056 : if ( present(radiation_scheme_out ) ) radiation_scheme_out = radiation_scheme
384 30424056 : if ( present(use_subcol_microp_out ) ) use_subcol_microp_out = use_subcol_microp
385 30424056 : if ( present(use_spcam_out ) ) use_spcam_out = use_spcam
386 :
387 30424056 : if ( present(macrop_scheme_out ) ) macrop_scheme_out = macrop_scheme
388 30424056 : if ( present(atm_dep_flux_out ) ) atm_dep_flux_out = atm_dep_flux
389 30424056 : if ( present(history_aerosol_out ) ) history_aerosol_out = history_aerosol
390 30424056 : if ( present(history_aero_optics_out ) ) history_aero_optics_out = history_aero_optics
391 30424056 : if ( present(history_budget_out ) ) history_budget_out = history_budget
392 30424056 : if ( present(history_amwg_out ) ) history_amwg_out = history_amwg
393 30424056 : if ( present(history_vdiag_out ) ) history_vdiag_out = history_vdiag
394 30424056 : if ( present(history_eddy_out ) ) history_eddy_out = history_eddy
395 30424056 : if ( present(history_budget_histfile_num_out ) ) history_budget_histfile_num_out = history_budget_histfile_num
396 30424056 : if ( present(history_waccm_out ) ) history_waccm_out = history_waccm
397 30424056 : if ( present(history_waccmx_out ) ) history_waccmx_out = history_waccmx
398 30424056 : if ( present(history_chemistry_out ) ) history_chemistry_out = history_chemistry
399 30424056 : if ( present(history_cesm_forcing_out) ) history_cesm_forcing_out = history_cesm_forcing
400 30424056 : if ( present(history_chemspecies_srf_out) ) history_chemspecies_srf_out = history_chemspecies_srf
401 30424056 : if ( present(history_scwaccm_forcing_out) ) history_scwaccm_forcing_out = history_scwaccm_forcing
402 30424056 : if ( present(history_carma_out ) ) history_carma_out = history_carma
403 30424056 : if ( present(history_clubb_out ) ) history_clubb_out = history_clubb
404 30424056 : if ( present(history_dust_out ) ) history_dust_out = history_dust
405 30424056 : if ( present(do_clubb_sgs_out ) ) do_clubb_sgs_out = do_clubb_sgs
406 30424056 : if ( present(cam_chempkg_out ) ) cam_chempkg_out = cam_chempkg
407 30424056 : if ( present(prog_modal_aero_out ) ) prog_modal_aero_out = prog_modal_aero
408 30424056 : if ( present(state_debug_checks_out ) ) state_debug_checks_out = state_debug_checks
409 30424056 : if ( present(cld_macmic_num_steps_out) ) cld_macmic_num_steps_out = cld_macmic_num_steps
410 30424056 : if ( present(offline_driver_out ) ) offline_driver_out = offline_driver
411 30424056 : if ( present(convproc_do_aer_out ) ) convproc_do_aer_out = convproc_do_aer
412 30424056 : if ( present(cam_snapshot_before_num_out ) ) cam_snapshot_before_num_out = cam_snapshot_before_num
413 30424056 : if ( present(cam_snapshot_after_num_out ) ) cam_snapshot_after_num_out = cam_snapshot_after_num
414 30424056 : if ( present(cam_take_snapshot_before_out) ) cam_take_snapshot_before_out = cam_take_snapshot_before
415 30424056 : if ( present(cam_take_snapshot_after_out ) ) cam_take_snapshot_after_out = cam_take_snapshot_after
416 30424056 : if ( present(physics_grid_out ) ) physics_grid_out = cam_physics_mesh
417 30424056 : if ( present(do_hb_above_clubb_out ) ) do_hb_above_clubb_out = do_hb_above_clubb
418 :
419 30424056 : end subroutine phys_getopts
420 :
421 : !===============================================================================
422 :
423 0 : subroutine phys_setopts(fv_am_correction_in)
424 :
425 : logical, intent(in), optional :: fv_am_correction_in
426 :
427 0 : if ( present(fv_am_correction_in) ) fv_am_correction = fv_am_correction_in
428 :
429 30424056 : end subroutine phys_setopts
430 :
431 : !===============================================================================
432 :
433 1536 : function phys_deepconv_pbl()
434 :
435 : logical phys_deepconv_pbl
436 :
437 : ! Don't allow deep convection in PBL if running UW PBL scheme
438 1536 : if ( (eddy_scheme .eq. 'diag_TKE' ) .or. (shallow_scheme .eq. 'UW' ) ) then
439 : phys_deepconv_pbl = .true.
440 : else
441 1536 : phys_deepconv_pbl = .false.
442 : endif
443 :
444 : return
445 :
446 : end function phys_deepconv_pbl
447 :
448 : !===============================================================================
449 :
450 1861656 : function phys_do_flux_avg()
451 :
452 : logical :: phys_do_flux_avg
453 : !----------------------------------------------------------------------
454 :
455 1861656 : phys_do_flux_avg = .false.
456 1861656 : if (srf_flux_avg == 1) phys_do_flux_avg = .true.
457 :
458 1861656 : end function phys_do_flux_avg
459 :
460 : !===============================================================================
461 : end module phys_control
|