runtime_opts.F90 coverage: 100.00 %func 82.01 %block
1) module runtime_opts
2)
3) !-----------------------------------------------------------------------
4) !
5) ! Purpose: This module is responsible for reading CAM namelist cam_inparm
6) ! and broadcasting namelist values if needed.
7) !
8) ! Author:
9) ! Original routines: CMS
10) ! Module: T. Henderson, September 2003
11) !
12) !-----------------------------------------------------------------------
13)
14) !-----------------------------------------------------------------------
15) !- use statements ------------------------------------------------------
16) !-----------------------------------------------------------------------
17) use shr_kind_mod, only: r8 => shr_kind_r8, SHR_KIND_CL
18) use spmd_utils, only: masterproc
19) use namelist_utils, only: find_group_name
20) use pmgrid, only: plon
21) use cam_instance, only: inst_suffix
22) use cam_history
23) use cam_control_mod
24) use cam_logfile, only: iulog
25) use pspect
26) use units
27) use constituents, only: pcnst, readtrace
28) use tracers, only: tracers_flag
29) use time_manager, only: dtime
30) use filenames, only: ncdata, bnd_topo, &
31) caseid, &
32) brnch_retain_casename
33) use dycore, only: dycore_is
34) use cam_abortutils, only: endrun
35) use rayleigh_friction, only: rayk0, raykrange, raytau0
36)
37) !-----------------------------------------------------------------------
38) !- module boilerplate --------------------------------------------------
39) !-----------------------------------------------------------------------
40) implicit none
41) private
42) save
43)
44)
45) !-----------------------------------------------------------------------
46) ! Public interfaces ----------------------------------------------------
47) !-----------------------------------------------------------------------
48) public read_namelist ! Set and/or get all runtime options
49)
50) !-----------------------------------------------------------------------
51) ! Private data ---------------------------------------------------------
52) !-----------------------------------------------------------------------
53)
54) character(len=SHR_KIND_CL), private :: nlfilename = 'atm_in' ! Namelist filename
55)
56) !-----------------------------------------------------------------------
57) !
58) ! SOMEWHAT ALPHABETICAL listing of variables in the cam_inparm namelist:
59) !
60) ! variable description
61) ! -------- -----------------
62) !
63) ! bnd_topo Path and filename of topography dataset
64) !
65) ! dtime = nnnn, Model time step in seconds. Default is dycore dependent.
66) !
67) ! nlvdry = nn, Number of layers over which to do dry
68) ! adjustment. Defaults to 3.
69) !
70) ! cam_branch_file Filepath of restart file to branch from (nsrest=3)
71) ! Full pathname required.
72) character(len=256) :: cam_branch_file = ' '
73) !
74)
75) !------------------------------------------------------------------
76) ! The following 3 are specific to Rayleigh friction
77) ! integer rayk0 vertical level at which rayleigh friction term is centered
78) ! real(r8) raykrange range of rayleigh friction profile; if 0, range is set automatically
79) ! real(r8) raytau0 approximate value of decay time at model top (days);
80) ! if 0., no rayleigh friction is applied
81) !------------------------------------------------------------------
82) !
83) !
84) ! pertlim = n.n Max size of perturbation to apply to initial
85) ! temperature field.
86) !
87) ! new_random logical: if .true., use RNG in dynamics/se/random_xgc.F90
88) ! instead of the fortran intrinsic.
89) !
90) ! seed_custom integer: if > 0, use new seeding mechanism that uses a
91) ! custom seed rather than a custom limit. Default 0
92) !
93) ! seed_clock logical: if .true., XOR the system_clock with the seed,
94) ! wheter it includes a custom seed or not. Default .false.
95) !
96) ! phys_chnk_fdim Declared first dimension for physics variables (chunks).
97) ! If <= 0, then value calculated based on problem specifics.
98) ! See phys_grid module.
99) integer :: phys_chnk_fdim
100) !
101) ! phys_chnk_fdim_max Upper bound on declared first dimension for physics
102) ! variables (chunks), for when phys_chnk_fdim <= 0.
103) ! See phys_grid module.
104) integer :: phys_chnk_fdim_max
105) !
106) ! phys_chnk_fdim_mult Restriction on declared first dimension for physics
107) ! variables (chunks) to be a multiple of this value,
108) ! for when phys_chnk_fdim <= 0. See phys_grid module.
109) integer :: phys_chnk_fdim_mult
110) !
111) ! phys_alltoall Dynamics/physics transpose option. See phys_grid module.
112) !
113) integer :: phys_alltoall
114) !
115) ! phys_loadbalance Load balance option for performance tuning of
116) ! physics chunks. See phys_grid module.
117) integer :: phys_loadbalance
118) !
119) ! phys_twin_algorithm Load balance option for performance tuning of
120) ! physics chunks. See phys_grid module.
121) integer :: phys_twin_algorithm
122) !
123) ! phys_chnk_per_thd Performance tuning option for physics chunks. See
124) ! phys_grid module.
125) integer :: phys_chnk_per_thd
126) !
127) ! phys_chnk_cost_write Output option for evaluating physics chunk load balance. See
128) ! phys_grid module.
129) logical :: phys_chnk_cost_write
130) !
131) ! tracers_flag = .F. If true, implement tracer test code. Number of tracers determined
132) ! in tracers_suite.F90 must agree with PCNST
133) !
134) ! readtrace = .T. If true, tracer initial conditions obtained from
135) ! initial file.
136) !
137) ! print_step_cost true => print per timestep cost info
138) !
139) !
140) ! logical indirect
141) ! ! true => include indirect radiative effects of
142) ! ! sulfate aerosols. Default is false.
143) !
144) !
145) ! met_data_file name of file that contains the offline meteorology data
146) ! met_data_path name of directory that contains the offline meteorology data
147) !
148) ! met_filenames_list name of file that contains names of the offline
149) ! meteorology data files
150) !
151) ! met_remove_file true => the offline meteorology file will be removed
152) !
153) ! met_cell_wall_winds true => the offline meteorology winds are defined on the model
154) ! grid cell walls
155) ! Physics buffer
156) logical :: pbuf_global_allocate ! allocate all buffers as global (default: .true.)
157)
158)
159) ! Conservation checks
160)
161) logical :: print_energy_errors ! switch for diagnostic output from check_energy module
162)
163) ! SCM Options
164) logical :: single_column
165) real(r8) :: scmlat,scmlon
166) real(r8) :: iop_nudge_tq_low
167) real(r8) :: iop_nudge_tq_high
168) real(r8) :: iop_nudge_tscale
169) real(r8) :: iop_perturb_high
170) integer, parameter :: max_chars = 128
171) character(len=max_chars) iopfile
172) logical :: scm_iop_srf_prop
173) logical :: iop_dosubsidence
174) logical :: iop_coriolis
175) logical :: iop_nudge_tq
176) logical :: iop_nudge_uv
177) logical :: scm_diurnal_avg
178) logical :: scm_observed_aero
179) logical :: precip_off
180) logical :: scm_multcols
181) logical :: dp_crm
182) logical :: scm_zero_non_iop_tracers
183)
184) contains
185)
186) !=======================================================================
187)
188) subroutine read_namelist(single_column_in, scmlon_in, scmlat_in, scm_multcols_in,&
189) nlfilename_in )
190)
191) !-----------------------------------------------------------------------
192) !
193) ! Purpose:
194) ! Read data from namelist cam_inparm to define the run. Process some of the
195) ! namelist variables to determine history and restart/branch file path
196) ! names. Check input namelist variables for validity and print them
197) ! to standard output.
198) !
199) ! Method:
200) ! Important Note for running on SUN systems: "implicit automatic (a-z)"
201) ! will not work because namelist data must be static.
202) !
203) ! Author:
204) ! Original version: CCM1
205) ! Standardized: L. Bath, June 1992
206) ! T. Acker, March 1996
207) !
208) !-----------------------------------------------------------------------
209)
210) ! Note that the following interfaces are prototypes proposed by Henderson
211) ! and Eaton. They minimize coupling with other modules. Design of these
212) ! interfaces should be refined via review by other CAM developers.
213) ! Interface *_defaultopts() gets default values from the responsible
214) ! module (Expert) prior to namelist read.
215) ! Interface *_setopts() sends values to the responsible module (Expert)
216) ! after namelist read. Erroneous values are handled by Experts.
217) ! TBH 9/8/03
218) !
219) use phys_grid, only: phys_grid_defaultopts, phys_grid_setopts
220)
221) use chem_surfvals, only: chem_surfvals_readnl
222) use check_energy, only: check_energy_defaultopts, check_energy_setopts
223) use cam_restart, only: restart_defaultopts, restart_setopts, restart_printopts
224) use co2_cycle, only: co2_cycle_readnl
225) use shr_string_mod, only: shr_string_toUpper
226) use iop_data_mod, only: iop_setopts,iop_default_opts
227)
228) ! Some modules read their own namelist input.
229) use spmd_utils, only: spmd_utils_readnl
230) use physconst, only: physconst_readnl
231) use phys_control, only: phys_ctl_readnl
232) use wv_saturation, only: wv_sat_readnl
233) use ref_pres, only: ref_pres_readnl
234) use cam3_aero_data, only: cam3_aero_data_readnl
235) use cam3_ozone_data, only: cam3_ozone_data_readnl
236) use macrop_driver, only: macrop_driver_readnl
237) use microp_driver, only: microp_driver_readnl
238) use microp_aero, only: microp_aero_readnl
239) use subcol, only: subcol_readnl
240) use cloud_fraction, only: cldfrc_readnl
241) use cldfrc2m, only: cldfrc2m_readnl
242) use cldwat, only: cldwat_readnl
243) use zm_conv, only: zmconv_readnl
244) use hk_conv, only: hkconv_readnl
245) use uwshcu, only: uwshcu_readnl
246) use pkg_cld_sediment, only: cld_sediment_readnl
247) use gw_drag, only: gw_drag_readnl
248) use qbo, only: qbo_readnl
249) use iondrag, only: iondrag_readnl
250) use phys_debug_util, only: phys_debug_readnl
251) use rad_constituents, only: rad_cnst_readnl
252) use radiation_data, only: rad_data_readnl
253) use modal_aer_opt, only: modal_aer_opt_readnl
254) use clubb_intr, only: clubb_readnl
255) use shoc_intr, only: shoc_readnl
256) use chemistry, only: chem_readnl
257) use lin_strat_chem, only: linoz_readnl
258) use prescribed_volcaero, only: prescribed_volcaero_readnl
259) use aerodep_flx, only: aerodep_flx_readnl
260) use solar_data, only: solar_data_readnl
261) use tropopause, only: tropopause_readnl
262) use aoa_tracers, only: aoa_tracers_readnl
263) use prescribed_ozone, only: prescribed_ozone_readnl
264) use prescribed_aero, only: prescribed_aero_readnl
265) use prescribed_ghg, only: prescribed_ghg_readnl
266) use read_spa_data, only: spa_readnl
267) use aircraft_emit, only: aircraft_emit_readnl
268) use cospsimulator_intr, only: cospsimulator_intr_readnl
269) use sat_hist, only: sat_hist_readnl
270) ! Needed by sat_hist_readnl
271) use cam_history, only: hfilename_spec, mfilt, fincl, nhtfrq, avgflag_pertape
272) use vertical_diffusion, only: vd_readnl
273) use cam_history_support, only: fieldname_len, fieldname_lenp2
274) use cam_diagnostics, only: diag_readnl
275) use nudging, only: nudging_readnl
276) use radheat, only: radheat_readnl
277) #if ( defined OFFLINE_DYN )
278) use metdata, only: metdata_readnl
279) #endif
280) use radiation, only: radiation_readnl
281) use conditional_diag, only: cnd_diag_readnl
282)
283) !---------------------------Arguments-----------------------------------
284)
285) logical , intent(in), optional :: single_column_in
286) logical , intent(in), optional :: scm_multcols_in
287) real(r8), intent(in), optional :: scmlon_in
288) real(r8), intent(in), optional :: scmlat_in
289) character(len=*) , optional :: nlfilename_in
290) !-----------------------------------------------------------------------
291)
292) include 'netcdf.inc'
293)
294) !---------------------------Local variables-----------------------------
295) character(len=*), parameter :: subname = "read_namelist"
296)
297) integer ntspdy ! number of timesteps per day
298) integer t ! history tape index
299) integer lastchar ! index to last char of a char variable
300) integer ierr ! error code
301) integer unitn ! namelist unit number
302)
303) integer f, i
304) integer, parameter :: max_chars = 128
305)
306)
307) ! Define the cam_inparm namelist
308) ! ***NOTE*** If a namelist option is not described in the CAM Users Guide,
309) ! it is not supported.
310) namelist /cam_inparm/ ncdata, bnd_topo, &
311) cam_branch_file , &
312) dtime, &
313) nlvdry, &
314) pertlim ,&
315) new_random ,&
316) seed_custom ,&
317) seed_clock ,&
318) readtrace, rayk0, raykrange, raytau0, &
319) tracers_flag, &
320) indirect, &
321) print_step_cost, &
322) phys_chnk_fdim, &
323) phys_chnk_fdim_max, &
324) phys_chnk_fdim_mult, &
325) phys_alltoall, phys_loadbalance, phys_twin_algorithm, &
326) phys_chnk_per_thd, phys_chnk_cost_write
327)
328) ! physics buffer
329) namelist /cam_inparm/ pbuf_global_allocate
330)
331) ! conservation checks
332) namelist /cam_inparm/ print_energy_errors
333)
334) ! IOP
335) namelist /cam_inparm/ iopfile, scm_iop_srf_prop, iop_nudge_tq, iop_nudge_uv, &
336) iop_nudge_tq_low, iop_nudge_tq_high, iop_nudge_tscale, &
337) scm_observed_aero, precip_off, iop_coriolis, &
338) scm_zero_non_iop_tracers, iop_perturb_high, dp_crm, &
339) iop_dosubsidence, scm_zero_non_iop_tracers
340)
341) !-----------------------------------------------------------------------
342)
343) if (present(nlfilename_in)) then
344) nlfilename = nlfilename_in
345) end if
346)
347) ! Determine preset values (this is currently being phased out)
348) call preset ()
349)
350) ! Preset sulfate aerosol related variables
351) indirect = .false.
352)
353) ! restart write interval
354) call restart_defaultopts( &
355) cam_branch_file_out =cam_branch_file )
356)
357) ! Get default values of runtime options for physics chunking.
358) call phys_grid_defaultopts( &
359) phys_chnk_fdim_out =phys_chnk_fdim, &
360) phys_chnk_fdim_max_out =phys_chnk_fdim_max, &
361) phys_chnk_fdim_mult_out =phys_chnk_fdim_mult, &
362) phys_loadbalance_out =phys_loadbalance, &
363) phys_twin_algorithm_out =phys_twin_algorithm, &
364) phys_alltoall_out =phys_alltoall, &
365) phys_chnk_per_thd_out =phys_chnk_per_thd, &
366) phys_chnk_cost_write_out=phys_chnk_cost_write )
367)
368) ! conservation
369) call check_energy_defaultopts( &
370) print_energy_errors_out = print_energy_errors )
371)
372) ! Set default options for single column or doubly periodic CRM mode
373) if (present(single_column_in)) then
374) call iop_default_opts(scmlat_out=scmlat,scmlon_out=scmlon, &
375) single_column_out=single_column, &
376) scm_iop_srf_prop_out=scm_iop_srf_prop,&
377) iop_dosubsidence_out=iop_dosubsidence, &
378) iop_coriolis_out=iop_coriolis, &
379) iop_nudge_tq_out=iop_nudge_tq, &
380) iop_nudge_uv_out=iop_nudge_uv, &
381) iop_nudge_tq_low_out=iop_nudge_tq_low, &
382) iop_nudge_tq_high_out=iop_nudge_tq_high, &
383) iop_nudge_tscale_out=iop_nudge_tscale, &
384) scm_observed_aero_out=scm_observed_aero, &
385) precip_off_out=precip_off, &
386) iop_perturb_high_out=iop_perturb_high, &
387) scm_multcols_out=scm_multcols, &
388) dp_crm_out=dp_crm, &
389) scm_zero_non_iop_tracers_out=scm_zero_non_iop_tracers)
390) end if
391)
392) ! Read in the cam_inparm namelist from input filename
393) if (masterproc) then
394) write(iulog,*) 'Read in cam_inparm namelist from: ', trim(nlfilename)
395) unitn = getunit()
396) open( unitn, file=trim(nlfilename), status='old' )
397)
398) ! Look for cam_inparm group name in the input file. If found, leave the
399) ! file positioned at that namelist group.
400) call find_group_name(unitn, 'cam_inparm', status=ierr)
401) if (ierr == 0) then ! found cam_inparm
402) read(unitn, cam_inparm, iostat=ierr) ! read the cam_inparm namelist group
403) if (ierr /= 0) then
404) call endrun( subname//':: namelist read returns an'// &
405) ' error condition for cam_inparm' )
406) end if
407) else
408) call endrun(subname // ':: can''t find cam_inparm in file ' // trim(nlfilename))
409) end if
410) close( unitn )
411) call freeunit( unitn )
412)
413) ! Check CASE namelist variable
414) if (caseid==' ') then
415) call endrun ('READ_NAMELIST: Namelist variable CASEID must be set')
416) end if
417)
418) lastchar = len(caseid)
419) if (caseid(lastchar:lastchar) /= ' ') then
420) write(iulog,*)'READ_NAMELIST: CASEID must not exceed ', len(caseid)-1, ' characters'
421) call endrun
422) end if
423) end if
424)
425) #if ( defined SPMD )
426) ! Scatter namelist data to all processes
427) call distnl ( )
428) #endif
429)
430) ! restart write interval
431) call restart_setopts( nsrest, &
432) cam_branch_file_in =cam_branch_file )
433)
434)
435) ! Set runtime options for physics chunking.
436) call phys_grid_setopts( &
437) phys_chnk_fdim_in =phys_chnk_fdim, &
438) phys_chnk_fdim_max_in =phys_chnk_fdim_max, &
439) phys_chnk_fdim_mult_in =phys_chnk_fdim_mult, &
440) phys_loadbalance_in =phys_loadbalance, &
441) phys_twin_algorithm_in =phys_twin_algorithm, &
442) phys_alltoall_in =phys_alltoall, &
443) phys_chnk_per_thd_in =phys_chnk_per_thd, &
444) phys_chnk_cost_write_in=phys_chnk_cost_write )
445)
446) ! conservation
447) call check_energy_setopts( &
448) print_energy_errors_in = print_energy_errors )
449)
450) ! Set runtime options for single column or doubly periodic CRM mode
451) if (present(single_column_in) .and. present(scmlon_in) .and. present(scmlat_in)) then
452) if (single_column_in) then
453) single_column = single_column_in
454) scmlon = scmlon_in
455) scmlat = scmlat_in
456) scm_multcols = scm_multcols_in
457) call iop_setopts( scmlat_in=scmlat,scmlon_in=scmlon, &
458) iopfile_in=iopfile,single_column_in=single_column,&
459) scm_iop_srf_prop_in=scm_iop_srf_prop,&
460) iop_dosubsidence_in=iop_dosubsidence,&
461) iop_coriolis_in=iop_coriolis,&
462) iop_nudge_tq_in=iop_nudge_tq, &
463) iop_nudge_uv_in=iop_nudge_uv, &
464) iop_nudge_tq_low_in=iop_nudge_tq_low, &
465) iop_nudge_tq_high_in=iop_nudge_tq_high, &
466) iop_nudge_tscale_in=iop_nudge_tscale, &
467) iop_perturb_high_in=iop_perturb_high, &
468) scm_observed_aero_in=scm_observed_aero, &
469) precip_off_in=precip_off, &
470) scm_multcols_in=scm_multcols,&
471) dp_crm_in=dp_crm,&
472) scm_zero_non_iop_tracers_in=scm_zero_non_iop_tracers)
473) end if
474) endif
475)
476) ! Call subroutines for modules to read their own namelist.
477) ! In some cases namelist default values may depend on settings from
478) ! other modules, so there may be an order dependence in the following
479) ! calls.
480) ! ***N.B.*** In particular, physconst_readnl should be called before
481) ! the other readnl methods in case that method is used to set
482) ! physical constants, some of which are set at runtime
483) ! by the physconst_readnl method.
484) ! Modules that read their own namelist are responsible for making sure
485) ! all processes receive the values.
486)
487) call spmd_utils_readnl(nlfilename)
488) call history_readnl(nlfilename, dtime)
489) call physconst_readnl(nlfilename)
490) call chem_surfvals_readnl(nlfilename)
491) call phys_ctl_readnl(nlfilename)
492) call wv_sat_readnl(nlfilename)
493) call ref_pres_readnl(nlfilename)
494) call cam3_aero_data_readnl(nlfilename)
495) call cam3_ozone_data_readnl(nlfilename)
496) call macrop_driver_readnl(nlfilename)
497) call microp_driver_readnl(nlfilename)
498) call microp_aero_readnl(nlfilename)
499) call clubb_readnl(nlfilename)
500) call shoc_readnl(nlfilename)
501) call subcol_readnl(nlfilename)
502) call cldfrc_readnl(nlfilename)
503) call cldfrc2m_readnl(nlfilename)
504) call zmconv_readnl(nlfilename)
505) call cldwat_readnl(nlfilename)
506) call hkconv_readnl(nlfilename)
507) call uwshcu_readnl(nlfilename)
508) call cld_sediment_readnl(nlfilename)
509) call gw_drag_readnl(nlfilename)
510) call qbo_readnl(nlfilename)
511) call iondrag_readnl(nlfilename)
512) call phys_debug_readnl(nlfilename)
513) call rad_cnst_readnl(nlfilename)
514) call rad_data_readnl(nlfilename)
515) call modal_aer_opt_readnl(nlfilename)
516) call chem_readnl(nlfilename)
517) call linoz_readnl(nlfilename)
518) call prescribed_volcaero_readnl(nlfilename)
519) call solar_data_readnl(nlfilename)
520) call tropopause_readnl(nlfilename)
521) call aoa_tracers_readnl(nlfilename)
522) call aerodep_flx_readnl(nlfilename)
523) call prescribed_ozone_readnl(nlfilename)
524) call prescribed_aero_readnl(nlfilename)
525) call spa_readnl(nlfilename)
526) call prescribed_ghg_readnl(nlfilename)
527) call co2_cycle_readnl(nlfilename)
528) call aircraft_emit_readnl(nlfilename)
529) call cospsimulator_intr_readnl(nlfilename)
530) call sat_hist_readnl(nlfilename, hfilename_spec, mfilt, fincl, nhtfrq, avgflag_pertape)
531) call diag_readnl(nlfilename)
532) call nudging_readnl(nlfilename)
533) call radheat_readnl(nlfilename)
534) call vd_readnl(nlfilename)
535) #if ( defined OFFLINE_DYN )
536) call metdata_readnl(nlfilename)
537) #endif
538) call cnd_diag_readnl(nlfilename)
539)
540) ! Read radiation namelist
541) call radiation_readnl(nlfilename, dtime_in=dtime)
542)
543) ! Print cam_inparm input variables to standard output
544) if (masterproc) then
545) write(iulog,*)' ------------------------------------------'
546) write(iulog,*)' *** INPUT VARIABLES (CAM_INPARM) ***'
547) write(iulog,*)' ------------------------------------------'
548) if (nsrest/=0) then
549) write(iulog,*) ' Continuation of an earlier run'
550) else
551) write(iulog,*) ' Initial run'
552) end if
553) write(iulog,*) ' ********** CASE = ',trim(caseid),' **********'
554) write(iulog,'(1x,a)') ctitle
555) if (len_trim(ncdata) > 0) then
556) write(iulog,*) 'Initial dataset is: ',trim(ncdata)
557) end if
558) write(iulog,*)'Topography dataset is: ', trim(bnd_topo)
559)
560) ! Type of run
561) write(iulog,*)'Run type flag (NSREST) 0=initial, 1=restart, 3=branch ',nsrest
562)
563) call restart_printopts()
564)
565) ! Write physics variables from namelist cam_inparm to std. output
566) write(iulog,9108) nlvdry
567) 9108 format('Lowest level for dry adiabatic adjust (NLVDRY)',i10)
568)
569) if ( (adiabatic .and. ideal_phys) .or. (adiabatic .and. aqua_planet) .or. &
570) (ideal_phys .and. aqua_planet) ) then
571) call endrun ('READ_NAMELIST: Only one of ADIABATIC, IDEAL_PHYS, or AQUA_PLANET can be .true.')
572) end if
573)
574) #ifdef COUP_SOM
575) if (adiabatic .or. ideal_phys .or. aqua_planet )then
576) call endrun ('READ_NAMELIST: adiabatic, ideal_phys or aqua_planet can not be used with SOM')
577) end if
578) #else
579) if (adiabatic) write(iulog,*) 'Model will run ADIABATICALLY (i.e. no physics)'
580) if (ideal_phys) write(iulog,*) 'Run ONLY the "idealized" dynamical core of the ', &
581) 'model (dynamics + Held&Suarez-specified physics)'
582) if (aqua_planet) then
583) write(iulog,*) 'Running model in "AQUA_PLANET" mode'
584) else
585) write(iulog,*) 'NOT Running model in "AQUA_PLANET" mode'
586) end if
587) #endif
588)
589)
590) end if
591)
592) ! set public data in cam_control_mod
593) moist_physics = (.not. adiabatic) .and. (.not. ideal_phys)
594)
595) #ifdef PERGRO
596) if (masterproc) then
597) write(iulog,*)'pergro for cloud water is true'
598) end if
599) #endif
600)
601) ntspdy = nint(86400._r8/dtime) ! no. timesteps per day
602)
603)
604) end subroutine read_namelist
605)
606)
607) !=======================================================================
608)
609) #ifdef SPMD
610) subroutine distnl
611) !-----------------------------------------------------------------------
612) !
613) ! Purpose:
614) ! Distribute namelist data to all processors.
615) !
616) ! The cpp SPMD definition provides for the funnelling of all program i/o
617) ! through the master processor. Processor 0 either reads restart/history
618) ! data from the disk and distributes it to all processors, or collects
619) ! data from all processors and writes it to disk.
620) !
621) !---------------------------Code history-------------------------------
622) !
623) ! Original version: CCM2
624) ! Standardized: J. Rosinski, Oct 1995
625) ! J. Truesdale, Feb. 1996
626) !
627) !-----------------------------------------------------------------------
628) use mpishorthand
629) !-----------------------------------------------------------------------
630)
631) !
632) !-----------------------------------------------------------------------
633) !
634) call mpibcast (dtime, 1,mpiint,0,mpicom)
635) call mpibcast (nsrest ,1,mpiint,0,mpicom)
636) call mpibcast (nlvdry ,1,mpiint,0,mpicom)
637)
638) call mpibcast (rayk0 ,1,mpiint,0,mpicom)
639) call mpibcast (raykrange,1,mpir8,0,mpicom)
640) call mpibcast (raytau0 ,1,mpir8,0,mpicom)
641)
642) call mpibcast (tracers_flag,1,mpilog,0,mpicom)
643) call mpibcast (readtrace ,1,mpilog,0,mpicom)
644) call mpibcast (adiabatic ,1,mpilog,0,mpicom)
645) call mpibcast (ideal_phys ,1,mpilog,0,mpicom)
646) call mpibcast (aqua_planet ,1,mpilog,0,mpicom)
647)
648) call mpibcast (print_step_cost,1,mpilog,0,mpicom)
649) call mpibcast (pertlim ,1, mpir8 , 0, mpicom )
650) call mpibcast (new_random ,1, mpilog, 0, mpicom )
651) call mpibcast (seed_custom ,1, mpiint, 0, mpicom )
652) call mpibcast (seed_clock ,1, mpilog, 0, mpicom )
653)
654) call mpibcast (caseid ,len(caseid) ,mpichar,0,mpicom)
655) call mpibcast (ctitle ,len(ctitle),mpichar,0,mpicom)
656) call mpibcast (ncdata ,len(ncdata) ,mpichar,0,mpicom)
657) call mpibcast (bnd_topo ,len(bnd_topo) ,mpichar,0,mpicom)
658) call mpibcast (cam_branch_file ,len(cam_branch_file) ,mpichar,0,mpicom)
659)
660) call mpibcast (indirect , 1 ,mpilog, 0,mpicom)
661)
662) ! Physics chunk tuning
663) call mpibcast (phys_chnk_fdim ,1,mpiint,0,mpicom)
664) call mpibcast (phys_chnk_fdim_max ,1,mpiint,0,mpicom)
665) call mpibcast (phys_chnk_fdim_mult ,1,mpiint,0,mpicom)
666) call mpibcast (phys_loadbalance ,1,mpiint,0,mpicom)
667) call mpibcast (phys_twin_algorithm ,1,mpiint,0,mpicom)
668) call mpibcast (phys_alltoall ,1,mpiint,0,mpicom)
669) call mpibcast (phys_chnk_per_thd ,1,mpiint,0,mpicom)
670) call mpibcast (phys_chnk_cost_write,1,mpilog,0,mpicom)
671)
672) ! Physics buffer
673) call mpibcast (pbuf_global_allocate, 1, mpilog, 0, mpicom)
674)
675) ! Conservation
676) call mpibcast (print_energy_errors, 1, mpilog, 0, mpicom)
677)
678) end subroutine distnl
679) #endif
680)
681)
682)
683) subroutine preset
684) !-----------------------------------------------------------------------
685) !
686) ! Purpose: Preset namelist CAM_INPARM input variables and initialize some other variables
687) !
688) ! Method: Hardwire the values
689) !
690) ! Author: CCM Core Group
691) !
692) !-----------------------------------------------------------------------
693) use rgrid
694) !-----------------------------------------------------------------------
695) include 'netcdf.inc'
696) !-----------------------------------------------------------------------
697) !
698) !
699) ! Flags
700) !
701) print_step_cost = .false. ! print per timestep cost info
702) !
703) ! rgrid: set default to full grid
704) !
705) nlon(:) = plon
706) !!
707) !! Unit numbers: set to invalid
708) !!
709) ! ncid_ini = -1
710) ! ncid_sst = -1
711) ! ncid_trc = -1
712) !
713) return
714) end subroutine preset
715)
716) end module runtime_opts