27 use mom_cpu_clock,
only : cpu_clock_id, cpu_clock_begin, cpu_clock_end
35 use mom_domains,
only : mom_infra_init, mom_infra_end
45 use mom_io,
only : check_nml_error, io_infra_init, io_infra_end
46 use mom_io,
only : append_file, ascii_file, readonly_file, single_file
53 use mom_time_manager,
only :
operator(+),
operator(-),
operator(*),
operator(/)
65 use ensemble_manager_mod,
only : ensemble_manager_init, get_ensemble_size
66 use ensemble_manager_mod,
only : ensemble_pelist_setup
67 use mpp_mod,
only : set_current_pelist => mpp_set_current_pelist
68 use time_interp_external_mod,
only : time_interp_external_init
79 #include <MOM_memory.h>
97 logical :: use_ice_shelf
100 logical :: use_waves = .false.
103 logical :: permit_incr_restart = .true.
111 integer :: nmax=2000000000
117 type(time_type),
target :: time
120 type(time_type) :: master_time
122 type(time_type) :: time1
124 type(time_type) :: start_time
125 type(time_type) :: segment_start_time
126 type(time_type) :: time_end
127 type(time_type) :: restart_time
128 type(time_type) :: time_step_ocean
130 real :: elapsed_time = 0.0
131 logical :: elapsed_time_master
144 real :: t_elapsed_seg
145 integer :: n, n_max, nts, n_last_thermo
146 logical :: diabatic_first, single_step_call
147 type(time_type) :: time2, time_chg
149 integer :: restart_control
157 type(time_type) :: restint
158 type(time_type) :: daymax
161 integer :: date_init(6)=0
162 integer :: date(6)=-1
163 integer :: years=0, months=0, days=0
164 integer :: hours=0, minutes=0, seconds=0
165 integer :: yr, mon, day, hr, mins, sec
168 character(len=9) :: month
169 character(len=16) :: calendar =
'julian'
170 integer :: calendar_type=-1
172 integer :: unit, io_status, ierr
173 integer :: ensemble_size, npes_per, ensemble_info(6)
175 integer,
dimension(0) :: atm_pelist, land_pelist, ice_pelist
176 integer,
dimension(:),
allocatable :: ocean_pelist
177 logical :: unit_in_use
178 integer :: initclock, mainclock, termclock
181 logical :: offline_tracer_mode
192 tracer_flow_csp => null()
198 restart_csp => null()
204 character(len=4),
parameter :: vers_num =
'v2.0'
206 #include "version_variable.h"
207 character(len=40) :: mod_name =
"MOM_main (MOM_driver)"
209 integer :: ocean_nthreads = 1
210 integer :: ncores_per_node = 36
211 logical :: use_hyper_thread = .false.
212 integer :: omp_get_num_threads,omp_get_thread_num,get_cpu_affinity,adder,base_cpu
213 namelist /ocean_solo_nml/ date_init, calendar, months, days, hours, minutes, seconds,&
214 ocean_nthreads, ncores_per_node, use_hyper_thread
220 call mom_infra_init() ;
call io_infra_init()
225 call ensemble_manager_init() ; ensemble_info(:) = get_ensemble_size()
226 ensemble_size=ensemble_info(1) ; npes_per=ensemble_info(2)
227 if (ensemble_size > 1)
then
228 allocate(ocean_pelist(npes_per))
229 call ensemble_pelist_setup(.true., 0, npes_per, 0, 0, atm_pelist, ocean_pelist, &
230 land_pelist, ice_pelist)
231 call set_current_pelist(ocean_pelist)
232 deallocate(ocean_pelist)
236 initclock = cpu_clock_id(
'Initialization' )
237 mainclock = cpu_clock_id(
'Main loop' )
238 termclock = cpu_clock_id(
'Termination' )
239 call cpu_clock_begin(initclock)
241 call mom_mesg(
'======== Model being driven by MOM_driver ========', 2)
246 call open_file(unit,
'input.nml', form=ascii_file, action=readonly_file)
247 read(unit, ocean_solo_nml, iostat=io_status)
248 call close_file(unit)
249 ierr = check_nml_error(io_status,
'ocean_solo_nml')
250 if (years+months+days+hours+minutes+seconds > 0)
then
251 if (is_root_pe())
write(*,ocean_solo_nml)
273 if (
file_exists(trim(dirs%restart_input_dir)//
'ocean_solo.res'))
then
274 call open_file(unit,trim(dirs%restart_input_dir)//
'ocean_solo.res', &
275 form=ascii_file,action=readonly_file)
276 read(unit,*) calendar_type
277 read(unit,*) date_init
279 call close_file(unit)
282 if (calendar(1:6) ==
'JULIAN')
then ; calendar_type = julian
283 elseif (calendar(1:9) ==
'GREGORIAN')
then ; calendar_type = gregorian
284 elseif (calendar(1:6) ==
'NOLEAP')
then ; calendar_type = noleap
285 elseif (calendar(1:10)==
'THIRTY_DAY')
then ; calendar_type = thirty_day_months
286 elseif (calendar(1:11)==
'NO_CALENDAR') then; calendar_type = no_calendar
287 elseif (calendar(1:1) /=
' ')
then
288 call mom_error(fatal,
'MOM_driver: Invalid namelist value '//trim(calendar)//
' for calendar')
290 call mom_error(fatal,
'MOM_driver: No namelist value for calendar')
293 call set_calendar_type(calendar_type)
296 if (sum(date_init) > 0)
then
297 start_time = set_date(date_init(1),date_init(2), date_init(3), &
298 date_init(4),date_init(5),date_init(6))
300 start_time = real_to_time(0.0)
303 call time_interp_external_init
305 if (sum(date) >= 0)
then
307 segment_start_time = set_date(date(1),date(2),date(3),date(4),date(5),date(6))
308 time = segment_start_time
309 call initialize_mom(time, start_time, param_file, dirs, mom_csp, restart_csp, &
310 segment_start_time, offline_tracer_mode=offline_tracer_mode, &
311 diag_ptr=diag, tracer_flow_csp=tracer_flow_csp)
316 call initialize_mom(time, start_time, param_file, dirs, mom_csp, restart_csp, &
317 offline_tracer_mode=offline_tracer_mode, diag_ptr=diag, &
318 tracer_flow_csp=tracer_flow_csp)
321 call get_mom_state_elements(mom_csp, g=grid, gv=gv, us=us, c_p=fluxes%C_p)
326 call extract_surface_state(mom_csp, sfc_state)
329 surface_forcing_csp, tracer_flow_csp)
332 call get_param(param_file, mod_name,
"ICE_SHELF", use_ice_shelf, &
333 "If true, enables the ice shelf model.", default=.false.)
334 if (use_ice_shelf)
then
337 call initialize_ice_shelf(param_file, grid, time, ice_shelf_csp, &
338 diag, forces, fluxes)
341 call get_param(param_file,mod_name,
"USE_WAVES",use_waves,&
342 "If true, enables surface wave modules.",default=.false.)
344 call mom_wave_interface_init(time, grid, gv, us, param_file, waves_csp, diag)
349 segment_start_time = time
353 call log_version(param_file, mod_name, version,
"")
354 call get_param(param_file, mod_name,
"DT", dt, fail_if_missing=.true.)
355 call get_param(param_file, mod_name,
"DT_FORCING", dt_forcing, &
356 "The time step for changing forcing, coupling with other "//&
357 "components, or potentially writing certain diagnostics. "//&
358 "The default value is given by DT.", units=
"s", default=dt)
359 if (offline_tracer_mode)
then
360 call get_param(param_file, mod_name,
"DT_OFFLINE", dt_forcing, &
361 "Time step for the offline time step")
364 ntstep = max(1,ceiling(dt_forcing/dt - 0.001))
366 time_step_ocean = real_to_time(dt_forcing)
367 elapsed_time_master = (abs(dt_forcing - time_type_to_real(time_step_ocean)) > 1.0e-12*dt_forcing)
368 if (elapsed_time_master) &
369 call mom_mesg(
"Using real elapsed time for the master clock.", 2)
372 call get_param(param_file, mod_name,
"TIMEUNIT", time_unit, &
373 "The time unit for DAYMAX, ENERGYSAVEDAYS, and RESTINT.", &
374 units=
"s", default=86400.0)
375 if (years+months+days+hours+minutes+seconds > 0)
then
376 time_end = increment_date(time, years, months, days, hours, minutes, seconds)
377 call mom_mesg(
'Segment run length determined from ocean_solo_nml.', 2)
378 call get_param(param_file, mod_name,
"DAYMAX", daymax, timeunit=time_unit, &
379 default=time_end, do_not_log=.true.)
380 call log_param(param_file, mod_name,
"DAYMAX", daymax, &
381 "The final time of the whole simulation, in units of "//&
382 "TIMEUNIT seconds. This also sets the potential end "//&
383 "time of the present run segment if the end time is "//&
384 "not set via ocean_solo_nml in input.nml.", &
387 call get_param(param_file, mod_name,
"DAYMAX", daymax, &
388 "The final time of the whole simulation, in units of "//&
389 "TIMEUNIT seconds. This also sets the potential end "//&
390 "time of the present run segment if the end time is "//&
391 "not set via ocean_solo_nml in input.nml.", &
392 timeunit=time_unit, fail_if_missing=.true.)
396 call get_param(param_file, mod_name,
"SINGLE_STEPPING_CALL", single_step_call, &
397 "If true, advance the state of MOM with a single step "//&
398 "including both dynamics and thermodynamics. If false "//&
399 "the two phases are advanced with separate calls.", default=.true.)
400 call get_param(param_file, mod_name,
"DT_THERM", dt_therm, &
401 "The thermodynamic and tracer advection time step. "//&
402 "Ideally DT_THERM should be an integer multiple of DT "//&
403 "and less than the forcing or coupling time-step, unless "//&
404 "THERMO_SPANS_COUPLING is true, in which case DT_THERM "//&
405 "can be an integer multiple of the coupling timestep. By "//&
406 "default DT_THERM is set to DT.", units=
"s", default=dt)
407 call get_param(param_file, mod_name,
"DIABATIC_FIRST", diabatic_first, &
408 "If true, apply diabatic and thermodynamic processes, "//&
409 "including buoyancy forcing and mass gain or loss, "//&
410 "before stepping the dynamics forward.", default=.false.)
413 if (time >= time_end)
call mom_error(fatal, &
414 "MOM_driver: The run has been started at or after the end time of the run.")
416 call get_param(param_file, mod_name,
"RESTART_CONTROL", restart_control, &
417 "An integer whose bits encode which restart files are "//&
418 "written. Add 2 (bit 1) for a time-stamped file, and odd "//&
419 "(bit 0) for a non-time-stamped file. A non-time-stamped "//&
420 "restart file is saved at the end of the run segment "//&
421 "for any non-negative value.", default=1)
422 call get_param(param_file, mod_name,
"RESTINT", restint, &
423 "The interval between saves of the restart file in units "//&
424 "of TIMEUNIT. Use 0 (the default) to not save "//&
425 "incremental restart files at all.", default=real_to_time(0.0), &
427 call get_param(param_file, mod_name,
"WRITE_CPU_STEPS", cpu_steps, &
428 "The number of coupled timesteps between writing the cpu "//&
429 "time. If this is not positive, do not check cpu time, and "//&
430 "the segment run-length can not be set via an elapsed CPU time.", &
432 call get_param(param_file,
"MOM",
"DEBUG", debug, &
433 "If true, write out verbose debugging data.", &
434 default=.false., debuggingparam=.true.)
436 call log_param(param_file, mod_name,
"ELAPSED TIME AS MASTER", elapsed_time_master)
439 call mom_write_cputime_init(param_file, dirs%output_directory, start_time, &
447 if (calendar_type /= no_calendar)
then
448 call open_file(unit,
'time_stamp.out', form=ascii_file, action=append_file, &
449 threading=single_file)
450 call get_date(time, date(1), date(2), date(3), date(4), date(5), date(6))
451 month = month_name(date(2))
452 if (is_root_pe())
write(unit,
'(6i4,2x,a3)') date, month(1:3)
453 call get_date(time_end, date(1), date(2), date(3), date(4), date(5), date(6))
454 month = month_name(date(2))
455 if (is_root_pe())
write(unit,
'(6i4,2x,a3)') date, month(1:3)
456 call close_file(unit)
459 if (cpu_steps > 0)
call write_cputime(time, 0, nmax, write_cpu_csp)
461 if (((.not.btest(restart_control,1)) .and. (.not.btest(restart_control,0))) &
462 .or. (restart_control < 0)) permit_incr_restart = .false.
464 if (restint > real_to_time(0.0))
then
466 restart_time = start_time + restint * &
467 (1 + ((time + time_step_ocean) - start_time) / restint)
470 restart_time = time_end + time_step_ocean
471 permit_incr_restart = .false.
474 call cpu_clock_end(initclock)
476 call cpu_clock_begin(mainclock)
479 do while ((ns < nmax) .and. (time < time_end))
483 if (.not. offline_tracer_mode)
then
484 call set_forcing(sfc_state, forces, fluxes, time, time_step_ocean, grid, us, &
492 if (use_ice_shelf)
then
493 call shelf_calc_flux(sfc_state, fluxes, time, dt_forcing, ice_shelf_csp)
496 fluxes%fluxes_used = .false.
497 fluxes%dt_buoy_accum = us%s_to_T*dt_forcing
504 call finish_mom_initialization(time, dirs, mom_csp, restart_csp)
508 time1 = master_time ; time = master_time
509 if (offline_tracer_mode)
then
510 call step_offline(forces, fluxes, sfc_state, time1, dt_forcing, mom_csp)
511 elseif (single_step_call)
then
512 call step_mom(forces, fluxes, sfc_state, time1, dt_forcing, mom_csp, waves=waves_csp)
514 n_max = 1 ;
if (dt_forcing > dt) n_max = ceiling(dt_forcing/dt - 0.001)
515 dt_dyn = dt_forcing / real(n_max)
517 nts = max(1,min(n_max,floor(dt_therm/dt_dyn + 0.001)))
520 time2 = time1 ; t_elapsed_seg = 0.0
522 if (diabatic_first)
then
523 if (modulo(n-1,nts)==0)
then
524 dtdia = dt_dyn*min(ntstep,n_max-(n-1))
525 call step_mom(forces, fluxes, sfc_state, time2, dtdia, mom_csp, &
526 do_dynamics=.false., do_thermodynamics=.true., &
527 start_cycle=(n==1), end_cycle=.false., cycle_length=dt_forcing)
530 call step_mom(forces, fluxes, sfc_state, time2, dt_dyn, mom_csp, &
531 do_dynamics=.true., do_thermodynamics=.false., &
532 start_cycle=.false., end_cycle=(n==n_max), cycle_length=dt_forcing)
534 call step_mom(forces, fluxes, sfc_state, time2, dt_dyn, mom_csp, &
535 do_dynamics=.true., do_thermodynamics=.false., &
536 start_cycle=(n==1), end_cycle=.false., cycle_length=dt_forcing)
538 if ((modulo(n,nts)==0) .or. (n==n_max))
then
539 dtdia = dt_dyn*(n - n_last_thermo)
541 if (n > n_last_thermo+1) &
542 time2 = time2 - real_to_time(dtdia - dt_dyn)
543 call step_mom(forces, fluxes, sfc_state, time2, dtdia, mom_csp, &
544 do_dynamics=.false., do_thermodynamics=.true., &
545 start_cycle=.false., end_cycle=(n==n_max), cycle_length=dt_forcing)
550 t_elapsed_seg = t_elapsed_seg + dt_dyn
551 time2 = time1 + real_to_time(t_elapsed_seg)
557 elapsed_time = elapsed_time + dt_forcing
558 if (elapsed_time > 2e9)
then
564 time_chg = real_to_time(elapsed_time)
565 segment_start_time = segment_start_time + time_chg
566 elapsed_time = elapsed_time - time_type_to_real(time_chg)
568 if (elapsed_time_master)
then
569 master_time = segment_start_time + real_to_time(elapsed_time)
571 master_time = master_time + time_step_ocean
575 if (cpu_steps > 0)
then ;
if (mod(ns, cpu_steps) == 0)
then
576 call write_cputime(time, ns+ntstep-1, nmax, write_cpu_csp)
579 call mech_forcing_diags(forces, dt_forcing, grid, time, diag, surface_forcing_csp%handles)
581 if (.not. offline_tracer_mode)
then
582 if (fluxes%fluxes_used)
then
583 call forcing_diagnostics(fluxes, sfc_state, grid, us, time, &
584 diag, surface_forcing_csp%handles)
586 call mom_error(fatal,
"The solo MOM_driver is not yet set up to handle "//&
587 "thermodynamic time steps that are longer than the coupling timestep.")
592 if ((permit_incr_restart) .and. (fluxes%fluxes_used) .and. &
593 (time + (time_step_ocean/2) > restart_time))
then
594 if (btest(restart_control,1))
then
595 call save_restart(dirs%restart_output_dir, time, grid, &
596 restart_csp, .true., gv=gv)
597 call forcing_save_restart(surface_forcing_csp, grid, time, &
598 dirs%restart_output_dir, .true.)
600 dirs%restart_output_dir, .true.)
602 if (btest(restart_control,0))
then
603 call save_restart(dirs%restart_output_dir, time, grid, &
605 call forcing_save_restart(surface_forcing_csp, grid, time, &
606 dirs%restart_output_dir)
608 dirs%restart_output_dir)
610 restart_time = restart_time + restint
617 call cpu_clock_end(mainclock)
618 call cpu_clock_begin(termclock)
619 if (restart_control>=0)
then
620 if (.not.mom_state_is_synchronized(mom_csp)) &
621 call mom_error(warning,
"End of MOM_main reached with inconsistent "//&
622 "dynamics and advective times. Additional restart fields "//&
623 "that have not been coded yet would be required for reproducibility.")
624 if (.not.fluxes%fluxes_used .and. .not.offline_tracer_mode)
call mom_error(fatal, &
625 "End of MOM_main reached with unused buoyancy fluxes. "//&
626 "For conservation, the ocean restart files can only be "//&
627 "created after the buoyancy forcing is applied.")
629 call save_restart(dirs%restart_output_dir, time, grid, restart_csp, gv=gv)
631 dirs%restart_output_dir)
633 call open_file(unit, trim(dirs%restart_output_dir)//
'ocean_solo.res', nohdrs=.true.)
634 if (is_root_pe())
then
635 write(unit,
'(i6,8x,a)') calendar_type, &
636 '(Calendar: no_calendar=0, thirty_day_months=1, julian=2, gregorian=3, noleap=4)'
638 call get_date(start_time, yr, mon, day, hr, mins, sec)
639 write(unit,
'(6i6,8x,a)') yr, mon, day, hr, mins, sec, &
640 'Model start time: year, month, day, hour, minute, second'
641 call get_date(time, yr, mon, day, hr, mins, sec)
642 write(unit,
'(6i6,8x,a)') yr, mon, day, hr, mins, sec, &
643 'Current model time: year, month, day, hour, minute, second'
645 call close_file(unit)
648 if (is_root_pe())
then
650 INQUIRE(unit,opened=unit_in_use)
651 if (.not.unit_in_use)
exit
653 open(unit,file=
"exitcode",form=
"FORMATTED",status=
"REPLACE",action=
"WRITE")
654 if (time < daymax)
then
663 call diag_mediator_end(time, diag, end_diag_manager=.true.)
664 call cpu_clock_end(termclock)
666 call io_infra_end ;
call mom_infra_end
668 call mom_end(mom_csp)
669 if (use_ice_shelf)
call ice_shelf_end(ice_shelf_csp)