Line data Source code
1 : module cam_comp
2 : !-----------------------------------------------------------------------
3 : !
4 : ! Community Atmosphere Model (CAM) component interfaces.
5 : !
6 : ! This interface layer is CAM specific, i.e., it deals entirely with CAM
7 : ! specific data structures. It is the layer above this, either atm_comp_mct
8 : ! or atm_comp_nuopc, which translates between CAM and either MCT or NUOPC
9 : ! data structures in order to interface with the driver/coupler.
10 : !
11 : !-----------------------------------------------------------------------
12 :
13 : use shr_kind_mod, only: r8 => SHR_KIND_R8, cl=>SHR_KIND_CL, cs=>SHR_KIND_CS
14 : use shr_sys_mod, only: shr_sys_flush
15 :
16 : use spmd_utils, only: masterproc, mpicom
17 : use cam_control_mod, only: cam_ctrl_init, cam_ctrl_set_orbit
18 : use runtime_opts, only: read_namelist
19 : use time_manager, only: timemgr_init, get_nstep
20 : use camsrfexch, only: cam_out_t, cam_in_t
21 : use ppgrid, only: begchunk, endchunk
22 : use physics_types, only: physics_state, physics_tend
23 : use dyn_comp, only: dyn_import_t, dyn_export_t
24 :
25 : use physics_buffer, only: physics_buffer_desc
26 : use offline_driver, only: offline_driver_init, offline_driver_dorun, offline_driver_run
27 :
28 : use perf_mod
29 : use cam_logfile, only: iulog
30 : use cam_abortutils, only: endrun
31 :
32 : implicit none
33 : private
34 :
35 : public cam_init ! First phase of CAM initialization
36 : public cam_run1 ! CAM run method phase 1
37 : public cam_run2 ! CAM run method phase 2
38 : public cam_run3 ! CAM run method phase 3
39 : public cam_run4 ! CAM run method phase 4
40 : public cam_final ! CAM Finalization
41 :
42 : type(dyn_import_t) :: dyn_in ! Dynamics import container
43 : type(dyn_export_t) :: dyn_out ! Dynamics export container
44 :
45 : type(physics_state), pointer :: phys_state(:) => null()
46 : type(physics_tend ), pointer :: phys_tend(:) => null()
47 : type(physics_buffer_desc), pointer :: pbuf2d(:,:) => null()
48 :
49 : real(r8) :: dtime_phys ! Time step for physics tendencies. Set by call to
50 : ! stepon_run1, then passed to the phys_run*
51 :
52 : !-----------------------------------------------------------------------
53 : contains
54 : !-----------------------------------------------------------------------
55 :
56 3072 : subroutine cam_init( &
57 1536 : caseid, ctitle, model_doi_url, &
58 : initial_run_in, restart_run_in, branch_run_in, post_assim_in, &
59 1536 : calendar, brnch_retain_casename, aqua_planet, &
60 : single_column, scmlat, scmlon, &
61 : eccen, obliqr, lambm0, mvelpp, &
62 : perpetual_run, perpetual_ymd, &
63 : dtime, start_ymd, start_tod, ref_ymd, ref_tod, &
64 : stop_ymd, stop_tod, curr_ymd, curr_tod, &
65 : cam_out, cam_in)
66 :
67 : !-----------------------------------------------------------------------
68 : !
69 : ! CAM component initialization.
70 : !
71 : !-----------------------------------------------------------------------
72 :
73 : use history_defaults, only: bldfld
74 : use cam_initfiles, only: cam_initfiles_open
75 : use dyn_grid, only: dyn_grid_init
76 : use phys_grid, only: phys_grid_init
77 : use physpkg, only: phys_register, phys_init
78 : use chem_surfvals, only: chem_surfvals_init
79 : use dyn_comp, only: dyn_init
80 : use cam_restart, only: cam_read_restart
81 : use stepon, only: stepon_init
82 : use ionosphere_interface, only: ionosphere_init
83 : use camsrfexch, only: hub2atm_alloc, atm2hub_alloc
84 : use cam_history, only: intht
85 : use history_scam, only: scm_intht
86 : use cam_pio_utils, only: init_pio_subsystem
87 : use cam_instance, only: inst_suffix
88 : use cam_snapshot_common, only: cam_snapshot_deactivate
89 : use air_composition, only: air_composition_init
90 : #if (defined BFB_CAM_SCAM_IOP)
91 : use history_defaults, only: initialize_iop_history
92 : #endif
93 : use phys_grid_ctem, only: phys_grid_ctem_reg
94 :
95 : ! Arguments
96 : character(len=cl), intent(in) :: caseid ! case ID
97 : character(len=cl), intent(in) :: ctitle ! case title
98 : character(len=cl), intent(in) :: model_doi_url ! CESM model DOI
99 : logical, intent(in) :: initial_run_in ! true => inital run
100 : logical, intent(in) :: restart_run_in ! true => restart run
101 : logical, intent(in) :: branch_run_in ! true => branch run
102 : logical, intent(in) :: post_assim_in ! true => resume mode
103 : character(len=cs), intent(in) :: calendar ! Calendar type
104 : logical, intent(in) :: brnch_retain_casename ! Flag to allow a branch to use the same
105 : ! caseid as the run being branched from.
106 : logical, intent(in) :: aqua_planet ! Flag to run model in "aqua planet" mode
107 :
108 : logical, intent(in) :: single_column
109 : real(r8), intent(in) :: scmlat
110 : real(r8), intent(in) :: scmlon
111 :
112 : real(r8), intent(in) :: eccen
113 : real(r8), intent(in) :: obliqr
114 : real(r8), intent(in) :: lambm0
115 : real(r8), intent(in) :: mvelpp
116 :
117 : logical, intent(in) :: perpetual_run ! true => perpetual mode enabled
118 : integer, intent(in) :: perpetual_ymd ! Perpetual date (YYYYMMDD)
119 : integer, intent(in) :: dtime ! model timestep (sec)
120 :
121 : integer, intent(in) :: start_ymd ! Start date (YYYYMMDD)
122 : integer, intent(in) :: start_tod ! Start time of day (sec)
123 : integer, intent(in) :: curr_ymd ! Start date (YYYYMMDD)
124 : integer, intent(in) :: curr_tod ! Start time of day (sec)
125 : integer, intent(in) :: stop_ymd ! Stop date (YYYYMMDD)
126 : integer, intent(in) :: stop_tod ! Stop time of day (sec)
127 : integer, intent(in) :: ref_ymd ! Reference date (YYYYMMDD)
128 : integer, intent(in) :: ref_tod ! Reference time of day (sec)
129 :
130 : type(cam_out_t), pointer :: cam_out(:) ! Output from CAM to surface
131 : type(cam_in_t) , pointer :: cam_in(:) ! Merged input state to CAM
132 :
133 : ! Local variables
134 : character(len=cs) :: filein ! Input namelist filename
135 : !-----------------------------------------------------------------------
136 :
137 1536 : call init_pio_subsystem()
138 :
139 : ! Initializations using data passed from coupler.
140 : call cam_ctrl_init( &
141 : caseid_in=caseid, &
142 : ctitle_in=ctitle, &
143 : initial_run_in=initial_run_in, &
144 : restart_run_in=restart_run_in, &
145 : branch_run_in=branch_run_in, &
146 : post_assim_in=post_assim_in, &
147 : aqua_planet_in=aqua_planet, &
148 1536 : brnch_retain_casename_in=brnch_retain_casename)
149 :
150 1536 : call cam_ctrl_set_orbit(eccen, obliqr, lambm0, mvelpp)
151 :
152 : call timemgr_init( &
153 : dtime, calendar, start_ymd, start_tod, ref_ymd, &
154 : ref_tod, stop_ymd, stop_tod, curr_ymd, curr_tod, &
155 1536 : perpetual_run, perpetual_ymd, initial_run_in)
156 :
157 : ! Read CAM namelists.
158 1536 : filein = "atm_in" // trim(inst_suffix)
159 1536 : call read_namelist(filein, single_column, scmlat, scmlon)
160 :
161 : ! Open initial or restart file, and topo file if specified.
162 1536 : call cam_initfiles_open()
163 :
164 : ! Initialize grids and dynamics grid decomposition
165 1536 : call dyn_grid_init()
166 :
167 : ! Initialize physics grid decomposition
168 1536 : call phys_grid_init()
169 :
170 : ! Register zonal average grid for phys TEM diagnostics
171 1536 : call phys_grid_ctem_reg()
172 :
173 : ! Register advected tracers and physics buffer fields
174 1536 : call phys_register ()
175 :
176 : ! Initialize ghg surface values before default initial distributions
177 : ! are set in dyn_init
178 1536 : call chem_surfvals_init()
179 :
180 1536 : call air_composition_init()
181 : ! initialize ionosphere
182 1536 : call ionosphere_init()
183 :
184 1536 : if (initial_run_in) then
185 :
186 768 : call dyn_init(dyn_in, dyn_out)
187 :
188 : ! Allocate and setup surface exchange data
189 768 : call atm2hub_alloc(cam_out)
190 768 : call hub2atm_alloc(cam_in)
191 :
192 : else
193 :
194 768 : call cam_read_restart(cam_in, cam_out, dyn_in, dyn_out, pbuf2d, stop_ymd, stop_tod)
195 :
196 : #if (defined BFB_CAM_SCAM_IOP)
197 : call initialize_iop_history()
198 : #endif
199 : end if
200 :
201 1536 : call phys_init( phys_state, phys_tend, pbuf2d, cam_in, cam_out )
202 :
203 1536 : call bldfld () ! master field list (if branch, only does hash tables)
204 :
205 1536 : call stepon_init(dyn_in, dyn_out)
206 :
207 1536 : call offline_driver_init()
208 :
209 1536 : if (single_column) call scm_intht()
210 1536 : call intht(model_doi_url)
211 :
212 1536 : call cam_snapshot_deactivate()
213 :
214 1536 : end subroutine cam_init
215 :
216 : !
217 : !-----------------------------------------------------------------------
218 : !
219 32256 : subroutine cam_run1(cam_in, cam_out)
220 : !-----------------------------------------------------------------------
221 : !
222 : ! Purpose: First phase of atmosphere model run method.
223 : ! Runs first phase of dynamics and first phase of
224 : ! physics (before surface model updates).
225 : !
226 : !-----------------------------------------------------------------------
227 :
228 1536 : use physpkg, only: phys_run1
229 : use stepon, only: stepon_run1
230 : use ionosphere_interface,only: ionosphere_run1
231 :
232 : type(cam_in_t) :: cam_in(begchunk:endchunk)
233 : type(cam_out_t) :: cam_out(begchunk:endchunk)
234 :
235 : !-----------------------------------------------------------------------
236 :
237 16128 : if (offline_driver_dorun) return
238 :
239 : !----------------------------------------------------------
240 : ! First phase of dynamics (at least couple from dynamics to physics)
241 : ! Return time-step for physics from dynamics.
242 : !----------------------------------------------------------
243 16128 : call t_barrierf ('sync_stepon_run1', mpicom)
244 16128 : call t_startf ('stepon_run1')
245 16128 : call stepon_run1( dtime_phys, phys_state, phys_tend, pbuf2d, dyn_in, dyn_out )
246 16128 : call t_stopf ('stepon_run1')
247 :
248 : !----------------------------------------------------------
249 : ! first phase of ionosphere -- write to IC file if needed
250 : !----------------------------------------------------------
251 16128 : call ionosphere_run1(pbuf2d)
252 :
253 : !
254 : !----------------------------------------------------------
255 : ! PHYS_RUN Call the Physics package
256 : !----------------------------------------------------------
257 : !
258 16128 : call t_barrierf ('sync_phys_run1', mpicom)
259 16128 : call t_startf ('phys_run1')
260 16128 : call phys_run1(phys_state, dtime_phys, phys_tend, pbuf2d, cam_in, cam_out)
261 16128 : call t_stopf ('phys_run1')
262 :
263 16128 : end subroutine cam_run1
264 :
265 : !
266 : !-----------------------------------------------------------------------
267 : !
268 :
269 29184 : subroutine cam_run2( cam_out, cam_in )
270 : !-----------------------------------------------------------------------
271 : !
272 : ! Purpose: Second phase of atmosphere model run method.
273 : ! Run the second phase physics, run methods that
274 : ! require the surface model updates. And run the
275 : ! second phase of dynamics that at least couples
276 : ! between physics to dynamics.
277 : !
278 : !-----------------------------------------------------------------------
279 :
280 16128 : use physpkg, only: phys_run2
281 : use stepon, only: stepon_run2
282 : use ionosphere_interface, only: ionosphere_run2
283 :
284 : type(cam_out_t), intent(inout) :: cam_out(begchunk:endchunk)
285 : type(cam_in_t), intent(inout) :: cam_in(begchunk:endchunk)
286 :
287 14592 : if (offline_driver_dorun) then
288 0 : call offline_driver_run( phys_state, pbuf2d, cam_out, cam_in )
289 : return
290 : endif
291 :
292 : !
293 : ! Second phase of physics (after surface model update)
294 : !
295 14592 : call t_barrierf ('sync_phys_run2', mpicom)
296 14592 : call t_startf ('phys_run2')
297 14592 : call phys_run2(phys_state, dtime_phys, phys_tend, pbuf2d, cam_out, cam_in )
298 14592 : call t_stopf ('phys_run2')
299 :
300 : !
301 : ! Second phase of dynamics (at least couple from physics to dynamics)
302 : !
303 14592 : call t_barrierf ('sync_stepon_run2', mpicom)
304 14592 : call t_startf ('stepon_run2')
305 14592 : call stepon_run2( phys_state, phys_tend, dyn_in, dyn_out )
306 14592 : call t_stopf ('stepon_run2')
307 :
308 : !
309 : ! Ion transport
310 : !
311 14592 : call t_startf('ionosphere_run2')
312 14592 : call ionosphere_run2( phys_state, pbuf2d )
313 14592 : call t_stopf ('ionosphere_run2')
314 :
315 14592 : end subroutine cam_run2
316 :
317 : !
318 : !-----------------------------------------------------------------------
319 : !
320 :
321 29184 : subroutine cam_run3( cam_out )
322 : !-----------------------------------------------------------------------
323 : !
324 : ! Purpose: Third phase of atmosphere model run method. This consists
325 : ! of the third phase of the dynamics. For some dycores
326 : ! this will be the actual dynamics run, for others the
327 : ! dynamics happens before physics in phase 1.
328 : !
329 : !-----------------------------------------------------------------------
330 14592 : use stepon, only: stepon_run3
331 :
332 : type(cam_out_t), intent(inout) :: cam_out(begchunk:endchunk)
333 : !-----------------------------------------------------------------------
334 :
335 14592 : if (offline_driver_dorun) return
336 :
337 : !
338 : ! Third phase of dynamics
339 : !
340 14592 : call t_barrierf ('sync_stepon_run3', mpicom)
341 14592 : call t_startf ('stepon_run3')
342 14592 : call stepon_run3( dtime_phys, cam_out, phys_state, dyn_in, dyn_out )
343 :
344 14592 : call t_stopf ('stepon_run3')
345 :
346 14592 : end subroutine cam_run3
347 :
348 : !
349 : !-----------------------------------------------------------------------
350 : !
351 :
352 29184 : subroutine cam_run4( cam_out, cam_in, rstwr, nlend, &
353 : yr_spec, mon_spec, day_spec, sec_spec )
354 :
355 : !-----------------------------------------------------------------------
356 : !
357 : ! Purpose: Final phase of atmosphere model run method. This consists
358 : ! of all the restart output, history writes, and other
359 : ! file output.
360 : !
361 : !-----------------------------------------------------------------------
362 14592 : use dycore_budget, only: print_budget
363 : use cam_history, only: wshist, wrapup, hstwr
364 : use cam_restart, only: cam_write_restart
365 : use qneg_module, only: qneg_print_summary
366 : use time_manager, only: is_last_step
367 :
368 : type(cam_out_t), intent(inout) :: cam_out(begchunk:endchunk)
369 : type(cam_in_t) , intent(inout) :: cam_in(begchunk:endchunk)
370 : logical , intent(in) :: rstwr ! true => write restart file
371 : logical , intent(in) :: nlend ! true => this is final timestep
372 : integer , intent(in), optional :: yr_spec ! Simulation year
373 : integer , intent(in), optional :: mon_spec ! Simulation month
374 : integer , intent(in), optional :: day_spec ! Simulation day
375 : integer , intent(in), optional :: sec_spec ! Seconds into current simulation day
376 :
377 : !----------------------------------------------------------
378 : ! History and restart logic: Write and/or dispose history tapes if required
379 : !----------------------------------------------------------
380 : !
381 14592 : call t_barrierf ('sync_wshist', mpicom)
382 14592 : call t_startf ('wshist')
383 14592 : call wshist ()
384 14592 : call t_stopf ('wshist')
385 :
386 : !
387 : ! Write restart files
388 : !
389 14592 : if (rstwr) then
390 1536 : call t_startf ('cam_write_restart')
391 1536 : if (present(yr_spec).and.present(mon_spec).and.present(day_spec).and.present(sec_spec)) then
392 : call cam_write_restart(cam_in, cam_out, dyn_out, pbuf2d, &
393 1536 : yr_spec=yr_spec, mon_spec=mon_spec, day_spec=day_spec, sec_spec= sec_spec )
394 : else
395 0 : call cam_write_restart(cam_in, cam_out, dyn_out, pbuf2d )
396 : end if
397 1536 : call t_stopf ('cam_write_restart')
398 : end if
399 :
400 14592 : call t_startf ('cam_run4_wrapup')
401 14592 : call wrapup(rstwr, nlend)
402 14592 : call t_stopf ('cam_run4_wrapup')
403 :
404 14592 : call qneg_print_summary(is_last_step())
405 :
406 14592 : call print_budget(hstwr)
407 :
408 14592 : call shr_sys_flush(iulog)
409 :
410 14592 : end subroutine cam_run4
411 :
412 : !
413 : !-----------------------------------------------------------------------
414 : !
415 :
416 1536 : subroutine cam_final( cam_out, cam_in )
417 : !-----------------------------------------------------------------------
418 : !
419 : ! Purpose: CAM finalization.
420 : !
421 : !-----------------------------------------------------------------------
422 14592 : use stepon, only: stepon_final
423 : use physpkg, only: phys_final
424 : use cam_initfiles, only: cam_initfiles_close
425 : use camsrfexch, only: atm2hub_deallocate, hub2atm_deallocate
426 : use ionosphere_interface, only: ionosphere_final
427 : use cam_control_mod, only: initial_run
428 :
429 : !
430 : ! Arguments
431 : !
432 : type(cam_out_t), pointer :: cam_out(:) ! Output from CAM to surface
433 : type(cam_in_t), pointer :: cam_in(:) ! Input from merged surface to CAM
434 :
435 : ! Local variables
436 : integer :: nstep ! Current timestep number.
437 : !-----------------------------------------------------------------------
438 :
439 1536 : call phys_final( phys_state, phys_tend , pbuf2d)
440 1536 : call stepon_final(dyn_in, dyn_out)
441 1536 : call ionosphere_final()
442 :
443 1536 : if (initial_run) then
444 768 : call cam_initfiles_close()
445 : end if
446 :
447 1536 : call hub2atm_deallocate(cam_in)
448 1536 : call atm2hub_deallocate(cam_out)
449 :
450 : ! This flush attempts to ensure that asynchronous diagnostic prints from all
451 : ! processes do not get mixed up with the "END OF MODEL RUN" message printed
452 : ! by masterproc below. The test-model script searches for this message in the
453 : ! output log to figure out if CAM completed successfully.
454 1536 : call shr_sys_flush( 0 ) ! Flush all output to standard error
455 1536 : call shr_sys_flush( iulog ) ! Flush all output to the CAM log file
456 :
457 1536 : if (masterproc) then
458 2 : nstep = get_nstep()
459 2 : write(iulog,9300) nstep-1,nstep
460 : 9300 format (//'Number of completed timesteps:',i6,/,'Time step ',i6, &
461 : ' partially done to provide convectively adjusted and ', &
462 : 'time filtered values for history tape.')
463 2 : write(iulog,*)' '
464 2 : write(iulog,*)'******* END OF MODEL RUN *******'
465 : end if
466 :
467 1536 : end subroutine cam_final
468 :
469 : !-----------------------------------------------------------------------
470 :
471 : end module cam_comp
|