CAM Component  1.2.2
 All Classes Files Functions Variables
cam_comp.F90
Go to the documentation of this file.
1 module cam_comp
2 !-----------------------------------------------------------------------
3 !
4 ! Purpose: The CAM Community Atmosphere Model component. Interfaces with
5 ! a merged surface field that is provided outside of this module.
6 ! This is the atmosphere only component. It can interface with a
7 ! host of surface components.
8 !
9 !-----------------------------------------------------------------------
10  use shr_kind_mod, only: r8 => shr_kind_r8, cl=>shr_kind_cl, cs=>shr_kind_cs
11  use pmgrid, only: plat, plev
12  use spmd_utils, only: masterproc
13  use abortutils, only: endrun
14  use camsrfexch, only: cam_out_t, cam_in_t
15  use shr_sys_mod, only: shr_sys_flush
16  use physics_types, only: physics_state, physics_tend
17  use cam_control_mod, only: nsrest, print_step_cost, obliqr, lambm0, mvelpp, eccen
18  use dyn_comp, only: dyn_import_t, dyn_export_t
19  use ppgrid, only: begchunk, endchunk
20  use perf_mod
21  use cam_logfile, only: iulog
22  use physics_buffer, only: physics_buffer_desc
23  use offline_driver, only: offline_driver_init, offline_driver_readnl
24  use offline_driver, only: offline_driver_dorun, offline_driver_run, offline_driver_done
25 
26  implicit none
27  private
28  save
29  !
30  ! Public access methods
31  !
32  public cam_init ! First phase of CAM initialization
33  public cam_run1 ! CAM run method phase 1
34  public cam_run2 ! CAM run method phase 2
35  public cam_run3 ! CAM run method phase 3
36  public cam_run4 ! CAM run method phase 4
37  public cam_final ! CAM Finalization
38  !
39  ! Private module data
40  !
41 #if ( defined SPMD )
42  real(r8) :: cam_time_beg ! Cam init begin timestamp
43  real(r8) :: cam_time_end ! Cam finalize end timestamp
44  real(r8) :: stepon_time_beg = -1.0_r8 ! Stepon (run1) begin timestamp
45  real(r8) :: stepon_time_end = -1.0_r8 ! Stepon (run4) end timestamp
46  integer :: nstep_beg = -1 ! nstep at beginning of run
47 #else
48  integer :: mpicom = 0
49 #endif
50 
51  real(r8) :: gw(plat) ! Gaussian weights
52  real(r8) :: etamid(plev) ! vertical coords at midpoints
53  real(r8) :: dtime ! Time step for either physics or dynamics (set in dynamics init)
54 
55  type(dyn_import_t) :: dyn_in ! Dynamics import container
56  type(dyn_export_t) :: dyn_out ! Dynamics export container
57 
58  type(physics_state), pointer :: phys_state(:) => null()
59  type(physics_tend ), pointer :: phys_tend(:) => null()
60  type(physics_buffer_desc), pointer :: pbuf2d(:,:) => null()
61 
62  real(r8) :: wcstart, wcend ! wallclock timestamp at start, end of timestep
63  real(r8) :: usrstart, usrend ! user timestamp at start, end of timestep
64  real(r8) :: sysstart, sysend ! sys timestamp at start, end of timestep
65 
66 !-----------------------------------------------------------------------
67  contains
68 !-----------------------------------------------------------------------
69 
70 !
71 !-----------------------------------------------------------------------
72 !
73 subroutine cam_init( cam_out, cam_in, mpicom_atm, &
74  start_ymd, start_tod, ref_ymd, ref_tod, stop_ymd, stop_tod, &
75  perpetual_run, perpetual_ymd, calendar)
76 
77  !-----------------------------------------------------------------------
78  !
79  ! Purpose: CAM initialization.
80  !
81  !-----------------------------------------------------------------------
82 
83  use infnan, only: nan, assignment(=)
84  use history_defaults, only: bldfld
85  use cam_initfiles, only: cam_initfiles_open
86  use inital, only: cam_initial
87  use cam_restart, only: cam_read_restart
88  use stepon, only: stepon_init
89  use physpkg, only: phys_init, phys_register
90 
91  use dycore, only: dycore_is
92 #if (defined BFB_CAM_SCAM_IOP)
93  use history_defaults, only: initialize_iop_history
94 #endif
95 ! use shr_orb_mod, only: shr_orb_params
97  use cam_history, only: addfld, add_default, phys_decomp, intht, init_masterlinkedlist
98  use history_scam, only: scm_intht
99  use scammod, only: single_column
100  use cam_pio_utils, only: init_pio_subsystem
101  use cam_instance, only: inst_suffix
102 
103 #if ( defined SPMD )
104  real(r8) :: mpi_wtime ! External
105 #endif
106  !-----------------------------------------------------------------------
107  !
108  ! Arguments
109  !
110  type(cam_out_t), pointer :: cam_out(:) ! Output from CAM to surface
111  type(cam_in_t) , pointer :: cam_in(:) ! Merged input state to CAM
112  integer , intent(in) :: mpicom_atm ! CAM MPI communicator
113  integer , intent(in) :: start_ymd ! Start date (YYYYMMDD)
114  integer , intent(in) :: start_tod ! Start time of day (sec)
115  integer , intent(in) :: ref_ymd ! Reference date (YYYYMMDD)
116  integer , intent(in) :: ref_tod ! Reference time of day (sec)
117  integer , intent(in) :: stop_ymd ! Stop date (YYYYMMDD)
118  integer , intent(in) :: stop_tod ! Stop time of day (sec)
119  logical , intent(in) :: perpetual_run ! If in perpetual mode or not
120  integer , intent(in) :: perpetual_ymd ! Perpetual date (YYYYMMDD)
121  character(len=cs) , intent(in) :: calendar ! Calendar type
122  !
123  ! Local variables
124  !
125  logical :: log_print ! Flag to print out log information or not
126  character(len=cs) :: filein ! Input namelist filename
127  !-----------------------------------------------------------------------
128  etamid = nan
129  !
130  ! Initialize CAM MPI communicator, number of processors, master processors
131  !
132 #if ( defined SPMD )
133  cam_time_beg = mpi_wtime()
134 #endif
135 
136  !
137  ! Initialization needed for cam_history
138  !
139  call init_masterlinkedlist()
140  !
141  ! Set up spectral arrays
142  !
143  call trunc()
144  !
145  ! Initialize index values for advected and non-advected tracers
146  !
147  call phys_register()
148  !
149  ! Determine input namelist filename
150  !
151  filein = "atm_in" // trim(inst_suffix)
152  !
153  ! Do appropriate dynamics and history initialization depending on whether initial, restart, or
154  ! branch. On restart run intht need not be called because all the info is on restart dataset.
155  !
156  call init_pio_subsystem(filein)
157 
158  ! read namelist for offline unit driver...
159  call offline_driver_readnl(filein)
160 
161  if ( nsrest == 0 )then
162 
163  call cam_initfiles_open()
164  call cam_initial(dyn_in, dyn_out, nlfilename=filein)
165 
166  ! Allocate and setup surface exchange data
167  call atm2hub_alloc(cam_out)
168  call hub2atm_alloc(cam_in)
169 
170  else
171 
172  call cam_read_restart( cam_out, dyn_in, dyn_out, pbuf2d, stop_ymd, stop_tod, nlfilename=filein )
173 
174  call hub2atm_alloc( cam_in )
175 #if (defined BFB_CAM_SCAM_IOP)
176  call initialize_iop_history()
177 #endif
178  end if
179 
180 
181  call phys_init( phys_state, phys_tend, pbuf2d, cam_out )
182 
183  call bldfld() ! master field list (if branch, only does hash tables)
184 
185  !
186  ! Setup the characteristics of the orbit
187  ! (Based on the namelist parameters)
188  !
189  if (masterproc) then
190  log_print = .true.
191  else
192  log_print = .false.
193  end if
194 
195  call stepon_init( gw, etamid, dyn_in, dyn_out ) ! dyn_out necessary?
196 
197  if (single_column) call scm_intht()
198  call intht()
199 
200  !
201  ! initialize offline unit driver -- needs to be after PIO initialization
202  !
203  call offline_driver_init()
204 
205 end subroutine cam_init
206 
207 !
208 !-----------------------------------------------------------------------
209 !
210 subroutine cam_run1(cam_in, cam_out)
211 !-----------------------------------------------------------------------
212 !
213 ! Purpose: First phase of atmosphere model run method.
214 ! Runs first phase of dynamics and first phase of
215 ! physics (before surface model updates).
216 !
217 !-----------------------------------------------------------------------
218 
219  use physpkg, only: phys_run1
220  use stepon, only: stepon_run1
221 #if ( defined SPMD )
222  use mpishorthand, only: mpicom
223 #endif
224  use time_manager, only: get_nstep
225 
226  type(cam_in_t) :: cam_in(begchunk:endchunk)
227  type(cam_out_t) :: cam_out(begchunk:endchunk)
228 
229 #if ( defined SPMD )
230  real(r8) :: mpi_wtime
231 #endif
232 !-----------------------------------------------------------------------
233 
234 #if ( defined SPMD )
235  if (stepon_time_beg == -1.0_r8) stepon_time_beg = mpi_wtime()
236  if (nstep_beg == -1) nstep_beg = get_nstep()
237 #endif
238  if (masterproc .and. print_step_cost) then
239  call t_stampf(wcstart, usrstart, sysstart)
240  end if
241 
242  if (offline_driver_dorun) return
243 
244  !----------------------------------------------------------
245  ! First phase of dynamics (at least couple from dynamics to physics)
246  ! Return time-step for physics from dynamics.
247  !----------------------------------------------------------
248  call t_barrierf('sync_stepon_run1', mpicom)
249  call t_startf('stepon_run1')
250  call stepon_run1( dtime, phys_state, phys_tend, pbuf2d, dyn_in, dyn_out )
251  call t_stopf('stepon_run1')
252 
253  !
254  !----------------------------------------------------------
255  ! PHYS_RUN Call the Physics package
256  !----------------------------------------------------------
257  !
258  call t_barrierf('sync_phys_run1', mpicom)
259  call t_startf('phys_run1')
260  call phys_run1(phys_state, dtime, phys_tend, pbuf2d, cam_in, cam_out)
261  call t_stopf('phys_run1')
262 
263 end subroutine cam_run1
264 
265 !
266 !-----------------------------------------------------------------------
267 !
268 
269 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  use physpkg, only: phys_run2
281  use stepon, only: stepon_run2
282  use time_manager, only: is_first_step, is_first_restart_step
283 #if ( defined SPMD )
284  use mpishorthand, only: mpicom
285 #endif
286 
287  type(cam_out_t), intent(inout) :: cam_out(begchunk:endchunk)
288  type(cam_in_t), intent(inout) :: cam_in(begchunk:endchunk)
289 
290  if (offline_driver_dorun) then
291  call offline_driver_run( phys_state, pbuf2d, cam_out, cam_in, dtime )
292  return
293  endif
294 
295  !
296  ! Second phase of physics (after surface model update)
297  !
298  call t_barrierf('sync_phys_run2', mpicom)
299  call t_startf('phys_run2')
300  call phys_run2(phys_state, dtime, phys_tend, pbuf2d, cam_out, cam_in )
301  call t_stopf('phys_run2')
302 
303  !
304  ! Second phase of dynamics (at least couple from physics to dynamics)
305  !
306  call t_barrierf('sync_stepon_run2', mpicom)
307  call t_startf('stepon_run2')
308  call stepon_run2( phys_state, phys_tend, dyn_in, dyn_out )
309 
310  call t_stopf('stepon_run2')
311 
312  if (is_first_step() .or. is_first_restart_step()) then
313  call t_startf('cam_run2_memusage')
314  call t_stopf('cam_run2_memusage')
315  end if
316 end subroutine cam_run2
317 
318 !
319 !-----------------------------------------------------------------------
320 !
321 
322 subroutine cam_run3( cam_out )
323 !-----------------------------------------------------------------------
324 !
325 ! Purpose: Third phase of atmosphere model run method. This consists
326 ! of the third phase of the dynamics. For some dycores
327 ! this will be the actual dynamics run, for others the
328 ! dynamics happens before physics in phase 1.
329 !
330 !-----------------------------------------------------------------------
331  use stepon, only: stepon_run3
332  use time_manager, only: is_first_step, is_first_restart_step
333 #if ( defined SPMD )
334  use mpishorthand, only: mpicom
335 #endif
336 
337  type(cam_out_t), intent(inout) :: cam_out(begchunk:endchunk)
338 !-----------------------------------------------------------------------
339 
340  if (offline_driver_dorun) return
341 
342  !
343  ! Third phase of dynamics
344  !
345  call t_barrierf('sync_stepon_run3', mpicom)
346  call t_startf('stepon_run3')
347  call stepon_run3( dtime, etamid, cam_out, phys_state, dyn_in, dyn_out )
348 
349  call t_stopf('stepon_run3')
350 
351  if (is_first_step() .or. is_first_restart_step()) then
352  call t_startf('cam_run3_memusage')
353  call t_stopf('cam_run3_memusage')
354  end if
355 end subroutine cam_run3
356 
357 !
358 !-----------------------------------------------------------------------
359 !
360 
361 subroutine cam_run4( cam_out, cam_in, rstwr, nlend, &
362  yr_spec, mon_spec, day_spec, sec_spec )
363 
364 !-----------------------------------------------------------------------
365 !
366 ! Purpose: Final phase of atmosphere model run method. This consists
367 ! of all the restart output, history writes, and other
368 ! file output.
369 !
370 !-----------------------------------------------------------------------
371  use cam_history, only: wshist, wrapup
372  use cam_restart, only: cam_write_restart
373  use dycore, only: dycore_is
374 #if ( defined SPMD )
375  use mpishorthand, only: mpicom
376 #endif
377 
378  type(cam_out_t), intent(inout) :: cam_out(begchunk:endchunk)
379  type(cam_in_t) , intent(inout) :: cam_in(begchunk:endchunk)
380  logical , intent(in) :: rstwr ! true => write restart file
381  logical , intent(in) :: nlend ! true => this is final timestep
382  integer , intent(in), optional :: yr_spec ! Simulation year
383  integer , intent(in), optional :: mon_spec ! Simulation month
384  integer , intent(in), optional :: day_spec ! Simulation day
385  integer , intent(in), optional :: sec_spec ! Seconds into current simulation day
386 
387 #if ( defined SPMD )
388  real(r8) :: mpi_wtime
389 #endif
390 !-----------------------------------------------------------------------
391 ! print_step_cost
392 
393  !
394  !----------------------------------------------------------
395  ! History and restart logic: Write and/or dispose history tapes if required
396  !----------------------------------------------------------
397  !
398  if (.not.offline_driver_done) then
399  call t_barrierf('sync_wshist', mpicom)
400  call t_startf('wshist')
401  call wshist()
402  call t_stopf('wshist')
403  endif
404 
405 #if ( defined SPMD )
406  stepon_time_end = mpi_wtime()
407 #endif
408  !
409  ! Write restart files
410  !
411  if (rstwr) then
412  call t_startf('cam_write_restart')
413  if (present(yr_spec).and.present(mon_spec).and.present(day_spec).and.present(sec_spec)) then
414  call cam_write_restart( cam_out, dyn_out, pbuf2d, &
415  yr_spec=yr_spec, mon_spec=mon_spec, day_spec=day_spec, sec_spec= sec_spec )
416  else
417  call cam_write_restart( cam_out, dyn_out, pbuf2d )
418  end if
419  call t_stopf('cam_write_restart')
420  end if
421 
422  call t_startf('cam_run4_wrapup')
423  call wrapup(rstwr, nlend)
424  call t_stopf('cam_run4_wrapup')
425 
426  if (masterproc .and. print_step_cost) then
427  call t_startf('cam_run4_print')
428  call t_stampf(wcend, usrend, sysend)
429  write(iulog,'(a,3f8.3,a)')'Prv timestep wallclock, usr, sys=', &
430  wcend-wcstart, usrend-usrstart, sysend-sysstart, &
431  ' seconds'
432  call t_stopf('cam_run4_print')
433  end if
434 
435 #ifndef UNICOSMP
436  call t_startf('cam_run4_flush')
437  call shr_sys_flush(iulog)
438  call t_stopf('cam_run4_flush')
439 #endif
440 
441 end subroutine cam_run4
442 
443 !
444 !-----------------------------------------------------------------------
445 !
446 
447 subroutine cam_final( cam_out, cam_in )
448 !-----------------------------------------------------------------------
449 !
450 ! Purpose: CAM finalization.
451 !
452 !-----------------------------------------------------------------------
453  use units, only: getunit
454  use time_manager, only: get_nstep, get_step_size
455 #if ( defined SPMD )
456  use mpishorthand, only: mpicom, mpiint, &
457  nsend, nrecv, nwsend, nwrecv
458  use spmd_utils, only: iam, npes
459 #endif
460  use stepon, only: stepon_final
461  use physpkg, only: phys_final
462  use cam_initfiles, only: cam_initfiles_close
464  !
465  ! Arguments
466  !
467  type(cam_out_t), pointer :: cam_out(:) ! Output from CAM to surface
468  type(cam_in_t), pointer :: cam_in(:) ! Input from merged surface to CAM
469 !-----------------------------------------------------------------------
470  !
471  ! Local variables
472  !
473  integer :: nstep ! Current timestep number.
474 
475 #if ( defined SPMD )
476  integer :: iu ! SPMD Statistics output unit number
477  character*24 :: filenam ! SPMD Stats output filename
478  integer :: signal ! MPI message buffer
479 !------------------------------Externals--------------------------------
480  real(r8) :: mpi_wtime
481 #endif
482 
483  call phys_final( phys_state, phys_tend , pbuf2d)
484  call stepon_final(dyn_in, dyn_out)
485 
486  if(nsrest==0) then
487  call cam_initfiles_close()
488  end if
489 
490  call hub2atm_deallocate(cam_in)
491  call atm2hub_deallocate(cam_out)
492 
493 #if ( defined SPMD )
494  if (.false.) then
495  write(iulog,*)'The following stats are exclusive of initialization/boundary datasets'
496  write(iulog,*)'Number of messages sent by proc ',iam,' is ',nsend
497  write(iulog,*)'Number of messages recv by proc ',iam,' is ',nrecv
498  end if
499 #endif
500 
501  ! This flush attempts to ensure that asynchronous diagnostic prints from all
502  ! processes do not get mixed up with the "END OF MODEL RUN" message printed
503  ! by masterproc below. The test-model script searches for this message in the
504  ! output log to figure out if CAM completed successfully. This problem has
505  ! only been observed with the Linux Lahey compiler (lf95) which does not
506  ! support line-buffered output.
507 #ifndef UNICOSMP
508  call shr_sys_flush( 0 ) ! Flush all output to standard error
509  call shr_sys_flush( iulog ) ! Flush all output to standard output
510 #endif
511 
512  if (masterproc) then
513 #if ( defined SPMD )
514  cam_time_end = mpi_wtime()
515 #endif
516  nstep = get_nstep()
517  write(iulog,9300) nstep-1,nstep
518 9300 format (//'Number of completed timesteps:',i6,/,'Time step ',i6, &
519  ' partially done to provide convectively adjusted and ', &
520  'time filtered values for history tape.')
521  write(iulog,*)'------------------------------------------------------------'
522 #if ( defined SPMD )
523  write(iulog,*)
524  write(iulog,*)' Total run time (sec) : ', cam_time_end-cam_time_beg
525  write(iulog,*)' Time Step Loop run time(sec) : ', stepon_time_end-stepon_time_beg
526  if (((nstep-1)-nstep_beg) > 0) then
527  write(iulog,*)' SYPD : ', &
528  236.55_r8/((86400._r8/(dtime*((nstep-1)-nstep_beg)))*(stepon_time_end-stepon_time_beg))
529  endif
530  write(iulog,*)
531 #endif
532  write(iulog,*)'******* END OF MODEL RUN *******'
533  end if
534 
535 
536 #if ( defined SPMDSTATS )
537  if (t_single_filef()) then
538  write(filenam,'(a17)') 'spmdstats_cam.all'
539  iu = getunit()
540  if (iam .eq. 0) then
541  open (unit=iu, file=filenam, form='formatted', status='replace')
542  signal = 1
543  else
544  call mpirecv(signal, 1, mpiint, iam-1, iam, mpicom)
545  open (unit=iu, file=filenam, form='formatted', status='old', position='append')
546  endif
547  write (iu,*)'************ PROCESS ',iam,' ************'
548  write (iu,*)'iam ',iam,' msgs sent =',nsend
549  write (iu,*)'iam ',iam,' msgs recvd=',nrecv
550  write (iu,*)'iam ',iam,' words sent =',nwsend
551  write (iu,*)'iam ',iam,' words recvd=',nwrecv
552  write (iu,*)
553  close(iu)
554  if (iam+1 < npes) then
555  call mpisend(signal, 1, mpiint, iam+1, iam+1, mpicom)
556  endif
557  else
558  iu = getunit()
559  write(filenam,'(a14,i5.5)') 'spmdstats_cam.', iam
560  open (unit=iu, file=filenam, form='formatted', status='replace')
561  write (iu,*)'************ PROCESS ',iam,' ************'
562  write (iu,*)'iam ',iam,' msgs sent =',nsend
563  write (iu,*)'iam ',iam,' msgs recvd=',nrecv
564  write (iu,*)'iam ',iam,' words sent =',nwsend
565  write (iu,*)'iam ',iam,' words recvd=',nwrecv
566  close(iu)
567  endif
568 #endif
569 
570 end subroutine cam_final
571 
572 !
573 !-----------------------------------------------------------------------
574 !
575 
576 end module cam_comp
subroutine, public cam_init(cam_out, cam_in, mpicom_atm, start_ymd, start_tod, ref_ymd, ref_tod, stop_ymd, stop_tod, perpetual_run, perpetual_ymd, calendar)
Definition: cam_comp.F90:73
subroutine, public cam_final(cam_out, cam_in)
Definition: cam_comp.F90:447
subroutine, public cam_run2(cam_out, cam_in)
Definition: cam_comp.F90:269
subroutine, public cam_run1(cam_in, cam_out)
Definition: cam_comp.F90:210
subroutine, public atm2hub_alloc(cam_out)
Initialize objects of type cam_out_t.
Definition: camsrfexch.F90:216
subroutine, public cam_run3(cam_out)
Definition: cam_comp.F90:322
subroutine, public cam_run4(cam_out, cam_in, rstwr, nlend, yr_spec, mon_spec, day_spec, sec_spec)
Definition: cam_comp.F90:361
subroutine, public atm2hub_deallocate(cam_out)
Destroy objects of type cam_out_t.
Definition: camsrfexch.F90:278
CAM export state.
Definition: camsrfexch.F90:34
CAM import state.
Definition: camsrfexch.F90:80
subroutine, public hub2atm_alloc(cam_in)
Initialize objects of type cam_in_t.
Definition: camsrfexch.F90:124
subroutine, public hub2atm_deallocate(cam_in)
Destroy objects of type cam_in_t.
Definition: camsrfexch.F90:289