MOM6
MOM_driver.F90
Go to the documentation of this file.
1 program mom_main
2 !***********************************************************************
3 !* GNU General Public License *
4 !* This file is a part of MOM. *
5 !* *
6 !* MOM is free software; you can redistribute it and/or modify it and *
7 !* are expected to follow the terms of the GNU General Public License *
8 !* as published by the Free Software Foundation; either version 2 of *
9 !* the License, or (at your option) any later version. *
10 !* *
11 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
13 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
14 !* License for more details. *
15 !* *
16 !* For the full text of the GNU General Public License, *
17 !* write to: Free Software Foundation, Inc., *
18 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
19 !* or see: http://www.gnu.org/licenses/gpl.html *
20 !***********************************************************************
21 
22 !********+*********+*********+*********+*********+*********+*********+**
23 !* *
24 !* The Modular Ocean Model, version 6 *
25 !* MOM6 *
26 !* *
27 !* By Alistair Adcroft, Stephen Griffies and Robert Hallberg *
28 !* *
29 !* This file is the ocean-only driver for Version 6 of the Modular *
30 !* Ocean Model (MOM). A separate ocean interface for use with *
31 !* coupled models is provided in ocean_model_MOM.F90. These two *
32 !* drivers are kept in separate directories for convenience of code *
33 !* selection during compiling. This file orchestrates the calls to *
34 !* the MOM initialization routines, to the subroutine that steps *
35 !* the model, and coordinates the output and saving restarts. A *
36 !* description of all of the files that constitute MOM is found in *
37 !* the comments at the beginning of MOM.F90. The arguments of each *
38 !* subroutine are described where the subroutine is defined. *
39 !* *
40 !* Macros written all in capital letters are defined in MOM_memory.h. *
41 !* *
42 !********+*********+*********+*********+*********+*********+*********+**
43 
44  use mom_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end
45  use mom_cpu_clock, only : clock_component
50  use mom, only : step_offline
51  use mom_domains, only : mom_infra_init, mom_infra_end
52  use mom_error_handler, only : mom_error, mom_mesg, warning, fatal, is_root_pe
57  use mom_get_input, only : directories
58  use mom_grid, only : ocean_grid_type
59  use mom_io, only : file_exists, open_file, close_file
60  use mom_io, only : check_nml_error, io_infra_init, io_infra_end
61  use mom_io, only : append_file, ascii_file, readonly_file, single_file
62  use mom_restart, only : save_restart
68  use mom_time_manager, only : time_type, set_date, set_time, get_date, time_type_to_real
69  use mom_time_manager, only : operator(+), operator(-), operator(*), operator(/)
70  use mom_time_manager, only : operator(>), operator(<), operator(>=)
71  use mom_time_manager, only : increment_date, set_calendar_type, month_name
72  use mom_time_manager, only : julian, gregorian, noleap, thirty_day_months
73  use mom_time_manager, only : no_calendar
74  use mom_variables, only : surface
78 
79  use ensemble_manager_mod, only : ensemble_manager_init, get_ensemble_size
80  use ensemble_manager_mod, only : ensemble_pelist_setup
81  use mpp_mod, only : set_current_pelist => mpp_set_current_pelist
82 
85 ! , add_shelf_flux_forcing, add_shelf_flux_IOB
86 
87  implicit none
88 
89 #include <MOM_memory.h>
90 
91  ! A structure containing pointers to the ocean forcing fields.
92  type(forcing) :: fluxes
93 
94  ! A structure containing pointers to the ocean surface state fields.
95  type(surface) :: state
96 
97  ! A pointer to a structure containing metrics and related information.
98  type(ocean_grid_type), pointer :: grid
99  type(verticalgrid_type), pointer :: GV
100 
101  ! If .true., use the ice shelf model for part of the domain.
102  logical :: use_ice_shelf
103 
104  ! This is .true. if incremental restart files may be saved.
105  logical :: permit_incr_restart = .true.
106 
107  integer :: n
108 
109  ! nmax is the number of iterations after which to stop so that the
110  ! simulation does not exceed its CPU time limit. nmax is determined by
111  ! evaluating the CPU time used between successive calls to write_energy.
112  ! Initially it is set to be very large.
113  integer :: nmax=2000000000;
114 
115  ! A structure containing several relevant directory paths.
116  type(directories) :: dirs
117 
118  ! A suite of time types for use by MOM
119  type(time_type), target :: Time ! A copy of the ocean model's time.
120  ! Other modules can set pointers to this and
121  ! change it to manage diagnostics.
122  type(time_type) :: Master_Time ! The ocean model's master clock. No other
123  ! modules are ever given access to this.
124  type(time_type) :: Time1 ! The value of the ocean model's time at the
125  ! start of a call to step_MOM.
126  type(time_type) :: Start_time ! The start time of the simulation.
127  type(time_type) :: segment_start_time ! The start time of this run segment.
128  type(time_type) :: Time_end ! End time for the segment or experiment.
129  type(time_type) :: write_energy_time ! The next time to write to the energy file.
130  type(time_type) :: restart_time ! The next time to write restart files.
131  type(time_type) :: Time_step_ocean ! A time_type version of time_step.
132 
133  real :: elapsed_time = 0.0 ! Elapsed time in this run in seconds.
134  logical :: elapsed_time_master ! If true, elapsed time is used to set the
135  ! model's master clock (Time). This is needed
136  ! if Time_step_ocean is not an exact
137  ! representation of time_step.
138  real :: time_step ! The time step of a call to step_MOM in seconds.
139  real :: dt ! The baroclinic dynamics time step, in seconds.
140  real :: dt_off ! Offline time step in seconds
141  integer :: ntstep ! The number of baroclinic dynamics time steps
142  ! within time_step.
143 
144  integer :: Restart_control ! An integer that is bit-tested to determine whether
145  ! incremental restart files are saved and whether they
146  ! have a time stamped name. +1 (bit 0) for generic
147  ! files and +2 (bit 1) for time-stamped files. A
148  ! restart file is saved at the end of a run segment
149  ! unless Restart_control is negative.
150 
151  real :: Time_unit ! The time unit in seconds for the following input fields.
152  type(time_type) :: restint ! The time between saves of the restart file.
153  type(time_type) :: daymax ! The final day of the simulation.
154  type(time_type) :: energysavedays ! The interval between writing the energies
155  ! and other integral quantities of the run.
156 
157  integer :: date_init(6)=0 ! The start date of the whole simulation.
158  integer :: date(6)=-1 ! Possibly the start date of this run segment.
159  integer :: years=0, months=0, days=0 ! These may determine the segment run
160  integer :: hours=0, minutes=0, seconds=0 ! length, if read from a namelist.
161  integer :: yr, mon, day, hr, min, sec ! Temp variables for writing the date.
162  type(param_file_type) :: param_file ! The structure indicating the file(s)
163  ! containing all run-time parameters.
164  character(len=9) :: month
165  character(len=16) :: calendar = 'julian'
166  integer :: calendar_type=-1
167 
168  integer :: unit, io_status, ierr
169  integer :: ensemble_size, nPEs_per, ensemble_info(6)
170 
171  integer, dimension(0) :: atm_PElist, land_PElist, ice_PElist
172  integer, dimension(:), allocatable :: ocean_PElist
173  logical :: unit_in_use
174  integer :: initClock, mainClock, termClock
175 
176  logical :: offline_tracer_mode ! If false, use the model in prognostic mode where
177  ! the barotropic and baroclinic dynamics, thermodynamics,
178  ! etc. are stepped forward integrated in time.
179  ! If true, then all of the above are bypassed with all
180  ! fields necessary to integrate only the tracer advection
181  ! and diffusion equation are read in from files stored from
182  ! a previous integration of the prognostic model
183 
184  type(mom_control_struct), pointer :: MOM_CSp => null()
185  type(surface_forcing_cs), pointer :: surface_forcing_CSp => null()
186  type(sum_output_cs), pointer :: sum_output_CSp => null()
187  type(write_cputime_cs), pointer :: write_CPU_CSp => null()
188  type(ice_shelf_cs), pointer :: ice_shelf_CSp => null()
189  !-----------------------------------------------------------------------
190 
191  character(len=4), parameter :: vers_num = 'v2.0'
192 ! This include declares and sets the variable "version".
193 #include "version_variable.h"
194  character(len=40) :: mod_name = "MOM_main (MOM_driver)" ! This module's name.
195 
196  integer :: ocean_nthreads = 1
197  integer :: ncores_per_node = 36
198  logical :: use_hyper_thread = .false.
199  integer :: omp_get_num_threads,omp_get_thread_num,get_cpu_affinity,adder,base_cpu
200  namelist /ocean_solo_nml/ date_init, calendar, months, days, hours, minutes, seconds,&
201  ocean_nthreads, ncores_per_node, use_hyper_thread
202 
203  !#######################################################################
204 
205  call write_cputime_start_clock(write_cpu_csp)
206 
207  call mom_infra_init() ; call io_infra_init()
208 
209  ! Initialize the ensemble manager. If there are no settings for ensemble_size
210  ! in input.nml(ensemble.nml), these should not do anything. In coupled
211  ! configurations, this all occurs in the external driver.
212  call ensemble_manager_init() ; ensemble_info(:) = get_ensemble_size()
213  ensemble_size=ensemble_info(1) ; npes_per=ensemble_info(2)
214  if (ensemble_size > 1) then ! There are multiple ensemble members.
215  allocate(ocean_pelist(npes_per))
216  call ensemble_pelist_setup(.true., 0, npes_per, 0, 0, atm_pelist, ocean_pelist, &
217  land_pelist, ice_pelist)
218  call set_current_pelist(ocean_pelist)
219  deallocate(ocean_pelist)
220  endif
221 
222  ! These clocks are on the global pelist.
223  initclock = cpu_clock_id( 'Initialization' )
224  mainclock = cpu_clock_id( 'Main loop' )
225  termclock = cpu_clock_id( 'Termination' )
226  call cpu_clock_begin(initclock)
227 
228  call mom_mesg('======== Model being driven by MOM_driver ========', 2)
229  call calltree_waypoint("Program MOM_main, MOM_driver.F90")
230 
231  if (file_exists('input.nml')) then
232  ! Provide for namelist specification of the run length and calendar data.
233  call open_file(unit, 'input.nml', form=ascii_file, action=readonly_file)
234  read(unit, ocean_solo_nml, iostat=io_status)
235  call close_file(unit)
236  ierr = check_nml_error(io_status,'ocean_solo_nml')
237  if (years+months+days+hours+minutes+seconds > 0) then
238  if (is_root_pe()) write(*,ocean_solo_nml)
239  endif
240  endif
241 
242 !$ call omp_set_num_threads(ocean_nthreads)
243 !$OMP PARALLEL private(adder)
244 !$ base_cpu = get_cpu_affinity()
245 !$ if (use_hyper_thread) then
246 !$ if (mod(omp_get_thread_num(),2) == 0) then
247 !$ adder = omp_get_thread_num()/2
248 !$ else
249 !$ adder = ncores_per_node + omp_get_thread_num()/2
250 !$ endif
251 !$ else
252 !$ adder = omp_get_thread_num()
253 !$ endif
254 !$ call set_cpu_affinity (base_cpu + adder)
255 !$ write(6,*) " ocean ", omp_get_num_threads(), get_cpu_affinity(), adder, omp_get_thread_num()
256 !$ call flush(6)
257 !$OMP END PARALLEL
258 
259  ! Read ocean_solo restart, which can override settings from the namelist.
260  if (file_exists(trim(dirs%restart_input_dir)//'ocean_solo.res')) then
261  call open_file(unit,trim(dirs%restart_input_dir)//'ocean_solo.res', &
262  form=ascii_file,action=readonly_file)
263  read(unit,*) calendar_type
264  read(unit,*) date_init
265  read(unit,*) date
266  call close_file(unit)
267  else
268  calendar = uppercase(calendar)
269  if (calendar(1:6) == 'JULIAN') then ; calendar_type = julian
270  else if (calendar(1:9) == 'GREGORIAN') then ; calendar_type = gregorian
271  else if (calendar(1:6) == 'NOLEAP') then ; calendar_type = noleap
272  else if (calendar(1:10)=='THIRTY_DAY') then ; calendar_type = thirty_day_months
273  else if (calendar(1:11)=='NO_CALENDAR') then; calendar_type = no_calendar
274  else if (calendar(1:1) /= ' ') then
275  call mom_error(fatal,'MOM_driver: Invalid namelist value '//trim(calendar)//' for calendar')
276  else
277  call mom_error(fatal,'MOM_driver: No namelist value for calendar')
278  endif
279  endif
280  call set_calendar_type(calendar_type)
281 
282 
283  if (sum(date_init) > 0) then
284  start_time = set_date(date_init(1),date_init(2), date_init(3), &
285  date_init(4),date_init(5),date_init(6))
286  else
287  start_time = set_time(0,days=0)
288  endif
289 
290  if (sum(date) >= 0) then
291  ! In this case, the segment starts at a time fixed by ocean_solo.res
292  segment_start_time = set_date(date(1),date(2),date(3),date(4),date(5),date(6))
293  time = segment_start_time
294  ! Note the not before CS%d
295  call initialize_mom(time, param_file, dirs, mom_csp, segment_start_time, offline_tracer_mode = offline_tracer_mode)
296  else
297  ! In this case, the segment starts at a time read from the MOM restart file
298  ! or left as Start_time by MOM_initialize.
299  time = start_time
300  call initialize_mom(time, param_file, dirs, mom_csp, offline_tracer_mode=offline_tracer_mode)
301  endif
302  fluxes%C_p = mom_csp%tv%C_p ! Copy the heat capacity for consistency.
303 
304  master_time = time
305  grid => mom_csp%G
306  gv => mom_csp%GV
307  call calculate_surface_state(state, mom_csp%u, mom_csp%v, mom_csp%h, &
308  mom_csp%ave_ssh, grid, gv, mom_csp)
309 
310 
311  call surface_forcing_init(time, grid, param_file, mom_csp%diag, &
312  surface_forcing_csp, mom_csp%tracer_flow_CSp)
313  call calltree_waypoint("done surface_forcing_init")
314 
315  call get_param(param_file, mod_name, "ICE_SHELF", use_ice_shelf, &
316  "If true, enables the ice shelf model.", default=.false.)
317  if (use_ice_shelf) then
318  ! These arrays are not initialized in most solo cases, but are needed
319  ! when using an ice shelf
320  call initialize_ice_shelf(param_file, grid, time, ice_shelf_csp, mom_csp%diag, fluxes)
321  endif
322 
323  call mom_sum_output_init(grid, param_file, dirs%output_directory, &
324  mom_csp%ntrunc, start_time, sum_output_csp)
325  call mom_write_cputime_init(param_file, dirs%output_directory, start_time, &
326  write_cpu_csp)
327  call calltree_waypoint("done MOM_sum_output_init")
328 
329  segment_start_time = time
330  elapsed_time = 0.0
331 
332  ! Read all relevant parameters and write them to the model log.
333  call log_version(param_file, mod_name, version, "")
334  call get_param(param_file, mod_name, "DT", dt, fail_if_missing=.true.)
335  call get_param(param_file, mod_name, "DT_FORCING", time_step, &
336  "The time step for changing forcing, coupling with other \n"//&
337  "components, or potentially writing certain diagnostics. \n"//&
338  "The default value is given by DT.", units="s", default=dt)
339  if (offline_tracer_mode) then
340  call get_param(param_file, mod_name, "DT_OFFLINE", time_step, &
341  "Time step for the offline time step")
342  dt = time_step
343  endif
344  ntstep = max(1,ceiling(time_step/dt - 0.001))
345 
346  time_step_ocean = set_time(int(floor(time_step+0.5)))
347  elapsed_time_master = (abs(time_step - time_type_to_real(time_step_ocean)) > 1.0e-12*time_step)
348  if (elapsed_time_master) &
349  call mom_mesg("Using real elapsed time for the master clock.", 2)
350 
351  ! Determine the segment end time, either from the namelist file or parsed input file.
352  call get_param(param_file, mod_name, "TIMEUNIT", time_unit, &
353  "The time unit for DAYMAX, ENERGYSAVEDAYS, and RESTINT.", &
354  units="s", default=86400.0)
355  if (years+months+days+hours+minutes+seconds > 0) then
356  time_end = increment_date(time, years, months, days, hours, minutes, seconds)
357  call mom_mesg('Segment run length determined from ocean_solo_nml.', 2)
358  call get_param(param_file, mod_name, "DAYMAX", daymax, timeunit=time_unit, &
359  default=time_end, do_not_log=.true.)
360  call log_param(param_file, mod_name, "DAYMAX", daymax, &
361  "The final time of the whole simulation, in units of \n"//&
362  "TIMEUNIT seconds. This also sets the potential end \n"//&
363  "time of the present run segment if the end time is \n"//&
364  "not set via ocean_solo_nml in input.nml.", &
365  timeunit=time_unit)
366  else
367  call get_param(param_file, mod_name, "DAYMAX", daymax, &
368  "The final time of the whole simulation, in units of \n"//&
369  "TIMEUNIT seconds. This also sets the potential end \n"//&
370  "time of the present run segment if the end time is \n"//&
371  "not set via ocean_solo_nml in input.nml.", &
372  timeunit=time_unit, fail_if_missing=.true.)
373  time_end = daymax
374  endif
375 
376  if (time >= time_end) call mom_error(fatal, &
377  "MOM_driver: The run has been started at or after the end time of the run.")
378 
379  call get_param(param_file, mod_name, "RESTART_CONTROL", restart_control, &
380  "An integer whose bits encode which restart files are \n"//&
381  "written. Add 2 (bit 1) for a time-stamped file, and odd \n"//&
382  "(bit 0) for a non-time-stamped file. A non-time-stamped \n"//&
383  "restart file is saved at the end of the run segment \n"//&
384  "for any non-negative value.", default=1)
385  call get_param(param_file, mod_name, "RESTINT", restint, &
386  "The interval between saves of the restart file in units \n"//&
387  "of TIMEUNIT. Use 0 (the default) to not save \n"//&
388  "incremental restart files at all.", default=set_time(0), &
389  timeunit=time_unit)
390  call get_param(param_file, mod_name, "ENERGYSAVEDAYS", energysavedays, &
391  "The interval in units of TIMEUNIT between saves of the \n"//&
392  "energies of the run and other globally summed diagnostics.", &
393  default=set_time(int(time_step+0.5)), timeunit=time_unit)
394 
395  call log_param(param_file, mod_name, "ELAPSED TIME AS MASTER", elapsed_time_master)
396 
397  ! Close the param_file. No further parsing of input is possible after this.
398  call close_param_file(param_file)
399  call diag_mediator_close_registration(mom_csp%diag)
400 
401  ! Write out a time stamp file.
402  if (calendar_type /= no_calendar) then
403  call open_file(unit, 'time_stamp.out', form=ascii_file, action=append_file, &
404  threading=single_file)
405  call get_date(time, date(1), date(2), date(3), date(4), date(5), date(6))
406  month = month_name(date(2))
407  if (is_root_pe()) write(unit,'(6i4,2x,a3)') date, month(1:3)
408  call get_date(time_end, date(1), date(2), date(3), date(4), date(5), date(6))
409  month = month_name(date(2))
410  if (is_root_pe()) write(unit,'(6i4,2x,a3)') date, month(1:3)
411  call close_file(unit)
412  endif
413 
414 ! This has been moved inside the loop to be applied when n=1.
415 ! call write_energy(MOM_CSp%u, MOM_CSp%v, MOM_CSp%h, &
416 ! MOM_CSp%tv, Time, 0, grid, GV, sum_output_CSp, MOM_CSp%tracer_flow_CSp)
417  call write_cputime(time, 0, nmax, write_cpu_csp)
418 
419  write_energy_time = start_time + energysavedays * &
420  (1 + (time - start_time) / energysavedays)
421 
422  if (((.not.btest(restart_control,1)) .and. (.not.btest(restart_control,0))) &
423  .or. (restart_control < 0)) permit_incr_restart = .false.
424 
425  if (restint > set_time(0)) then
426  ! restart_time is the next integral multiple of restint.
427  restart_time = start_time + restint * &
428  (1 + ((time + time_step_ocean) - start_time) / restint)
429  else
430  ! Set the time so late that there is no intermediate restart.
431  restart_time = time_end + time_step_ocean
432  permit_incr_restart = .false.
433  endif
434 
435  call cpu_clock_end(initclock) !end initialization
436 
437  call cpu_clock_begin(mainclock) !begin main loop
438 
439  n = 1
440  do while ((n < nmax) .and. (time < time_end))
441  call calltree_enter("Main loop, MOM_driver.F90",n)
442 
443  ! Set the forcing for the next steps.
444  if (.not. offline_tracer_mode) then
445  call set_forcing(state, fluxes, time, time_step_ocean, grid, &
446  surface_forcing_csp)
447  endif
448  if (mom_csp%debug) then
449  call mom_forcing_chksum("After set forcing", fluxes, grid, haloshift=0)
450  endif
451 
452  if (use_ice_shelf) then
453  call shelf_calc_flux(state, fluxes, time, time_step, ice_shelf_csp)
454 !###IS call add_shelf_flux_forcing(fluxes, ice_shelf_CSp)
455 !###IS ! With a coupled ice/ocean run, use the following call.
456 !###IS call add_shelf_flux_IOB(ice_ocean_bdry_type, ice_shelf_CSp)
457  endif
458  fluxes%fluxes_used = .false.
459  fluxes%dt_buoy_accum = time_step
460 
461  if (n==1) then
462  call finish_mom_initialization(time, dirs, mom_csp, fluxes)
463 
464  call write_energy(mom_csp%u, mom_csp%v, mom_csp%h, mom_csp%tv, &
465  time, 0, grid, gv, sum_output_csp, mom_csp%tracer_flow_CSp)
466  endif
467 
468  ! This call steps the model over a time time_step.
469  time1 = master_time ; time = master_time
470  if (offline_tracer_mode) then
471  call step_offline(fluxes, state, time1, time_step, mom_csp)
472  else
473  call step_mom(fluxes, state, time1, time_step, mom_csp)
474  endif
475 
476 ! Time = Time + Time_step_ocean
477 ! This is here to enable fractional-second time steps.
478  elapsed_time = elapsed_time + time_step
479  if (elapsed_time > 2e9) then
480  ! This is here to ensure that the conversion from a real to an integer
481  ! can be accurately represented in long runs (longer than ~63 years).
482  ! It will also ensure that elapsed time does not loose resolution of order
483  ! the timetype's resolution, provided that the timestep and tick are
484  ! larger than 10-5 seconds. If a clock with a finer resolution is used,
485  ! a smaller value would be required.
486  segment_start_time = segment_start_time + set_time(int(floor(elapsed_time)))
487  elapsed_time = elapsed_time - floor(elapsed_time)
488  endif
489  if (elapsed_time_master) then
490  master_time = segment_start_time + set_time(int(floor(elapsed_time+0.5)))
491  else
492  master_time = master_time + time_step_ocean
493  endif
494  time = master_time
495 
496  call enable_averaging(time_step, time, mom_csp%diag)
497  call mech_forcing_diags(fluxes, time_step, grid, mom_csp%diag, &
498  surface_forcing_csp%handles)
499  call disable_averaging(mom_csp%diag)
500 
501  if (.not. offline_tracer_mode) then
502  if (fluxes%fluxes_used) then
503  call enable_averaging(fluxes%dt_buoy_accum, time, mom_csp%diag)
504  call forcing_diagnostics(fluxes, state, fluxes%dt_buoy_accum, grid, &
505  mom_csp%diag, surface_forcing_csp%handles)
506  call accumulate_net_input(fluxes, state, fluxes%dt_buoy_accum, grid, sum_output_csp)
507  call disable_averaging(mom_csp%diag)
508  else
509  call mom_error(fatal, "The solo MOM_driver is not yet set up to handle "//&
510  "thermodynamic time steps that are longer than the coupling timestep.")
511  endif
512  endif
513 
514 ! See if it is time to write out the energy.
515  if ((time + (time_step_ocean/2) > write_energy_time) .and. &
516  (mom_csp%t_dyn_rel_adv == 0.0)) then
517  call write_energy(mom_csp%u, mom_csp%v, mom_csp%h, &
518  mom_csp%tv, time, n+ntstep-1, grid, gv, sum_output_csp, &
519  mom_csp%tracer_flow_CSp)
520  call write_cputime(time, n+ntstep-1, nmax, write_cpu_csp)
521  write_energy_time = write_energy_time + energysavedays
522  endif
523 
524 ! See if it is time to write out a restart file - timestamped or not.
525  if ((permit_incr_restart) .and. (fluxes%fluxes_used) .and. &
526  (time + (time_step_ocean/2) > restart_time)) then
527  if (btest(restart_control,1)) then
528  call save_restart(dirs%restart_output_dir, time, grid, &
529  mom_csp%restart_CSp, .true., gv=gv)
530  call forcing_save_restart(surface_forcing_csp, grid, time, &
531  dirs%restart_output_dir, .true.)
532  if (use_ice_shelf) call ice_shelf_save_restart(ice_shelf_csp, time, &
533  dirs%restart_output_dir, .true.)
534  endif
535  if (btest(restart_control,0)) then
536  call save_restart(dirs%restart_output_dir, time, grid, &
537  mom_csp%restart_CSp, gv=gv)
538  call forcing_save_restart(surface_forcing_csp, grid, time, &
539  dirs%restart_output_dir)
540  if (use_ice_shelf) call ice_shelf_save_restart(ice_shelf_csp, time, &
541  dirs%restart_output_dir)
542  endif
543  restart_time = restart_time + restint
544  endif
545 
546  n = n + ntstep
547  call calltree_leave("Main loop")
548  enddo
549 
550  call cpu_clock_end(mainclock)
551  call cpu_clock_begin(termclock)
552  if (restart_control>=0) then
553  if (mom_csp%t_dyn_rel_adv > 0.0) call mom_error(warning, "End of MOM_main reached "//&
554  "with inconsistent dynamics and advective times. Additional restart fields "//&
555  "that have not been coded yet would be required for reproducibility.")
556  if (.not.fluxes%fluxes_used .and. .not.offline_tracer_mode) call mom_error(fatal, &
557  "End of MOM_main reached with unused buoyancy fluxes. "//&
558  "For conservation, the ocean restart files can only be "//&
559  "created after the buoyancy forcing is applied.")
560 
561  call save_restart(dirs%restart_output_dir, time, grid, mom_csp%restart_CSp, gv=gv)
562  if (use_ice_shelf) call ice_shelf_save_restart(ice_shelf_csp, time, &
563  dirs%restart_output_dir)
564  ! Write ocean solo restart file.
565  call open_file(unit, trim(dirs%restart_output_dir)//'ocean_solo.res', nohdrs=.true.)
566  if (is_root_pe())then
567  write(unit, '(i6,8x,a)') calendar_type, &
568  '(Calendar: no_calendar=0, thirty_day_months=1, julian=2, gregorian=3, noleap=4)'
569 
570  call get_date(start_time, yr, mon, day, hr, min, sec)
571  write(unit, '(6i6,8x,a)') yr, mon, day, hr, min, sec, &
572  'Model start time: year, month, day, hour, minute, second'
573  call get_date(time, yr, mon, day, hr, min, sec)
574  write(unit, '(6i6,8x,a)') yr, mon, day, hr, min, sec, &
575  'Current model time: year, month, day, hour, minute, second'
576  end if
577  call close_file(unit)
578  endif
579 
580  if (is_root_pe()) then
581  do unit=10,1967
582  INQUIRE(unit,opened=unit_in_use)
583  if (.not.unit_in_use) exit
584  enddo
585  open(unit,file="exitcode",form="FORMATTED",status="REPLACE",action="WRITE")
586  if (time < daymax) then
587  write(unit,*) 9
588  else
589  write(unit,*) 0
590  endif
591  close(unit)
592  endif
593 
594  call calltree_waypoint("End MOM_main")
595  call diag_mediator_end(time, mom_csp%diag, end_diag_manager=.true.)
596  call cpu_clock_end(termclock)
597 
598  call io_infra_end ; call mom_infra_end
599 
600  call mom_end(mom_csp)
601  if (use_ice_shelf) call ice_shelf_end(ice_shelf_csp)
602 
603 end program mom_main
subroutine, public set_forcing(state, fluxes, day_start, day_interval, G, CS)
subroutine, public diag_mediator_close_registration(diag_CS)
The following structure contains pointers to various fields which may be used describe the surface st...
subroutine, public write_cputime_start_clock(CS)
subroutine, public initialize_mom(Time, param_file, dirs, CS, Time_in, offline_tracer_mode)
This subroutine initializes MOM.
Definition: MOM.F90:1480
subroutine, public mom_write_cputime_init(param_file, directory, Input_start_time, CS)
This module implements boundary forcing for MOM6.
subroutine, public enable_averaging(time_int_in, time_end_in, diag_cs)
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
subroutine, public write_cputime(day, n, nmax, CS)
This is the main routine for MOM.
Definition: MOM.F90:2
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine, public mom_forcing_chksum(mesg, fluxes, G, haloshift)
Write out chksums for basic state variables.
subroutine, public calltree_leave(mesg)
Writes a message about leaving a subroutine if call tree reporting is active.
This module contains I/O framework code.
Definition: MOM_io.F90:2
subroutine, public diag_mediator_end(time, diag_CS, end_diag_manager)
subroutine, public ice_shelf_end(CS)
Deallocates all memory associated with this module.
subroutine, public accumulate_net_input(fluxes, state, dt, G, CS)
This subroutine accumates the net input of volume, and perhaps later salt and heat, through the ocean surface for use in diagnosing conservation.
Implements the thermodynamic aspects of ocean / ice-shelf interactions,.
subroutine, public calltree_waypoint(mesg, n)
Writes a message about reaching a milestone if call tree reporting is active.
subroutine, public write_energy(u, v, h, tv, day, n, G, GV, CS, tracer_CSp)
This subroutine calculates and writes the total model energy, the energy and mass of each layer...
character(len=len(input_string)) function, public uppercase(input_string)
subroutine, public close_param_file(CS, quiet_close, component)
subroutine, public ice_shelf_save_restart(CS, Time, directory, time_stamped, filename_suffix)
Save the ice shelf restart file.
logical function, public is_root_pe()
subroutine, public forcing_diagnostics(fluxes, state, dt, G, diag, handles)
Offer buoyancy forcing fields for diagnostics for those fields registered as part of register_forcing...
subroutine, public forcing_save_restart(CS, G, Time, directory, time_stamped, filename_suffix)
Control structure for this module.
Definition: MOM.F90:148
program mom_main
Definition: MOM_driver.F90:1
subroutine, public initialize_ice_shelf(param_file, ocn_grid, Time, CS, diag, fluxes, Time_in, solo_ice_sheet_in)
Initializes shelf model data, parameters and diagnostics.
Structure that contains pointers to the boundary forcing used to drive the liquid ocean simulated by ...
subroutine, public mom_mesg(message, verb, all_print)
Control structure that contains ice shelf parameters and diagnostics handles.
subroutine, public calculate_surface_state(state, u, v, h, ssh, G, GV, CS)
This subroutine sets the surface (return) properties of the ocean model by setting the appropriate fi...
Definition: MOM.F90:3441
subroutine, public step_offline(fluxes, state, Time_start, time_interval, CS)
step_offline is the main driver for running tracers offline in MOM6. This has been primarily develope...
Definition: MOM.F90:1294
subroutine, public save_restart(directory, time, G, CS, time_stamped, filename, GV)
subroutine, public step_mom(fluxes, state, Time_start, time_interval, CS)
This subroutine orchestrates the time stepping of MOM. The adiabatic dynamics are stepped by calls to...
Definition: MOM.F90:466
subroutine, public disable_averaging(diag_cs)
subroutine, public mom_end(CS)
End of model.
Definition: MOM.F90:3746
subroutine, public surface_forcing_init(Time, G, param_file, diag, CS, tracer_flow_CSp)
subroutine, public mom_error(level, message, all_print)
subroutine, public mech_forcing_diags(fluxes, dt, G, diag, handles)
Offer mechanical forcing fields for diagnostics for those fields registered as part of register_forci...
subroutine, public finish_mom_initialization(Time, dirs, CS, fluxes)
This subroutine finishes initializing MOM and writes out the initial conditions.
Definition: MOM.F90:2345
subroutine, public shelf_calc_flux(state, fluxes, Time, time_step, CS)
Calculates fluxes between the ocean and ice-shelf using the three-equations formulation (optional to ...
subroutine, public mom_sum_output_init(G, param_file, directory, ntrnc, Input_start_time, CS)
subroutine, public calltree_enter(mesg, n)
Writes a message about entering a subroutine if call tree reporting is active.