MOM6
ocn_comp_mct.F90
Go to the documentation of this file.
1 !> This is the main driver for MOM6 in CIME
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 ! mct modules
7 use esmf, only: esmf_clock, esmf_time, esmf_timeinterval
8 use esmf, only: esmf_clockget, esmf_timeget, esmf_timeintervalget
9 use seq_cdata_mod, only: seq_cdata, seq_cdata_setptrs
10 use seq_flds_mod, only: seq_flds_x2o_fields, seq_flds_o2x_fields
11 use mct_mod, only: mct_gsmap, mct_gsmap_init, mct_gsmap_lsize, &
12  mct_gsmap_orderedpoints
13 use mct_mod, only: mct_avect, mct_avect_init, mct_avect_zero, &
14  mct_avect_nrattr
15 use mct_mod, only: mct_ggrid, mct_ggrid_init, mct_ggrid_importrattr, &
16  mct_ggrid_importiattr
17 use seq_infodata_mod, only: seq_infodata_type, seq_infodata_getdata, &
18  seq_infodata_start_type_start, seq_infodata_start_type_cont, &
19  seq_infodata_start_type_brnch, seq_infodata_putdata
20 use seq_comm_mct, only: seq_comm_name, seq_comm_inst, seq_comm_suffix
21 use seq_timemgr_mod, only: seq_timemgr_eclockgetdata, seq_timemgr_restartalarmison
22 use perf_mod, only: t_startf, t_stopf
23 use shr_file_mod, only: shr_file_getunit, shr_file_freeunit, shr_file_setio, &
24  shr_file_getlogunit, shr_file_getloglevel, &
25  shr_file_setlogunit, shr_file_setloglevel
26 
27 ! MOM6 modules
28 use mom, only: extract_surface_state
29 use mom_variables, only: surface
30 use mom_domains, only: mom_infra_init
31 use mom_restart, only: save_restart
33 use mom_domains, only: num_pes, root_pe, pe_here
35 use mom_error_handler, only: mom_error, fatal, is_root_pe, warning
36 use mom_time_manager, only: time_type, set_date, set_time, set_calendar_type, noleap
37 use mom_time_manager, only: operator(+), operator(-), operator(*), operator(/)
38 use mom_time_manager, only: operator(==), operator(/=), operator(>), get_time
41 use mom_eos, only: gsw_sp_from_sr, gsw_pt_from_ct
43 use mom_domains, only: agrid, bgrid_ne, cgrid_ne, pass_vector
44 use mpp_domains_mod, only: mpp_get_compute_domain
45 
46 ! Previously inlined - now in separate modules
52 
53 ! FMS modules
54 use time_interp_external_mod, only : time_interp_external
55 
56 ! MCT indices structure and import and export routines that access mom data
58 
59 ! GFDL coupler modules
60 use coupler_types_mod, only : coupler_type_spawn
61 use coupler_types_mod, only : coupler_type_initialized, coupler_type_copy_data
62 
63 ! By default make data private
64 implicit none; private
65 
66 #include <MOM_memory.h>
67 
68 ! Public member functions
69 public :: ocn_init_mct
70 public :: ocn_run_mct
71 public :: ocn_final_mct
72 
73 ! Private member functions
74 private :: ocn_setgsmap_mct
75 private :: ocn_domain_mct
76 private :: get_runtype
77 private :: ocean_model_init_sfc
78 
79 ! Flag for debugging
80 logical, parameter :: debug=.true.
81 
82 !> Control structure for this module
84  type(ocean_state_type), pointer :: ocn_state => null() !< The private state of ocean
85  type(ocean_public_type), pointer :: ocn_public => null() !< The public state of ocean
86  type(ocean_grid_type), pointer :: grid => null() !< The grid structure
87  type(seq_infodata_type), pointer :: infodata !< The input info type
88  type(cpl_indices_type) :: ind !< Variable IDs
89  logical :: sw_decomp !< Controls whether shortwave is decomposed into 4 components
90  real :: c1, c2, c3, c4 !< Coeffs. used in the shortwave decomposition i/o
91  integer :: stdout !< standard output unit. (by default, points to ocn.log.* )
92  character(len=384) :: pointer_filename !< Name of the ascii file that contains the path
93  !! and filename of the latest restart file.
94 end type mct_mom_data
95 
96 type(mct_mom_data) :: glb !< global structure
98 
99 !=======================================================================
100 contains
101 !=======================================================================
102 
103 !> This subroutine initializes MOM6.
104 subroutine ocn_init_mct( EClock, cdata_o, x2o_o, o2x_o, NLFilename )
105  type(esmf_clock), intent(inout) :: eclock !< Time and time step ? \todo Why must this
106  !! be intent(inout)?
107  type(seq_cdata) , intent(inout) :: cdata_o !< Input parameters
108  type(mct_avect) , intent(inout) :: x2o_o !< Fluxes from coupler to ocean, computed by ocean
109  type(mct_avect) , intent(inout) :: o2x_o !< Fluxes from ocean to coupler, computed by ocean
110  character(len=*), optional , intent(in) :: nlfilename !< Namelist filename
111 
112  ! local variable
113  type(time_type) :: time0 !< Start time of coupled model's calendar.
114  type(time_type) :: time_start !< The time at which to initialize the ocean model
115  type(esmf_time) :: time_var !< ESMF_time variable to query time
116  type(esmf_time) :: time_in_esmf !< Initial time for ocean
117  type(esmf_timeinterval) :: ocn_cpl_interval !< Ocean coupling interval
118  integer :: ncouple_per_day
119  integer :: year, month, day, hour, minute, seconds, seconds_n, seconds_d, rc
120  character(len=240) :: runid !< Run ID
121  character(len=32) :: runtype !< Run type
122  character(len=240) :: restartfile !< Path/Name of restart file
123  integer :: nu !< i/o unit to read pointer file
124  character(len=240) :: restart_pointer_file !< File name for restart pointer file
125  character(len=240) :: restartpath !< Path of the restart file
126  integer :: mpicom_ocn !< MPI ocn communicator
127  integer :: npes, pe0 !< # of processors and current processor
128  integer :: i, errorcode
129  integer :: lsize, nsend, nrecv
130  logical :: ldiag_cpl = .false.
131  integer :: isc, iec, jsc, jec, ni, nj !< Indices for the start and end of the domain
132  !! in the x and y dir., respectively.
133  ! runtime params
134  type(param_file_type) :: param_file !< A structure to parse for run-time parameters
135  type(directories) :: dirs_tmp !< A structure containing several relevant directory paths
136  character(len=40) :: mdl = "ocn_comp_mct" !< This module's name.
137 
138  ! mct variables (these are local for now)
139  integer :: mom_mct_id
140  type(mct_gsmap), pointer :: mom_mct_gsmap => null() !< 2d, points to cdata
141  type(mct_ggrid), pointer :: mom_mct_dom => null() !< 2d, points to cdata
142  type(mct_gsmap) :: mom_mct_gsmap3d !< for 3d streams, local
143  type(mct_ggrid) :: mom_mct_dom3d !< for 3d streams, local
144 
145  ! time management
146  integer :: ocn_cpl_dt !< one ocn coupling interval in seconds. (to be received from cesm)
147  real (kind=8) :: mom_cpl_dt !< one ocn coupling interval in seconds. (internal)
148  real (kind=8), parameter :: &
149  seconds_in_minute = 60.0d0, &
150  seconds_in_hour = 3600.0d0, &
151  seconds_in_day = 86400.0d0, &
152  minutes_in_hour = 60.0d0
153 
154  character(len=99) :: ocn_modelio_name !< ocn model input namelist filename
155  integer :: shrlogunit !< original log file unit
156  integer :: shrloglev !< original log level
157 
158  integer(kind=4) :: inst_index !< instance control vars (these are local for now)
159  character(len=16) :: inst_name
160  character(len=16) :: inst_suffix
161 
162  ! TODO: Change the following vars with the corresponding MOM6 vars
163  integer :: km=1 !< Number of vertical levels
164  !logical :: lsend_precip_fact !< If T,send precip_fact to cpl for use in fw balance
165  !! (partially-coupled option)
166  character(len=128) :: err_msg !< Error message
167 
168  ! set the cdata pointers:
169  call seq_cdata_setptrs(cdata_o, id=mom_mct_id, mpicom=mpicom_ocn, &
170  gsmap=mom_mct_gsmap, dom=mom_mct_dom, infodata=glb%infodata)
171 
172  ! Determine attribute vector indices
173  call cpl_indices_init(glb%ind)
174 
175  call seq_infodata_getdata( glb%infodata, case_name=runid )
176 
177  ! instance control
178  inst_name = seq_comm_name(mom_mct_id)
179  inst_index = seq_comm_inst(mom_mct_id)
180  inst_suffix = seq_comm_suffix(mom_mct_id)
181 
182  call t_startf('MOM_init')
183 
184  ! Initialize MOM6 comm
185  call mom_infra_init(mpicom_ocn)
186 
187  ! initialize ocn log file
188  if (is_root_pe()) then
189 
190  ! get original log file properties
191  call shr_file_getlogunit (shrlogunit)
192  call shr_file_getloglevel(shrloglev)
193 
194  glb%stdout = shr_file_getunit() ! get an unused unit number
195 
196  ! open the ocn_modelio.nml file and then open a log file associated with stdout
197  ocn_modelio_name = 'ocn_modelio.nml' // trim(inst_suffix)
198  call shr_file_setio(ocn_modelio_name,glb%stdout)
199 
200  ! set the shr log io unit number
201  call shr_file_setlogunit(glb%stdout)
202  end if
203 
204  call set_calendar_type(noleap) !TODO: confirm this
205 
206  ! Get start time
207  call esmf_clockget(eclock, starttime=time_var, rc=rc)
208  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
209  time0 = set_date(year, month, day, hour, minute, seconds, err_msg=err_msg)
210 
211  ! Get current time
212  call esmf_clockget(eclock, currtime=time_var, rc=rc)
213  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
214  time_start = set_date(year, month, day, hour, minute, seconds, err_msg=err_msg)
215 
216  ! Debugging clocks
217  if (debug .and. is_root_pe()) then
218  write(glb%stdout,*) 'ocn_init_mct, current time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
219 
220  call esmf_clockget(eclock, starttime=time_var, rc=rc)
221  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
222  write(glb%stdout,*) 'ocn_init_mct, start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
223 
224  call esmf_clockget(eclock, stoptime=time_var, rc=rc)
225  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
226  write(glb%stdout,*) 'ocn_init_mct, stop time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
227 
228  call esmf_clockget(eclock, prevtime=time_var, rc=rc)
229  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
230  write(glb%stdout,*) 'ocn_init_mct, previous time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
231 
232  call esmf_clockget(eclock, timestep=ocn_cpl_interval, rc=rc)
233  call esmf_timeintervalget(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
234  write(glb%stdout,*) 'ocn_init_mct, time step: y,m,d-',year,month,day,'s,sn,sd=',seconds,seconds_n,seconds_d
235  endif
236 
237  npes = num_pes()
238  pe0 = root_pe()
239 
240  allocate(glb%ocn_public)
241  glb%ocn_public%is_ocean_PE = .true.
242 
243  allocate(glb%ocn_public%pelist(npes))
244  glb%ocn_public%pelist(:) = (/(i,i=pe0,pe0+npes)/)
245  ! \todo Set other bits of glb$ocn_public
246 
247  ! This include declares and sets the variable "version".
248  ! read useful runtime params
249  call get_mom_input(param_file, dirs_tmp, check_params=.false.)
250  !call log_version(param_file, mdl, version, "")
251 
252  call get_param(param_file, mdl, "POINTER_FILENAME", glb%pointer_filename, &
253  "Name of the ascii file that contains the path and filename of" // &
254  " the latest restart file.", default='rpointer.ocn')
255 
256  call get_param(param_file, mdl, "SW_DECOMP", glb%sw_decomp, &
257  "If True, read coeffs c1, c2, c3 and c4 and decompose" // &
258  "the net shortwave radiation (SW) into four components:\n" // &
259  "visible, direct shortwave = c1 * SW \n" // &
260  "visible, diffuse shortwave = c2 * SW \n" // &
261  "near-IR, direct shortwave = c3 * SW \n" // &
262  "near-IR, diffuse shortwave = c4 * SW", default=.true.)
263 
264  if (glb%sw_decomp) then
265  call get_param(param_file, mdl, "SW_c1", glb%c1, &
266  "Coeff. used to convert net shortwave rad. into "//&
267  "visible, direct shortwave.", units="nondim", default=0.285)
268 
269  call get_param(param_file, mdl, "SW_c2", glb%c2, &
270  "Coeff. used to convert net shortwave rad. into "//&
271  "visible, diffuse shortwave.", units="nondim", default=0.285)
272 
273  call get_param(param_file, mdl, "SW_c3", glb%c3, &
274  "Coeff. used to convert net shortwave rad. into "//&
275  "near-IR, direct shortwave.", units="nondim", default=0.215)
276 
277  call get_param(param_file, mdl, "SW_c4", glb%c4, &
278  "Coeff. used to convert net shortwave rad. into "//&
279  "near-IR, diffuse shortwave.", units="nondim", default=0.215)
280  else
281  glb%c1 = 0.0; glb%c2 = 0.0; glb%c3 = 0.0; glb%c4 = 0.0
282  endif
283 
284  ! Close param file before it gets opened by ocean_model_init again.
285  call close_param_file(param_file)
286 
287  ! Initialize the MOM6 model
288  runtype = get_runtype()
289  if (runtype == "initial") then
290  ! startup (new run) - 'n' is needed below since we don't specify input_filename in input.nml
291  call ocean_model_init(glb%ocn_public, glb%ocn_state, time0, time_start, input_restart_file = 'n')
292  else ! hybrid or branch or continuos runs
293  ! get output path root
294  call seq_infodata_getdata( glb%infodata, outpathroot=restartpath )
295  ! read name of restart file in the pointer file
296  nu = shr_file_getunit()
297  restart_pointer_file = trim(glb%pointer_filename)
298  if (is_root_pe()) write(glb%stdout,*) 'Reading ocn pointer file: ',restart_pointer_file
299  open(nu, file=restart_pointer_file, form='formatted', status='unknown')
300  read(nu,'(a)') restartfile
301  close(nu)
302  !restartfile = trim(restartpath) // trim(restartfile)
303  if (is_root_pe()) then
304  write(glb%stdout,*) 'Reading restart file: ',trim(restartfile)
305  end if
306  call shr_file_freeunit(nu)
307  call ocean_model_init(glb%ocn_public, glb%ocn_state, time0, time_start, input_restart_file=trim(restartfile))
308  endif
309  if (is_root_pe()) then
310  write(glb%stdout,'(/12x,a/)') '======== COMPLETED MOM INITIALIZATION ========'
311  end if
312 
313  ! Initialize ocn_state%sfc_state out of sight
314  call ocean_model_init_sfc(glb%ocn_state, glb%ocn_public)
315 
316  ! Store pointers to components inside MOM
317  glb%grid => glb%ocn_state%grid
318 
319  ! Allocate IOB data type (needs to be called after glb%grid is set)
320  !write(6,*)'DEBUG: isc,iec,jsc,jec= ',glb%grid%isc, glb%grid%iec, glb%grid%jsc, glb%grid%jec
321  call iob_allocate(ice_ocean_boundary, glb%grid%isc, glb%grid%iec, glb%grid%jsc, glb%grid%jec)
322 
323  call t_stopf('MOM_init')
324 
325  ! Initialize MCT attribute vectors and indices
326  call t_startf('MOM_mct_init')
327 
328  if (debug .and. root_pe().eq.pe_here()) print *, "calling ocn_SetGSMap_mct"
329 
330  ! Set mct global seg maps:
331 
332  call ocn_setgsmap_mct(mpicom_ocn, mom_mct_id, mom_mct_gsmap, mom_mct_gsmap3d)
333  lsize = mct_gsmap_lsize(mom_mct_gsmap, mpicom_ocn)
334 
335  ! Initialize mct ocn domain (needs ocn initialization info)
336 
337  if (debug .and. root_pe().eq.pe_here()) print *, "calling ocn_domain_mct"
338  call ocn_domain_mct(lsize, mom_mct_gsmap, mom_mct_dom)
339  !call ocn_domain_mct(lsize*km, MOM_MCT_gsmap3d, MOM_MCT_dom3d) !TODO: this is not used
340 
341  ! Inialize mct attribute vectors
342 
343  if (debug .and. root_pe().eq.pe_here()) print *, "calling mct_avect_init a"
344 
345  ! Initialize the mct attribute vector x2o_o, given Attribute list and length:
346  call mct_avect_init(x2o_o, rlist=seq_flds_x2o_fields, lsize=lsize)
347  ! set the mct attribute vector x2o_o to zero:
348  call mct_avect_zero(x2o_o)
349 
350  if (debug .and. root_pe().eq.pe_here()) print *, "calling mct_avect_init b"
351 
352  ! Initialize the mct attribute vector o2x_o, given Attribute list and length:
353  call mct_avect_init(o2x_o, rlist=seq_flds_o2x_fields, lsize=lsize)
354  ! set the mct attribute vector o2x_o to zero:
355  call mct_avect_zero(o2x_o)
356 
357  ! allocate send buffer
358  nsend = mct_avect_nrattr(o2x_o)
359  nrecv = mct_avect_nrattr(x2o_o)
360 
361  ! initialize necessary coupling info
362 
363  if (debug .and. root_pe().eq.pe_here()) print *, "calling seq_timemgr_eclockgetdata"
364 
365  call seq_timemgr_eclockgetdata(eclock, dtime=ocn_cpl_dt)
366 
367  ! \todo Need interface to get dt from MOM6
368  ncouple_per_day = seconds_in_day / ocn_cpl_dt
369  mom_cpl_dt = seconds_in_day / ncouple_per_day
370  if (mom_cpl_dt /= ocn_cpl_dt) then
371  write(glb%stdout,*) 'ERROR mom_cpl_dt and ocn_cpl_dt must be identical'
372  call exit(0)
373  end if
374 
375  ! send initial state to driver
376 
377  !TODO:
378  ! if ( lsend_precip_fact ) then
379  ! call seq_infodata_PutData( infodata, precip_fact=precip_fact)
380  ! end if
381 
382  if (debug .and. root_pe().eq.pe_here()) print *, "calling ocn_export"
383  call ocn_export(glb%ind, glb%ocn_public, glb%grid, o2x_o%rattr, mom_cpl_dt, ncouple_per_day)
384 
385  call t_stopf('MOM_mct_init')
386 
387  ! Size of global domain
388  call get_global_grid_size(glb%grid, ni, nj)
389 
390  if (debug .and. root_pe().eq.pe_here()) print *, "calling seq_infodata_putdata"
391 
392  call seq_infodata_putdata( glb%infodata, &
393  ocn_nx = ni , ocn_ny = nj)
394  call seq_infodata_putdata( glb%infodata, &
395  ocn_prognostic=.true., ocnrof_prognostic=.true.)
396 
397  if (debug .and. root_pe().eq.pe_here()) print *, "leaving ocean_init_mct"
398 
399  ! Reset shr logging to original values
400  if (is_root_pe()) then
401  call shr_file_setlogunit (shrlogunit)
402  call shr_file_setloglevel(shrloglev)
403  end if
404 
405 end subroutine ocn_init_mct
406 
407 !=======================================================================
408 
409 !> Step forward ocean model for coupling interval
410 subroutine ocn_run_mct( EClock, cdata_o, x2o_o, o2x_o)
411  type(esmf_clock), intent(inout) :: eclock !< Time and time step ? \todo Why must this be intent(inout)?
412  type(seq_cdata), intent(inout) :: cdata_o !< Input parameters
413  type(mct_avect), intent(inout) :: x2o_o !< Fluxes from coupler to ocean, computed by ocean
414  type(mct_avect), intent(inout) :: o2x_o !< Fluxes from ocean to coupler, computed by ocean
415  ! Local variables
416  type(esmf_time) :: time_var !< ESMF_time variable to query time
417  type(esmf_timeinterval) :: ocn_cpl_interval !< The length of one ocean coupling interval
418  integer :: year, month, day, hour, minute, seconds, seconds_n, seconds_d, rc
419  logical :: write_restart_at_eod !< Controls if restart files must be written
420  logical :: debug=.false.
421  type(time_type) :: time_start !< Start of coupled time interval to pass to MOM6
422  type(time_type) :: coupling_timestep !< Coupled time interval to pass to MOM6
423  character(len=128) :: err_msg !< Error message
424  character(len=32) :: timestamp !< Name of intermediate restart file
425  character(len=384) :: restartname !< The restart file name (no dir)
426  character(len=384) :: restart_pointer_file !< File name for restart pointer file
427  character(len=384) :: runid !< Run ID
428  character(len=32) :: runtype !< Run type
429  integer :: nu !< i/o unit to write pointer file
430  integer :: shrlogunit ! original log file unit
431  integer :: shrloglev ! original log level
432  logical, save :: firstcall = .true.
433  real (kind=8), parameter :: seconds_in_day = 86400.0 !< number of seconds in one day
434  integer :: ocn_cpl_dt !< one ocn coupling interval in seconds. (to be received from cesm)
435  real (kind=8) :: mom_cpl_dt !< one ocn coupling interval in seconds. (internal)
436  integer :: ncouple_per_day !< number of ocean coupled call in one day (non-dim)
437 
438  ! reset shr logging to ocn log file:
439  if (is_root_pe()) then
440  call shr_file_getlogunit(shrlogunit)
441  call shr_file_getloglevel(shrloglev)
442  call shr_file_setlogunit(glb%stdout)
443  endif
444 
445  ! Query the beginning time of the current coupling interval
446  call esmf_clockget(eclock, prevtime=time_var, rc=rc)
447  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
448  time_start = set_date(year, month, day, hour, minute, seconds, err_msg=err_msg)
449 
450  ! Query the coupling interval duration
451  call esmf_clockget(eclock, timestep=ocn_cpl_interval, rc=rc)
452  call esmf_timeintervalget(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
453  coupling_timestep = set_time(seconds, days=day, err_msg=err_msg)
454 
455  call seq_timemgr_eclockgetdata(eclock, dtime=ocn_cpl_dt)
456  ncouple_per_day = seconds_in_day / ocn_cpl_dt
457  mom_cpl_dt = seconds_in_day / ncouple_per_day
458 
459  ! The following if-block is to correct monthly mean outputs:
460  ! With this change, MOM6 starts at the same date as the other components, and runs for the same
461  ! duration as other components, unlike POP, which would have one missing interval due to ocean
462  ! lag. MOM6 accounts for this lag by doubling the duration of the first coupling interval.
463  if (firstcall) then
464 
465  runtype = get_runtype()
466  if (runtype /= "continue" .and. runtype /= "branch") then
467 
468  if (debug .and. is_root_pe()) then
469  write(glb%stdout,*) 'doubling first interval duration!'
470  endif
471 
472  ! shift back the start time by one coupling interval (to align the start time with other components)
473  time_start = time_start-coupling_timestep
474  ! double the first coupling interval (to account for the missing coupling interval to due to lag)
475  coupling_timestep = coupling_timestep*2
476  end if
477 
478  firstcall = .false.
479  end if
480 
481  ! Debugging clocks
482  if (debug .and. is_root_pe()) then
483  call esmf_clockget(eclock, currtime=time_var, rc=rc)
484  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
485  write(glb%stdout,*) 'ocn_run_mct, current time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
486  call esmf_clockget(eclock, starttime=time_var, rc=rc)
487  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
488  write(glb%stdout,*) 'ocn_run_mct, start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
489  call esmf_clockget(eclock, stoptime=time_var, rc=rc)
490  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
491  write(glb%stdout,*) 'ocn_run_mct, stop time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
492  call esmf_clockget(eclock, prevtime=time_var, rc=rc)
493  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
494  write(glb%stdout,*) 'ocn_run_mct, previous time: y,m,d-',year,month,day,'h,m,s=',hour,minute,seconds
495  call esmf_clockget(eclock, timestep=ocn_cpl_interval, rc=rc)
496  call esmf_timeintervalget(ocn_cpl_interval, yy=year, mm=month, d=day, s=seconds, sn=seconds_n, sd=seconds_d, rc=rc)
497  write(glb%stdout,*) 'ocn_init_mct, time step: y,m,d-',year,month,day,'s,sn,sd=',seconds,seconds_n,seconds_d
498  endif
499 
500  ! set the cdata pointers:
501  ! \todo this was done in _init_, is it needed again. Does this infodata need to be in glb%?
502  ! GMM, check if this is needed!
503  call seq_cdata_setptrs(cdata_o, infodata=glb%infodata)
504 
505  ! Translate import fields to ice_ocean_boundary
506  !TODO: make this an input variable
507  !glb%sw_decomp = .false.
508  !END TODO:
509  if (glb%sw_decomp) then
510  call ocn_import(x2o_o%rattr, glb%ind, glb%grid, ice_ocean_boundary, glb%ocn_public, glb%stdout, eclock, &
511  c1=glb%c1, c2=glb%c2, c3=glb%c3, c4=glb%c4)
512  else
513  call ocn_import(x2o_o%rattr, glb%ind, glb%grid, ice_ocean_boundary, glb%ocn_public, glb%stdout, eclock )
514  end if
515 
516  ! Update internal ocean
517  call update_ocean_model(ice_ocean_boundary, glb%ocn_state, glb%ocn_public, time_start, coupling_timestep)
518 
519  ! Return export state to driver
520  call ocn_export(glb%ind, glb%ocn_public, glb%grid, o2x_o%rattr, mom_cpl_dt, ncouple_per_day)
521 
522  !--- write out intermediate restart file when needed.
523  ! Check alarms for flag to write restart at end of day
524  write_restart_at_eod = seq_timemgr_restartalarmison(eclock)
525  if (debug .and. is_root_pe()) write(glb%stdout,*) 'ocn_run_mct, write_restart_at_eod=', write_restart_at_eod
526 
527  if (write_restart_at_eod) then
528  ! case name
529  call seq_infodata_getdata( glb%infodata, case_name=runid )
530  ! add time stamp to the restart filename
531  call esmf_clockget(eclock, currtime=time_var, rc=rc)
532  call esmf_timeget(time_var, yy=year, mm=month, dd=day, h=hour, m=minute, s=seconds, rc=rc)
533  seconds = seconds + hour*3600 + minute*60
534  write(restartname,'(A,".mom6.r.",I4.4,"-",I2.2,"-",I2.2,"-",I5.5)') trim(runid), year, month, day, seconds
535 
536  call save_restart(glb%ocn_state%dirs%restart_output_dir, glb%ocn_state%Time, glb%grid, &
537  glb%ocn_state%restart_CSp, .false., filename=restartname, gv=glb%ocn_state%GV)
538 
539  ! write name of restart file in the rpointer file
540  nu = shr_file_getunit()
541  if (is_root_pe()) then
542  restart_pointer_file = trim(glb%pointer_filename)
543  open(nu, file=restart_pointer_file, form='formatted', status='unknown')
544  write(nu,'(a)') trim(restartname) //'.nc'
545  close(nu)
546  write(glb%stdout,*) 'ocn restart pointer file written: ',trim(restartname)
547  endif
548  call shr_file_freeunit(nu)
549 
550  ! Is this needed?
551  call forcing_save_restart(glb%ocn_state%forcing_CSp, glb%grid, glb%ocn_state%Time, &
552  glb%ocn_state%dirs%restart_output_dir, .true.)
553 
554  ! Once we start using the ice shelf module, the following will be needed
555  if (glb%ocn_state%use_ice_shelf) then
556  call ice_shelf_save_restart(glb%ocn_state%Ice_shelf_CSp, glb%ocn_state%Time, &
557  glb%ocn_state%dirs%restart_output_dir, .true.)
558  endif
559 
560  endif
561 
562  ! reset shr logging to original values
563  if (is_root_pe()) then
564  call shr_file_setlogunit(shrlogunit)
565  call shr_file_setloglevel(shrloglev)
566  endif
567 
568 end subroutine ocn_run_mct
569 
570 !=======================================================================
571 
572 !> Finalizes MOM6
573 !!
574 !! \todo This needs to be done here.
575 subroutine ocn_final_mct( EClock, cdata_o, x2o_o, o2x_o)
576  type(esmf_clock) , intent(inout) :: eclock
577  type(seq_cdata) , intent(inout) :: cdata_o
578  type(mct_avect) , intent(inout) :: x2o_o !< Fluxes from coupler to ocean, computed by ocean
579  type(mct_avect) , intent(inout) :: o2x_o !< Fluxes from ocean to coupler, computed by ocean
580 
581  call ocean_model_end(glb%ocn_public, glb%ocn_state, glb%ocn_state%Time)
582 
583 end subroutine ocn_final_mct
584 
585 !=======================================================================
586 
587 !> Sets mct global segment maps for the MOM decomposition.
588 !!
589 !! \todo Find out if we should only provide indirect indexing for ocean points and not land.
590 subroutine ocn_setgsmap_mct(mpicom_ocn, MOM_MCT_ID, gsMap_ocn, gsMap3d_ocn)
591  integer, intent(in) :: mpicom_ocn !< MPI communicator
592  integer, intent(in) :: mom_mct_id !< MCT component ID
593  type(mct_gsmap), intent(inout) :: gsmap_ocn !< MCT global segment map for 2d data
594  type(mct_gsmap), intent(inout) :: gsmap3d_ocn !< MCT global segment map for 3d data
595 
596  ! Local variables
597  integer :: lsize !< Local size of indirect indexing array
598  integer :: i, j, k !< Local indices
599  integer :: ni, nj !< Declared sizes of h-point arrays
600  integer :: ig, jg !< Global indices
601  type(ocean_grid_type), pointer :: grid => null() !< A pointer to a grid structure
602  integer, allocatable :: gindex(:) !< Indirect indices
603 
604  grid => glb%grid ! for convenience
605  if (.not. associated(grid)) call mom_error(fatal, 'ocn_comp_mct.F90, ocn_SetGSMap_mct():' // &
606  'grid is not associated!')
607 
608  ! Size of computational domain
609  lsize = ( grid%iec - grid%isc + 1 ) * ( grid%jec - grid%jsc + 1 )
610 
611  ! Size of global domain
612  call get_global_grid_size(grid, ni, nj)
613 
614  ! Create indirect indices for the computational domain
615  allocate(gindex(lsize))
616 
617  ! Set indirect indices in gindex
618  k = 0
619  do j = grid%jsc, grid%jec
620  jg = j + grid%jdg_offset ! TODO: check this calculation
621  do i = grid%isc, grid%iec
622  ig = i + grid%idg_offset ! TODO: check this calculation
623  k = k + 1 ! Increment position within gindex
624  gindex(k) = ni * (jg - 1) + ig
625  enddo
626  enddo
627 
628  ! Tell MCT how to indirectly index into the 2d buffer
629  call mct_gsmap_init(gsmap_ocn, gindex, mpicom_ocn, mom_mct_id, lsize, ni * nj)
630 
631  deallocate(gindex)
632 
633 end subroutine ocn_setgsmap_mct
634 
635 !=======================================================================
636 
637 !> Sets MCT global segment maps for the MOM6 decomposition
638 subroutine ocn_domain_mct( lsize, gsMap_ocn, dom_ocn)
639  integer , intent(in) :: lsize !< Size of attr. vector
640  type(mct_gsmap), intent(in) :: gsmap_ocn !< MCT global segment map for 2d data
641  type(mct_ggrid), intent(inout) :: dom_ocn !< WHAT IS THIS?
642 
643  ! Local Variables
644  integer, parameter :: shr_real_r8 = selected_real_kind(12)
645  integer, pointer :: idata(:)
646  integer :: i,j,k
647  real(kind=shr_real_r8), pointer :: data(:)
648  real(kind=shr_real_r8) :: l2_to_rad2
649  type(ocean_grid_type), pointer :: grid => null() ! A pointer to a grid structure
650 
651  grid => glb%grid ! for convenience
652 
653  ! set coords to lat and lon, and areas to rad^2
654  call mct_ggrid_init(ggrid=dom_ocn, coordchars='lat:lon:hgt', otherchars='area:aream:mask:frac', lsize=lsize )
655 
656  call mct_avect_zero(dom_ocn%data)
657  allocate(data(lsize))
658 
659  ! Determine global gridpoint number attribute, GlobGridNum, which is set automatically by MCT
660  k = pe_here()
661  call mct_gsmap_orderedpoints(gsmap_ocn, k, idata)
662  call mct_ggrid_importiattr(dom_ocn,'GlobGridNum',idata,lsize)
663 
664  !initialization
665  data(:) = -9999.0
666  call mct_ggrid_importrattr(dom_ocn,"lat" ,data,lsize)
667  call mct_ggrid_importrattr(dom_ocn,"lon" ,data,lsize)
668  call mct_ggrid_importrattr(dom_ocn,"area" ,data,lsize)
669  call mct_ggrid_importrattr(dom_ocn,"aream",data,lsize)
670  data(:) = 0.0
671  call mct_ggrid_importrattr(dom_ocn,"mask",data,lsize)
672  call mct_ggrid_importrattr(dom_ocn,"frac",data,lsize)
673 
674  k = 0
675  do j = grid%jsc, grid%jec
676  do i = grid%isc, grid%iec
677  k = k + 1 ! Increment position within gindex
678  data(k) = grid%geoLonT(i,j)
679  enddo
680  enddo
681  call mct_ggrid_importrattr(dom_ocn,"lon",data,lsize)
682 
683  k = 0
684  do j = grid%jsc, grid%jec
685  do i = grid%isc, grid%iec
686  k = k + 1 ! Increment position within gindex
687  data(k) = grid%geoLatT(i,j)
688  enddo
689  enddo
690  call mct_ggrid_importrattr(dom_ocn,"lat",data,lsize)
691 
692  k = 0
693  l2_to_rad2 = grid%US%L_to_m**2 / grid%Rad_Earth**2
694  do j = grid%jsc, grid%jec
695  do i = grid%isc, grid%iec
696  k = k + 1 ! Increment position within gindex
697  data(k) = grid%AreaT(i,j) * l2_to_rad2
698  enddo
699  enddo
700  call mct_ggrid_importrattr(dom_ocn,"area",data,lsize)
701 
702  k = 0
703  do j = grid%jsc, grid%jec
704  do i = grid%isc, grid%iec
705  k = k + 1 ! Increment position within gindex
706  data(k) = grid%mask2dT(i,j)
707  enddo
708  enddo
709  call mct_ggrid_importrattr(dom_ocn,"mask",data,lsize)
710  call mct_ggrid_importrattr(dom_ocn,"frac",data,lsize)
711 
712  deallocate(data)
713  deallocate(idata)
714 
715 end subroutine ocn_domain_mct
716 
717 !=======================================================================
718 
719 !> Returns the CESM run type
720 character(32) function get_runtype()
721  character(len=32) :: starttype !< infodata start type
722 
723  call seq_infodata_getdata( glb%infodata, start_type=starttype)
724 
725  if ( trim(starttype) == trim(seq_infodata_start_type_start)) then
726  get_runtype = "initial"
727  else if (trim(starttype) == trim(seq_infodata_start_type_cont) ) then
728  get_runtype = "continue"
729  else if (trim(starttype) == trim(seq_infodata_start_type_brnch)) then
730  get_runtype = "branch"
731  else
732  write(glb%stdout,*) 'ocn_comp_mct ERROR: unknown starttype'
733  call exit(0)
734  end if
735  return
736 
737 end function
738 
739 !=======================================================================
740 
741 !> It has to be separate from the ocean_initialization call because the coupler
742 !! module allocates the space for some of these variables.
743 subroutine ocean_model_init_sfc(OS, Ocean_sfc)
744  type(ocean_state_type), pointer :: os
745  type(ocean_public_type), intent(inout) :: ocean_sfc
746 
747  integer :: is, ie, js, je
748 
749  is = os%grid%isc ; ie = os%grid%iec ; js = os%grid%jsc ; je = os%grid%jec
750  call coupler_type_spawn(ocean_sfc%fields, os%sfc_state%tr_fields, &
751  (/is,is,ie,ie/), (/js,js,je,je/), as_needed=.true.)
752 
753  call extract_surface_state(os%MOM_CSp, os%sfc_state)
754 
755  call convert_state_to_ocean_type(os%sfc_state, ocean_sfc, os%grid, os%US)
756 
757 end subroutine ocean_model_init_sfc
758 
759 !=======================================================================
760 
761 !> \namespace ocn_comp_mct
762 !!
763 !! \section section_ocn_import Fluxes imported from the coupler (MCT) to MOM6
764 !! The following summarizes the mismatches between MCT and MOM6 in terms
765 !! of ice ocean fluxes.
766 !!
767 !! Redundancies:
768 !! x2o_Faxa_prec = x2o_Faxa_rain + x2o_Faxa_snow
769 !!
770 !! Variables whose units and sign **could not** be verified so far:
771 !! x2o_Foxx_rofl
772 !! x2o_Foxx_rof
773 !!
774 !! Variables in MOM6 fluxes that are **NOT** filled by the coupler:
775 !! ustar_berg, frictional velocity beneath icebergs [m s-1]
776 !! area_berg, area covered by icebergs(m2/m2)
777 !! mass_berg, mass of icebergs(kg/m2)
778 !! runoff_hflx, heat content of liquid runoff (W/m2)
779 !! calving_hflx, heat content of frozen runoff (W/m2)
780 !! mi, mass of ice (kg/m2)
781 !!
782 !! Variables in the coupler that are **NOT** used in MOM6 (i.e., no corresponding field in fluxes):
783 !! x2o_Si_ifrac, fractional ice wrt ocean
784 !! x2o_So_duu10n, 10m wind speed squared (m^2/s^2)
785 !! x2o_Sa_co2prog, bottom atm level prognostic CO2
786 !! x2o_Sa_co2diag, bottom atm level diagnostic CO2
787 !!
788 !! \TODO Langmuir related fields:
789 !! surface Stokes drift, x-comp. (x2o_Sw_ustokes)
790 !! surface Stokes drift, y-comp. (x2o_Sw_vstokes)
791 !! wave model langmuir multiplier (x2o_Sw_lamult)
792 !!
793 !! \TODO Biogeochemistry:
794 !! x2o_Fioi_bcpho, Black Carbon hydrophobic release from sea ice component
795 !! x2o_Fioi_bcphi, Black Carbon hydrophilic release from sea ice component
796 !! x2o_Fioi_flxdst, Dust release from sea ice component
797 !! x2o_Faxa_bcphidry, Black Carbon hydrophilic dry deposition
798 !! x2o_Faxa_bcphodry, Black Carbon hydrophobic dry deposition
799 !! x2o_Faxa_bcphiwet, Black Carbon hydrophobic wet deposition
800 !! x2o_Faxa_ocphidry, Organic Carbon hydrophilic dry deposition
801 !! x2o_Faxa_ocphodry, Organic Carbon hydrophobic dry deposition
802 !! x2o_Faxa_ocphiwet, Organic Carbon hydrophilic dry deposition
803 !! x2o_Faxa_dstwet, Sizes 1 to 4 dust - wet deposition
804 !! x2o_Faxa_dstdry, Sizes 1 to 4 dust - dry deposition
805 !!
806 !! \section section_ocn_export Fluxes exported from MOM6 to the coupler (MCT)
807 !!
808 !! Variables that are currently being exported:
809 !!
810 !! Surface temperature (Kelvin)
811 !! Surface salinity (psu)
812 !! Surface eastward velocity [m s-1]
813 !! Surface northward velocity [m s-1]
814 !! Zonal slope in the sea surface height
815 !! Meridional slope in the sea surface height
816 !!
817 !! \TODO Variables that **are not** currently being exported:
818 !!
819 !! Boundary layer depth
820 !! CO2
821 !! DMS
822 
823 !> Allocates ice-ocean boundary type containers and sets to 0.
824 subroutine iob_allocate(IOB, isc, iec, jsc, jec)
825  type(ice_ocean_boundary_type), intent(inout) :: IOB !< An ice-ocean boundary type with fluxes to drive
826  integer, intent(in) :: isc, iec, jsc, jec !< The ocean's local grid size
827 
828  allocate ( iob% rofl_flux (isc:iec,jsc:jec), &
829  iob% rofi_flux (isc:iec,jsc:jec), &
830  iob% u_flux (isc:iec,jsc:jec), &
831  iob% v_flux (isc:iec,jsc:jec), &
832  iob% t_flux (isc:iec,jsc:jec), &
833  iob% seaice_melt_heat (isc:iec,jsc:jec),&
834  iob% seaice_melt (isc:iec,jsc:jec), &
835  iob% q_flux (isc:iec,jsc:jec), &
836  iob% salt_flux (isc:iec,jsc:jec), &
837  iob% lw_flux (isc:iec,jsc:jec), &
838  iob% sw_flux_vis_dir (isc:iec,jsc:jec), &
839  iob% sw_flux_vis_dif (isc:iec,jsc:jec), &
840  iob% sw_flux_nir_dir (isc:iec,jsc:jec), &
841  iob% sw_flux_nir_dif (isc:iec,jsc:jec), &
842  iob% lprec (isc:iec,jsc:jec), &
843  iob% fprec (isc:iec,jsc:jec), &
844  iob% ustar_berg (isc:iec,jsc:jec), &
845  iob% area_berg (isc:iec,jsc:jec), &
846  iob% mass_berg (isc:iec,jsc:jec), &
847  iob% calving (isc:iec,jsc:jec), &
848  iob% runoff_hflx (isc:iec,jsc:jec), &
849  iob% calving_hflx (isc:iec,jsc:jec), &
850  iob% mi (isc:iec,jsc:jec), &
851  iob% p (isc:iec,jsc:jec))
852 
853  iob%rofl_flux = 0.0
854  iob%rofi_flux = 0.0
855  iob%u_flux = 0.0
856  iob%v_flux = 0.0
857  iob%t_flux = 0.0
858  iob%seaice_melt_heat = 0.0
859  iob%seaice_melt = 0.0
860  iob%q_flux = 0.0
861  iob%salt_flux = 0.0
862  iob%lw_flux = 0.0
863  iob%sw_flux_vis_dir = 0.0
864  iob%sw_flux_vis_dif = 0.0
865  iob%sw_flux_nir_dir = 0.0
866  iob%sw_flux_nir_dif = 0.0
867  iob%lprec = 0.0
868  iob%fprec = 0.0
869  iob%ustar_berg = 0.0
870  iob%area_berg = 0.0
871  iob%mass_berg = 0.0
872  iob%calving = 0.0
873  iob%runoff_hflx = 0.0
874  iob%calving_hflx = 0.0
875  iob%mi = 0.0
876  iob%p = 0.0
877 
878 end subroutine iob_allocate
879 
880 end module ocn_comp_mct
ocn_comp_mct::ocn_setgsmap_mct
subroutine, private ocn_setgsmap_mct(mpicom_ocn, MOM_MCT_ID, gsMap_ocn, gsMap3d_ocn)
Sets mct global segment maps for the MOM decomposition.
Definition: ocn_comp_mct.F90:591
mom_time_manager
Wraps the FMS time manager functions.
Definition: MOM_time_manager.F90:2
ocn_cpl_indices::cpl_indices_init
subroutine, public cpl_indices_init(ind)
Determines attribute vector indices.
Definition: ocn_cpl_indices.F90:85
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_ocean_model_mct::ocean_model_end
subroutine, public ocean_model_end(Ocean_sfc, Ocean_state, Time)
ocean_model_end terminates the model run, saving the ocean state in a restart and deallocating any da...
Definition: mom_ocean_model_mct.F90:729
mom_ocean_model_mct::convert_state_to_ocean_type
subroutine convert_state_to_ocean_type(sfc_state, Ocean_sfc, G, US, patm, press_to_z)
This subroutine translates the coupler's ocean_data_type into MOM's surface state variable....
Definition: mom_ocean_model_mct.F90:844
mom_ice_shelf
Implements the thermodynamic aspects of ocean / ice-shelf interactions, along with a crude placeholde...
Definition: MOM_ice_shelf.F90:4
ocn_cap_methods::ocn_import
subroutine, public ocn_import(x2o, ind, grid, ice_ocean_boundary, ocean_public, logunit, Eclock, c1, c2, c3, c4)
Maps incomping ocean data to MOM6 data structures.
Definition: ocn_cap_methods.F90:26
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
ocn_comp_mct::debug
logical, parameter debug
Definition: ocn_comp_mct.F90:80
mom_constants
Provides a few physical constants.
Definition: MOM_constants.F90:2
mom_get_input::directories
Container for paths and parameter file names.
Definition: MOM_get_input.F90:20
ocn_comp_mct::ocn_domain_mct
subroutine, private ocn_domain_mct(lsize, gsMap_ocn, dom_ocn)
Sets MCT global segment maps for the MOM6 decomposition.
Definition: ocn_comp_mct.F90:639
ocn_comp_mct
This is the main driver for MOM6 in CIME.
Definition: ocn_comp_mct.F90:2
ocn_comp_mct::ocn_init_mct
subroutine, public ocn_init_mct(EClock, cdata_o, x2o_o, o2x_o, NLFilename)
This subroutine initializes MOM6.
Definition: ocn_comp_mct.F90:105
mom_surface_forcing_mct::surface_forcing_cs
Contains pointers to the forcing fields which may be used to drive MOM. All fluxes are positive downw...
Definition: mom_surface_forcing_mct.F90:58
mom_eos
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
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_ocean_model_mct::ocean_model_init
subroutine, public ocean_model_init(Ocean_sfc, OS, Time_init, Time_in, gas_fields_ocn, input_restart_file)
ocean_model_init initializes the ocean model, including registering fields for restarts and reading r...
Definition: mom_ocean_model_mct.F90:224
ocn_cap_methods::ocn_export
subroutine, public ocn_export(ind, ocn_public, grid, o2x, dt_int, ncouple_per_day)
Maps outgoing ocean data to MCT attribute vector real array.
Definition: ocn_cap_methods.F90:151
mom_get_input
Reads the only Fortran name list needed to boot-strap the model.
Definition: MOM_get_input.F90:6
ocn_comp_mct::mct_mom_data
Control structure for this module.
Definition: ocn_comp_mct.F90:83
mom_domains::pass_vector
Do a halo update on a pair of arrays representing the two components of a vector.
Definition: MOM_domains.F90:54
mom_ice_shelf::ice_shelf_save_restart
subroutine, public ice_shelf_save_restart(CS, Time, directory, time_stamped, filename_suffix)
Save the ice shelf restart file.
Definition: MOM_ice_shelf.F90:1721
ocn_comp_mct::iob_allocate
subroutine iob_allocate(IOB, isc, iec, jsc, jec)
Allocates ice-ocean boundary type containers and sets to 0.
Definition: ocn_comp_mct.F90:825
mom_surface_forcing_mct::forcing_save_restart
subroutine, public forcing_save_restart(CS, G, Time, directory, time_stamped, filename_suffix)
Save any restart files associated with the surface forcing.
Definition: mom_surface_forcing_mct.F90:988
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
ocn_comp_mct::ocean_model_init_sfc
subroutine, private ocean_model_init_sfc(OS, Ocean_sfc)
It has to be separate from the ocean_initialization call because the coupler module allocates the spa...
Definition: ocn_comp_mct.F90:744
ocn_comp_mct::ocn_run_mct
subroutine, public ocn_run_mct(EClock, cdata_o, x2o_o, o2x_o)
Step forward ocean model for coupling interval.
Definition: ocn_comp_mct.F90:411
ocn_comp_mct::ice_ocean_boundary
type(ice_ocean_boundary_type) ice_ocean_boundary
Definition: ocn_comp_mct.F90:97
ocn_cpl_indices
Definition: ocn_cpl_indices.F90:1
mom_ocean_model_mct::ocean_state_type
The ocean_state_type contains all information about the state of the ocean, with a format that is pri...
Definition: mom_ocean_model_mct.F90:134
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
ocn_cpl_indices::cpl_indices_type
Structure with indices needed for MCT attribute vectors.
Definition: ocn_cpl_indices.F90:10
mom_grid::get_global_grid_size
subroutine, public get_global_grid_size(G, niglobal, njglobal)
Return global shape of horizontal grid.
Definition: MOM_grid.F90:510
mom_get_input::get_mom_input
subroutine, public get_mom_input(param_file, dirs, check_params, default_input_filename, ensemble_num)
Get the names of the I/O directories and initialization file. Also calls the subroutine that opens ru...
Definition: MOM_get_input.F90:34
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
ocn_comp_mct::get_runtype
character(32) function, private get_runtype()
Returns the CESM run type.
Definition: ocn_comp_mct.F90:721
mom_surface_forcing_mct::ice_ocean_boundary_type
Structure corresponding to forcing, but with the elements, units, and conventions that exactly confor...
Definition: mom_surface_forcing_mct.F90:147
mom_error_handler::is_root_pe
logical function, public is_root_pe()
This returns .true. if the current PE is the root PE.
Definition: MOM_error_handler.F90:44
mom
The central module of the MOM6 ocean model.
Definition: MOM.F90:2
mom_file_parser::close_param_file
subroutine, public close_param_file(CS, quiet_close, component)
Close any open input files and deallocate memory associated with this param_file_type....
Definition: MOM_file_parser.F90:242
mom_ocean_model_mct::ocean_public_type
This type is used for communication with other components via the FMS coupler. The element names and ...
Definition: mom_ocean_model_mct.F90:88
mom_error_handler::mom_error
subroutine, public mom_error(level, message, all_print)
This provides a convenient interface for writing an mpp_error message with run-time filter based on a...
Definition: MOM_error_handler.F90:72
mom_restart::save_restart
subroutine, public save_restart(directory, time, G, CS, time_stamped, filename, GV)
save_restart saves all registered variables to restart files.
Definition: MOM_restart.F90:781
mom_ocean_model_mct::update_ocean_model
subroutine, public update_ocean_model(Ice_ocean_boundary, OS, Ocean_sfc, time_start_update, Ocean_coupling_time_step, update_dyn, update_thermo, Ocn_fluxes_used)
update_ocean_model uses the forcing in Ice_ocean_boundary to advance the ocean model's state from the...
Definition: mom_ocean_model_mct.F90:425
ocn_comp_mct::glb
type(mct_mom_data) glb
global structure
Definition: ocn_comp_mct.F90:96
mom_surface_forcing_mct
Definition: mom_surface_forcing_mct.F90:1
ocn_comp_mct::ocn_final_mct
subroutine, public ocn_final_mct(EClock, cdata_o, x2o_o, o2x_o)
Finalizes MOM6.
Definition: ocn_comp_mct.F90:576
mom_ocean_model_mct
Top-level module for the MOM6 ocean model in coupled mode.
Definition: mom_ocean_model_mct.F90:2
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom::extract_surface_state
subroutine, public extract_surface_state(CS, sfc_state)
Set the surface (return) properties of the ocean model by setting the appropriate fields in sfc_state...
Definition: MOM.F90:2712
ocn_cap_methods
Definition: ocn_cap_methods.F90:1
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:26
mom_constants::celsius_kelvin_offset
real, parameter, public celsius_kelvin_offset
The constant offset for converting temperatures in Kelvin to Celsius.
Definition: MOM_constants.F90:11