MOM6
MOM_driver.F90
1 program mom_main
2 
3 ! This file is part of MOM6. See LICENSE.md for the license.
4 
5 !********+*********+*********+*********+*********+*********+*********+**
6 !* *
7 !* The Modular Ocean Model, version 6 *
8 !* MOM6 *
9 !* *
10 !* By Alistair Adcroft, Stephen Griffies and Robert Hallberg *
11 !* *
12 !* This file is the ocean-only driver for Version 6 of the Modular *
13 !* Ocean Model (MOM). A separate ocean interface for use with *
14 !* coupled models is provided in ocean_model_MOM.F90. These two *
15 !* drivers are kept in separate directories for convenience of code *
16 !* selection during compiling. This file orchestrates the calls to *
17 !* the MOM initialization routines, to the subroutine that steps *
18 !* the model, and coordinates the output and saving restarts. A *
19 !* description of all of the files that constitute MOM is found in *
20 !* the comments at the beginning of MOM.F90. The arguments of each *
21 !* subroutine are described where the subroutine is defined. *
22 !* *
23 !* Macros written all in capital letters are defined in MOM_memory.h. *
24 !* *
25 !********+*********+*********+*********+*********+*********+*********+**
26 
27  use mom_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end
28  use mom_cpu_clock, only : clock_component
29  use mom_diag_mediator, only : enable_averaging, disable_averaging, diag_mediator_end
30  use mom_diag_mediator, only : diag_ctrl, diag_mediator_close_registration
31  use mom, only : initialize_mom, step_mom, mom_control_struct, mom_end
32  use mom, only : extract_surface_state, finish_mom_initialization
33  use mom, only : get_mom_state_elements, mom_state_is_synchronized
34  use mom, only : step_offline
35  use mom_domains, only : mom_infra_init, mom_infra_end
36  use mom_error_handler, only : mom_error, mom_mesg, warning, fatal, is_root_pe
37  use mom_error_handler, only : calltree_enter, calltree_leave, calltree_waypoint
39  use mom_file_parser, only : close_param_file
40  use mom_forcing_type, only : forcing, mech_forcing, forcing_diagnostics
41  use mom_forcing_type, only : mech_forcing_diags, mom_forcing_chksum, mom_mech_forcing_chksum
42  use mom_get_input, only : directories
43  use mom_grid, only : ocean_grid_type
44  use mom_io, only : file_exists, open_file, close_file
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
47  use mom_restart, only : mom_restart_cs, save_restart
48  use mom_string_functions,only : uppercase
49  use mom_surface_forcing, only : set_forcing, forcing_save_restart
50  use mom_surface_forcing, only : surface_forcing_init, surface_forcing_cs
51  use mom_time_manager, only : time_type, set_date, get_date
52  use mom_time_manager, only : real_to_time, time_type_to_real
53  use mom_time_manager, only : operator(+), operator(-), operator(*), operator(/)
54  use mom_time_manager, only : operator(>), operator(<), operator(>=)
55  use mom_time_manager, only : increment_date, set_calendar_type, month_name
56  use mom_time_manager, only : julian, gregorian, noleap, thirty_day_months
57  use mom_time_manager, only : no_calendar
60  use mom_variables, only : surface
62  use mom_write_cputime, only : write_cputime, mom_write_cputime_init
63  use mom_write_cputime, only : write_cputime_start_clock, write_cputime_cs
64 
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
69 
70  use mom_ice_shelf, only : initialize_ice_shelf, ice_shelf_end, ice_shelf_cs
71  use mom_ice_shelf, only : shelf_calc_flux, add_shelf_forces, ice_shelf_save_restart
72 ! , add_shelf_flux_forcing, add_shelf_flux_IOB
73 
74  use mom_wave_interface, only: wave_parameters_cs, mom_wave_interface_init
75  use mom_wave_interface, only: mom_wave_interface_init_lite, update_surface_waves
76 
77  implicit none
78 
79 #include <MOM_memory.h>
80 
81  ! A structure with the driving mechanical surface forces
82  type(mech_forcing) :: forces
83  ! A structure containing pointers to the thermodynamic forcing fields
84  ! at the ocean surface.
85  type(forcing) :: fluxes
86 
87  ! A structure containing pointers to the ocean surface state fields.
88  type(surface) :: sfc_state
89 
90  ! A pointer to a structure containing metrics and related information.
91  type(ocean_grid_type), pointer :: grid
92  type(verticalGrid_type), pointer :: GV
93  ! A pointer to a structure containing dimensional unit scaling factors.
94  type(unit_scale_type), pointer :: US
95 
96  ! If .true., use the ice shelf model for part of the domain.
97  logical :: use_ice_shelf
98 
99  ! If .true., use surface wave coupling
100  logical :: use_waves = .false.
101 
102  ! This is .true. if incremental restart files may be saved.
103  logical :: permit_incr_restart = .true.
104 
105  integer :: ns
106 
107  ! nmax is the number of iterations after which to stop so that the
108  ! simulation does not exceed its CPU time limit. nmax is determined by
109  ! evaluating the CPU time used between successive calls to write_cputime.
110  ! Initially it is set to be very large.
111  integer :: nmax=2000000000
112 
113  ! A structure containing several relevant directory paths.
114  type(directories) :: dirs
115 
116  ! A suite of time types for use by MOM
117  type(time_type), target :: Time ! A copy of the ocean model's time.
118  ! Other modules can set pointers to this and
119  ! change it to manage diagnostics.
120  type(time_type) :: Master_Time ! The ocean model's master clock. No other
121  ! modules are ever given access to this.
122  type(time_type) :: Time1 ! The value of the ocean model's time at the
123  ! start of a call to step_MOM.
124  type(time_type) :: Start_time ! The start time of the simulation.
125  type(time_type) :: segment_start_time ! The start time of this run segment.
126  type(time_type) :: Time_end ! End time for the segment or experiment.
127  type(time_type) :: restart_time ! The next time to write restart files.
128  type(time_type) :: Time_step_ocean ! A time_type version of dt_forcing.
129 
130  real :: elapsed_time = 0.0 ! Elapsed time in this run [s].
131  logical :: elapsed_time_master ! If true, elapsed time is used to set the
132  ! model's master clock (Time). This is needed
133  ! if Time_step_ocean is not an exact
134  ! representation of dt_forcing.
135  real :: dt_forcing ! The coupling time step [s].
136  real :: dt ! The baroclinic dynamics time step [s].
137  real :: dt_off ! Offline time step [s].
138  integer :: ntstep ! The number of baroclinic dynamics time steps
139  ! within dt_forcing.
140  real :: dt_therm
141  real :: dt_dyn, dtdia, t_elapsed_seg
142  integer :: n, n_max, nts, n_last_thermo
143  logical :: diabatic_first, single_step_call
144  type(time_type) :: Time2, time_chg
145 
146  integer :: Restart_control ! An integer that is bit-tested to determine whether
147  ! incremental restart files are saved and whether they
148  ! have a time stamped name. +1 (bit 0) for generic
149  ! files and +2 (bit 1) for time-stamped files. A
150  ! restart file is saved at the end of a run segment
151  ! unless Restart_control is negative.
152 
153  real :: Time_unit ! The time unit for the following input fields [s].
154  type(time_type) :: restint ! The time between saves of the restart file.
155  type(time_type) :: daymax ! The final day of the simulation.
156 
157  integer :: CPU_steps ! The number of steps between writing CPU time.
158  integer :: date_init(6)=0 ! The start date of the whole simulation.
159  integer :: date(6)=-1 ! Possibly the start date of this run segment.
160  integer :: years=0, months=0, days=0 ! These may determine the segment run
161  integer :: hours=0, minutes=0, seconds=0 ! length, if read from a namelist.
162  integer :: yr, mon, day, hr, mins, sec ! Temp variables for writing the date.
163  type(param_file_type) :: param_file ! The structure indicating the file(s)
164  ! containing all run-time parameters.
165  character(len=9) :: month
166  character(len=16) :: calendar = 'julian'
167  integer :: calendar_type=-1
168 
169  integer :: unit, io_status, ierr
170  integer :: ensemble_size, nPEs_per, ensemble_info(6)
171 
172  integer, dimension(0) :: atm_PElist, land_PElist, ice_PElist
173  integer, dimension(:), allocatable :: ocean_PElist
174  logical :: unit_in_use
175  integer :: initClock, mainClock, termClock
176 
177  logical :: debug ! If true, write verbose checksums for debugging purposes.
178  logical :: offline_tracer_mode ! If false, use the model in prognostic mode where
179  ! the barotropic and baroclinic dynamics, thermodynamics,
180  ! etc. are stepped forward integrated in time.
181  ! If true, then all of the above are bypassed with all
182  ! fields necessary to integrate only the tracer advection
183  ! and diffusion equation are read in from files stored from
184  ! a previous integration of the prognostic model
185 
186  type(MOM_control_struct), pointer :: MOM_CSp => null()
187  !> A pointer to the tracer flow control structure.
188  type(tracer_flow_control_CS), pointer :: &
189  tracer_flow_CSp => null() !< A pointer to the tracer flow control structure
190  type(surface_forcing_CS), pointer :: surface_forcing_CSp => null()
191  type(write_cputime_CS), pointer :: write_CPU_CSp => null()
192  type(ice_shelf_CS), pointer :: ice_shelf_CSp => null()
193  type(wave_parameters_cs), pointer :: waves_CSp => null()
194  type(MOM_restart_CS), pointer :: &
195  restart_CSp => null() !< A pointer to the restart control structure
196  !! that will be used for MOM restart files.
197  type(diag_ctrl), pointer :: &
198  diag => null() !< A pointer to the diagnostic regulatory structure
199  !-----------------------------------------------------------------------
200 
201  character(len=4), parameter :: vers_num = 'v2.0'
202 ! This include declares and sets the variable "version".
203 #include "version_variable.h"
204  character(len=40) :: mod_name = "MOM_main (MOM_driver)" ! This module's name.
205 
206  integer :: ocean_nthreads = 1
207  integer :: ncores_per_node = 36
208  logical :: use_hyper_thread = .false.
209  integer :: omp_get_num_threads,omp_get_thread_num,get_cpu_affinity,adder,base_cpu
210  namelist /ocean_solo_nml/ date_init, calendar, months, days, hours, minutes, seconds,&
211  ocean_nthreads, ncores_per_node, use_hyper_thread
212 
213  !=====================================================================
214 
215  call write_cputime_start_clock(write_cpu_csp)
216 
217  call mom_infra_init() ; call io_infra_init()
218 
219  ! Initialize the ensemble manager. If there are no settings for ensemble_size
220  ! in input.nml(ensemble.nml), these should not do anything. In coupled
221  ! configurations, this all occurs in the external driver.
222  call ensemble_manager_init() ; ensemble_info(:) = get_ensemble_size()
223  ensemble_size=ensemble_info(1) ; npes_per=ensemble_info(2)
224  if (ensemble_size > 1) then ! There are multiple ensemble members.
225  allocate(ocean_pelist(npes_per))
226  call ensemble_pelist_setup(.true., 0, npes_per, 0, 0, atm_pelist, ocean_pelist, &
227  land_pelist, ice_pelist)
228  call set_current_pelist(ocean_pelist)
229  deallocate(ocean_pelist)
230  endif
231 
232  ! These clocks are on the global pelist.
233  initclock = cpu_clock_id( 'Initialization' )
234  mainclock = cpu_clock_id( 'Main loop' )
235  termclock = cpu_clock_id( 'Termination' )
236  call cpu_clock_begin(initclock)
237 
238  call mom_mesg('======== Model being driven by MOM_driver ========', 2)
239  call calltree_waypoint("Program MOM_main, MOM_driver.F90")
240 
241  if (file_exists('input.nml')) then
242  ! Provide for namelist specification of the run length and calendar data.
243  call open_file(unit, 'input.nml', form=ascii_file, action=readonly_file)
244  read(unit, ocean_solo_nml, iostat=io_status)
245  call close_file(unit)
246  ierr = check_nml_error(io_status,'ocean_solo_nml')
247  if (years+months+days+hours+minutes+seconds > 0) then
248  if (is_root_pe()) write(*,ocean_solo_nml)
249  endif
250  endif
251 
252 !$ call omp_set_num_threads(ocean_nthreads)
253 !$ base_cpu = get_cpu_affinity()
254 !$OMP PARALLEL private(adder)
255 !$ if (use_hyper_thread) then
256 !$ if (mod(omp_get_thread_num(),2) == 0) then
257 !$ adder = omp_get_thread_num()/2
258 !$ else
259 !$ adder = ncores_per_node + omp_get_thread_num()/2
260 !$ endif
261 !$ else
262 !$ adder = omp_get_thread_num()
263 !$ endif
264 !$ call set_cpu_affinity (base_cpu + adder)
265 !$ write(6,*) " ocean ", base_cpu, get_cpu_affinity(), adder, omp_get_thread_num(), omp_get_num_threads()
266 !$ call flush(6)
267 !$OMP END PARALLEL
268 
269  ! Read ocean_solo restart, which can override settings from the namelist.
270  if (file_exists(trim(dirs%restart_input_dir)//'ocean_solo.res')) then
271  call open_file(unit,trim(dirs%restart_input_dir)//'ocean_solo.res', &
272  form=ascii_file,action=readonly_file)
273  read(unit,*) calendar_type
274  read(unit,*) date_init
275  read(unit,*) date
276  call close_file(unit)
277  else
278  calendar = uppercase(calendar)
279  if (calendar(1:6) == 'JULIAN') then ; calendar_type = julian
280  elseif (calendar(1:9) == 'GREGORIAN') then ; calendar_type = gregorian
281  elseif (calendar(1:6) == 'NOLEAP') then ; calendar_type = noleap
282  elseif (calendar(1:10)=='THIRTY_DAY') then ; calendar_type = thirty_day_months
283  elseif (calendar(1:11)=='NO_CALENDAR') then; calendar_type = no_calendar
284  elseif (calendar(1:1) /= ' ') then
285  call mom_error(fatal,'MOM_driver: Invalid namelist value '//trim(calendar)//' for calendar')
286  else
287  call mom_error(fatal,'MOM_driver: No namelist value for calendar')
288  endif
289  endif
290  call set_calendar_type(calendar_type)
291 
292 
293  if (sum(date_init) > 0) then
294  start_time = set_date(date_init(1),date_init(2), date_init(3), &
295  date_init(4),date_init(5),date_init(6))
296  else
297  start_time = real_to_time(0.0)
298  endif
299 
300  call time_interp_external_init
301 
302  if (sum(date) >= 0) then
303  ! In this case, the segment starts at a time fixed by ocean_solo.res
304  segment_start_time = set_date(date(1),date(2),date(3),date(4),date(5),date(6))
305  time = segment_start_time
306  call initialize_mom(time, start_time, param_file, dirs, mom_csp, restart_csp, &
307  segment_start_time, offline_tracer_mode=offline_tracer_mode, &
308  diag_ptr=diag, tracer_flow_csp=tracer_flow_csp)
309  else
310  ! In this case, the segment starts at a time read from the MOM restart file
311  ! or left as Start_time by MOM_initialize.
312  time = start_time
313  call initialize_mom(time, start_time, param_file, dirs, mom_csp, restart_csp, &
314  offline_tracer_mode=offline_tracer_mode, diag_ptr=diag, &
315  tracer_flow_csp=tracer_flow_csp)
316  endif
317 
318  call get_mom_state_elements(mom_csp, g=grid, gv=gv, us=us, c_p=fluxes%C_p)
319  master_time = time
320 
321  call calltree_waypoint("done initialize_MOM")
322 
323  call extract_surface_state(mom_csp, sfc_state)
324 
325  call surface_forcing_init(time, grid, us, param_file, diag, &
326  surface_forcing_csp, tracer_flow_csp)
327  call calltree_waypoint("done surface_forcing_init")
328 
329  call get_param(param_file, mod_name, "ICE_SHELF", use_ice_shelf, &
330  "If true, enables the ice shelf model.", default=.false.)
331  if (use_ice_shelf) then
332  ! These arrays are not initialized in most solo cases, but are needed
333  ! when using an ice shelf
334  call initialize_ice_shelf(param_file, grid, time, ice_shelf_csp, &
335  diag, forces, fluxes)
336  endif
337 
338  call get_param(param_file,mod_name,"USE_WAVES",use_waves,&
339  "If true, enables surface wave modules.",default=.false.)
340  if (use_waves) then
341  call mom_wave_interface_init(time, grid, gv, us, param_file, waves_csp, diag)
342  else
343  call mom_wave_interface_init_lite(param_file)
344  endif
345 
346  segment_start_time = time
347  elapsed_time = 0.0
348 
349  ! Read all relevant parameters and write them to the model log.
350  call log_version(param_file, mod_name, version, "")
351  call get_param(param_file, mod_name, "DT", dt, fail_if_missing=.true.)
352  call get_param(param_file, mod_name, "DT_FORCING", dt_forcing, &
353  "The time step for changing forcing, coupling with other "//&
354  "components, or potentially writing certain diagnostics. "//&
355  "The default value is given by DT.", units="s", default=dt)
356  if (offline_tracer_mode) then
357  call get_param(param_file, mod_name, "DT_OFFLINE", dt_forcing, &
358  "Time step for the offline time step")
359  dt = dt_forcing
360  endif
361  ntstep = max(1,ceiling(dt_forcing/dt - 0.001))
362 
363  time_step_ocean = real_to_time(dt_forcing)
364  elapsed_time_master = (abs(dt_forcing - time_type_to_real(time_step_ocean)) > 1.0e-12*dt_forcing)
365  if (elapsed_time_master) &
366  call mom_mesg("Using real elapsed time for the master clock.", 2)
367 
368  ! Determine the segment end time, either from the namelist file or parsed input file.
369  call get_param(param_file, mod_name, "TIMEUNIT", time_unit, &
370  "The time unit for DAYMAX, ENERGYSAVEDAYS, and RESTINT.", &
371  units="s", default=86400.0)
372  if (years+months+days+hours+minutes+seconds > 0) then
373  time_end = increment_date(time, years, months, days, hours, minutes, seconds)
374  call mom_mesg('Segment run length determined from ocean_solo_nml.', 2)
375  call get_param(param_file, mod_name, "DAYMAX", daymax, timeunit=time_unit, &
376  default=time_end, do_not_log=.true.)
377  call log_param(param_file, mod_name, "DAYMAX", daymax, &
378  "The final time of the whole simulation, in units of "//&
379  "TIMEUNIT seconds. This also sets the potential end "//&
380  "time of the present run segment if the end time is "//&
381  "not set via ocean_solo_nml in input.nml.", &
382  timeunit=time_unit)
383  else
384  call get_param(param_file, mod_name, "DAYMAX", daymax, &
385  "The final time of the whole simulation, in units of "//&
386  "TIMEUNIT seconds. This also sets the potential end "//&
387  "time of the present run segment if the end time is "//&
388  "not set via ocean_solo_nml in input.nml.", &
389  timeunit=time_unit, fail_if_missing=.true.)
390  time_end = daymax
391  endif
392 
393  call get_param(param_file, mod_name, "SINGLE_STEPPING_CALL", single_step_call, &
394  "If true, advance the state of MOM with a single step "//&
395  "including both dynamics and thermodynamics. If false "//&
396  "the two phases are advanced with separate calls.", default=.true.)
397  call get_param(param_file, mod_name, "DT_THERM", dt_therm, &
398  "The thermodynamic and tracer advection time step. "//&
399  "Ideally DT_THERM should be an integer multiple of DT "//&
400  "and less than the forcing or coupling time-step, unless "//&
401  "THERMO_SPANS_COUPLING is true, in which case DT_THERM "//&
402  "can be an integer multiple of the coupling timestep. By "//&
403  "default DT_THERM is set to DT.", units="s", default=dt)
404  call get_param(param_file, mod_name, "DIABATIC_FIRST", diabatic_first, &
405  "If true, apply diabatic and thermodynamic processes, "//&
406  "including buoyancy forcing and mass gain or loss, "//&
407  "before stepping the dynamics forward.", default=.false.)
408 
409 
410  if (time >= time_end) call mom_error(fatal, &
411  "MOM_driver: The run has been started at or after the end time of the run.")
412 
413  call get_param(param_file, mod_name, "RESTART_CONTROL", restart_control, &
414  "An integer whose bits encode which restart files are "//&
415  "written. Add 2 (bit 1) for a time-stamped file, and odd "//&
416  "(bit 0) for a non-time-stamped file. A non-time-stamped "//&
417  "restart file is saved at the end of the run segment "//&
418  "for any non-negative value.", default=1)
419  call get_param(param_file, mod_name, "RESTINT", restint, &
420  "The interval between saves of the restart file in units "//&
421  "of TIMEUNIT. Use 0 (the default) to not save "//&
422  "incremental restart files at all.", default=real_to_time(0.0), &
423  timeunit=time_unit)
424  call get_param(param_file, mod_name, "WRITE_CPU_STEPS", cpu_steps, &
425  "The number of coupled timesteps between writing the cpu "//&
426  "time. If this is not positive, do not check cpu time, and "//&
427  "the segment run-length can not be set via an elapsed CPU time.", &
428  default=1000)
429  call get_param(param_file, "MOM", "DEBUG", debug, &
430  "If true, write out verbose debugging data.", &
431  default=.false., debuggingparam=.true.)
432 
433  call log_param(param_file, mod_name, "ELAPSED TIME AS MASTER", elapsed_time_master)
434 
435  if (cpu_steps > 0) &
436  call mom_write_cputime_init(param_file, dirs%output_directory, start_time, &
437  write_cpu_csp)
438 
439  ! Close the param_file. No further parsing of input is possible after this.
440  call close_param_file(param_file)
441  call diag_mediator_close_registration(diag)
442 
443  ! Write out a time stamp file.
444  if (calendar_type /= no_calendar) then
445  call open_file(unit, 'time_stamp.out', form=ascii_file, action=append_file, &
446  threading=single_file)
447  call get_date(time, date(1), date(2), date(3), date(4), date(5), date(6))
448  month = month_name(date(2))
449  if (is_root_pe()) write(unit,'(6i4,2x,a3)') date, month(1:3)
450  call get_date(time_end, 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 close_file(unit)
454  endif
455 
456  if (cpu_steps > 0) call write_cputime(time, 0, nmax, write_cpu_csp)
457 
458  if (((.not.btest(restart_control,1)) .and. (.not.btest(restart_control,0))) &
459  .or. (restart_control < 0)) permit_incr_restart = .false.
460 
461  if (restint > real_to_time(0.0)) then
462  ! restart_time is the next integral multiple of restint.
463  restart_time = start_time + restint * &
464  (1 + ((time + time_step_ocean) - start_time) / restint)
465  else
466  ! Set the time so late that there is no intermediate restart.
467  restart_time = time_end + time_step_ocean
468  permit_incr_restart = .false.
469  endif
470 
471  call cpu_clock_end(initclock) !end initialization
472 
473  call cpu_clock_begin(mainclock) !begin main loop
474 
475  ns = 1
476  do while ((ns < nmax) .and. (time < time_end))
477  call calltree_enter("Main loop, MOM_driver.F90",ns)
478 
479  ! Set the forcing for the next steps.
480  if (.not. offline_tracer_mode) then
481  call set_forcing(sfc_state, forces, fluxes, time, time_step_ocean, grid, us, &
482  surface_forcing_csp)
483  endif
484  if (debug) then
485  call mom_mech_forcing_chksum("After set forcing", forces, grid, us, haloshift=0)
486  call mom_forcing_chksum("After set forcing", fluxes, grid, us, haloshift=0)
487  endif
488 
489  if (use_ice_shelf) then
490  call shelf_calc_flux(sfc_state, fluxes, time, dt_forcing, ice_shelf_csp)
491  call add_shelf_forces(grid, ice_shelf_csp, forces)
492  endif
493  fluxes%fluxes_used = .false.
494  fluxes%dt_buoy_accum = dt_forcing
495 
496  if (use_waves) then
497  call update_surface_waves(grid, gv, us, time, time_step_ocean, waves_csp)
498  endif
499 
500  if (ns==1) then
501  call finish_mom_initialization(time, dirs, mom_csp, restart_csp)
502  endif
503 
504  ! This call steps the model over a time dt_forcing.
505  time1 = master_time ; time = master_time
506  if (offline_tracer_mode) then
507  call step_offline(forces, fluxes, sfc_state, time1, dt_forcing, mom_csp)
508  elseif (single_step_call) then
509  call step_mom(forces, fluxes, sfc_state, time1, dt_forcing, mom_csp, waves=waves_csp)
510  else
511  n_max = 1 ; if (dt_forcing > dt) n_max = ceiling(dt_forcing/dt - 0.001)
512  dt_dyn = dt_forcing / real(n_max)
513 
514  nts = max(1,min(n_max,floor(dt_therm/dt_dyn + 0.001)))
515  n_last_thermo = 0
516 
517  time2 = time1 ; t_elapsed_seg = 0.0
518  do n=1,n_max
519  if (diabatic_first) then
520  if (modulo(n-1,nts)==0) then
521  dtdia = dt_dyn*min(ntstep,n_max-(n-1))
522  call step_mom(forces, fluxes, sfc_state, time2, dtdia, mom_csp, &
523  do_dynamics=.false., do_thermodynamics=.true., &
524  start_cycle=(n==1), end_cycle=.false., cycle_length=dt_forcing)
525  endif
526 
527  call step_mom(forces, fluxes, sfc_state, time2, dt_dyn, mom_csp, &
528  do_dynamics=.true., do_thermodynamics=.false., &
529  start_cycle=.false., end_cycle=(n==n_max), cycle_length=dt_forcing)
530  else
531  call step_mom(forces, fluxes, sfc_state, time2, dt_dyn, mom_csp, &
532  do_dynamics=.true., do_thermodynamics=.false., &
533  start_cycle=(n==1), end_cycle=.false., cycle_length=dt_forcing)
534 
535  if ((modulo(n,nts)==0) .or. (n==n_max)) then
536  dtdia = dt_dyn*(n - n_last_thermo)
537  ! Back up Time2 to the start of the thermodynamic segment.
538  if (n > n_last_thermo+1) &
539  time2 = time2 - real_to_time(dtdia - dt_dyn)
540  call step_mom(forces, fluxes, sfc_state, time2, dtdia, mom_csp, &
541  do_dynamics=.false., do_thermodynamics=.true., &
542  start_cycle=.false., end_cycle=(n==n_max), cycle_length=dt_forcing)
543  n_last_thermo = n
544  endif
545  endif
546 
547  t_elapsed_seg = t_elapsed_seg + dt_dyn
548  time2 = time1 + real_to_time(t_elapsed_seg)
549  enddo
550  endif
551 
552 ! Time = Time + Time_step_ocean
553 ! This is here to enable fractional-second time steps.
554  elapsed_time = elapsed_time + dt_forcing
555  if (elapsed_time > 2e9) then
556  ! This is here to ensure that the conversion from a real to an integer can be accurately
557  ! represented in long runs (longer than ~63 years). It will also ensure that elapsed time
558  ! does not lose resolution of order the timetype's resolution, provided that the timestep and
559  ! tick are larger than 10-5 seconds. If a clock with a finer resolution is used, a smaller
560  ! value would be required.
561  time_chg = real_to_time(elapsed_time)
562  segment_start_time = segment_start_time + time_chg
563  elapsed_time = elapsed_time - time_type_to_real(time_chg)
564  endif
565  if (elapsed_time_master) then
566  master_time = segment_start_time + real_to_time(elapsed_time)
567  else
568  master_time = master_time + time_step_ocean
569  endif
570  time = master_time
571 
572  if (cpu_steps > 0) then ; if (mod(ns, cpu_steps) == 0) then
573  call write_cputime(time, ns+ntstep-1, nmax, write_cpu_csp)
574  endif ; endif
575 
576  call enable_averaging(dt_forcing, time, diag)
577  call mech_forcing_diags(forces, dt_forcing, grid, diag, surface_forcing_csp%handles)
578  call disable_averaging(diag)
579 
580  if (.not. offline_tracer_mode) then
581  if (fluxes%fluxes_used) then
582  call enable_averaging(fluxes%dt_buoy_accum, time, diag)
583  call forcing_diagnostics(fluxes, sfc_state, fluxes%dt_buoy_accum, grid, &
584  diag, surface_forcing_csp%handles)
585  call disable_averaging(diag)
586  else
587  call mom_error(fatal, "The solo MOM_driver is not yet set up to handle "//&
588  "thermodynamic time steps that are longer than the coupling timestep.")
589  endif
590  endif
591 
592 ! See if it is time to write out a restart file - timestamped or not.
593  if ((permit_incr_restart) .and. (fluxes%fluxes_used) .and. &
594  (time + (time_step_ocean/2) > restart_time)) then
595  if (btest(restart_control,1)) then
596  call save_restart(dirs%restart_output_dir, time, grid, &
597  restart_csp, .true., gv=gv)
598  call forcing_save_restart(surface_forcing_csp, grid, time, &
599  dirs%restart_output_dir, .true.)
600  if (use_ice_shelf) call ice_shelf_save_restart(ice_shelf_csp, time, &
601  dirs%restart_output_dir, .true.)
602  endif
603  if (btest(restart_control,0)) then
604  call save_restart(dirs%restart_output_dir, time, grid, &
605  restart_csp, gv=gv)
606  call forcing_save_restart(surface_forcing_csp, grid, time, &
607  dirs%restart_output_dir)
608  if (use_ice_shelf) call ice_shelf_save_restart(ice_shelf_csp, time, &
609  dirs%restart_output_dir)
610  endif
611  restart_time = restart_time + restint
612  endif
613 
614  ns = ns + ntstep
615  call calltree_leave("Main loop")
616  enddo
617 
618  call cpu_clock_end(mainclock)
619  call cpu_clock_begin(termclock)
620  if (restart_control>=0) then
621  if (.not.mom_state_is_synchronized(mom_csp)) &
622  call mom_error(warning, "End of MOM_main reached with inconsistent "//&
623  "dynamics and advective times. Additional restart fields "//&
624  "that have not been coded yet would be required for reproducibility.")
625  if (.not.fluxes%fluxes_used .and. .not.offline_tracer_mode) call mom_error(fatal, &
626  "End of MOM_main reached with unused buoyancy fluxes. "//&
627  "For conservation, the ocean restart files can only be "//&
628  "created after the buoyancy forcing is applied.")
629 
630  call save_restart(dirs%restart_output_dir, time, grid, restart_csp, gv=gv)
631  if (use_ice_shelf) call ice_shelf_save_restart(ice_shelf_csp, time, &
632  dirs%restart_output_dir)
633  ! Write ocean solo restart file.
634  call open_file(unit, trim(dirs%restart_output_dir)//'ocean_solo.res', nohdrs=.true.)
635  if (is_root_pe())then
636  write(unit, '(i6,8x,a)') calendar_type, &
637  '(Calendar: no_calendar=0, thirty_day_months=1, julian=2, gregorian=3, noleap=4)'
638 
639  call get_date(start_time, yr, mon, day, hr, mins, sec)
640  write(unit, '(6i6,8x,a)') yr, mon, day, hr, mins, sec, &
641  'Model start time: year, month, day, hour, minute, second'
642  call get_date(time, yr, mon, day, hr, mins, sec)
643  write(unit, '(6i6,8x,a)') yr, mon, day, hr, mins, sec, &
644  'Current model time: year, month, day, hour, minute, second'
645  endif
646  call close_file(unit)
647  endif
648 
649  if (is_root_pe()) then
650  do unit=10,1967
651  INQUIRE(unit,opened=unit_in_use)
652  if (.not.unit_in_use) exit
653  enddo
654  open(unit,file="exitcode",form="FORMATTED",status="REPLACE",action="WRITE")
655  if (time < daymax) then
656  write(unit,*) 9
657  else
658  write(unit,*) 0
659  endif
660  close(unit)
661  endif
662 
663  call calltree_waypoint("End MOM_main")
664  call diag_mediator_end(time, diag, end_diag_manager=.true.)
665  call cpu_clock_end(termclock)
666 
667  call io_infra_end ; call mom_infra_end
668 
669  call mom_end(mom_csp)
670  if (use_ice_shelf) call ice_shelf_end(ice_shelf_csp)
671 
672 end program mom_main
mom_time_manager
Wraps the FMS time manager functions.
Definition: MOM_time_manager.F90:2
mom_forcing_type::mech_forcing
Structure that contains pointers to the mechanical forcing at the surface used to drive the liquid oc...
Definition: MOM_forcing_type.F90:185
mom_variables::surface
Pointers to various fields which may be used describe the surface state of MOM, and which will be ret...
Definition: MOM_variables.F90:38
mom_write_cputime
A module to monitor the overall CPU time used by MOM6 and project when to stop the model.
Definition: MOM_write_cputime.F90:2
mom_ice_shelf
Implements the thermodynamic aspects of ocean / ice-shelf interactions, along with a crude placeholde...
Definition: MOM_ice_shelf.F90:4
mom_verticalgrid
Provides a transparent vertical ocean grid type and supporting routines.
Definition: MOM_verticalGrid.F90:2
mom_surface_forcing::surface_forcing_cs
Structure containing pointers to the forcing fields that may be used to drive MOM....
Definition: MOM_surface_forcing.F90:71
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
mom_diag_mediator
The subroutines here provide convenient wrappers to the fms diag_manager interfaces with additional d...
Definition: MOM_diag_mediator.F90:3
mom_get_input::directories
Container for paths and parameter file names.
Definition: MOM_get_input.F90:20
mom_string_functions
Handy functions for manipulating strings.
Definition: MOM_string_functions.F90:2
mom::mom_control_struct
Control structure for the MOM module, including the variables that describe the state of the ocean.
Definition: MOM.F90:152
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_io
This module contains I/O framework code.
Definition: MOM_io.F90:2
mom_restart::mom_restart_cs
A restart registry and the control structure for restarts.
Definition: MOM_restart.F90:72
mom_get_input
Reads the only Fortran name list needed to boot-strap the model.
Definition: MOM_get_input.F90:6
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
mom_forcing_type
This module implements boundary forcing for MOM6.
Definition: MOM_forcing_type.F90:2
mom_wave_interface
Interface for surface waves.
Definition: MOM_wave_interface.F90:2
mom_wave_interface::wave_parameters_cs
Container for all surface wave related parameters.
Definition: MOM_wave_interface.F90:47
mom_ice_shelf::ice_shelf_cs
Control structure that contains ice shelf parameters and diagnostics handles.
Definition: MOM_ice_shelf.F90:71
mom_surface_forcing
Functions that calculate the surface wind stresses and fluxes of buoyancy or temperature/salinity and...
Definition: MOM_surface_forcing.F90:8
mom_verticalgrid::verticalgrid_type
Describes the vertical ocean grid, including unit conversion factors.
Definition: MOM_verticalGrid.F90:24
mom_restart
The MOM6 facility for reading and writing restart files, and querying what has been read.
Definition: MOM_restart.F90:2
mom_domains
Describes the decomposed MOM domain and has routines for communications across PEs.
Definition: MOM_domains.F90:2
mom_variables
Provides transparent structures with groups of MOM6 variables and supporting routines.
Definition: MOM_variables.F90:2
mom_cpu_clock
Wraps the MPP cpu clock functions.
Definition: MOM_cpu_clock.F90:2
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_tracer_flow_control
Orchestrates the registration and calling of tracer packages.
Definition: MOM_tracer_flow_control.F90:2
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
mom_tracer_flow_control::tracer_flow_control_cs
The control structure for orchestrating the calling of tracer packages.
Definition: MOM_tracer_flow_control.F90:75
mom
The central module of the MOM6 ocean model.
Definition: MOM.F90:2
mom_forcing_type::forcing
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
Definition: MOM_forcing_type.F90:49
mom_io::file_exists
Indicate whether a file exists, perhaps with domain decomposition.
Definition: MOM_io.F90:68
mom_write_cputime::write_cputime_cs
A control structure that regulates the writing of CPU time.
Definition: MOM_write_cputime.F90:22
mom_file_parser::log_param
An overloaded interface to log the values of various types of parameters.
Definition: MOM_file_parser.F90:96
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25
mom_diag_mediator::diag_ctrl
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Definition: MOM_diag_mediator.F90:239
mom_file_parser::read_param
An overloaded interface to read various types of parameters.
Definition: MOM_file_parser.F90:90