MOM6
mom_cap.F90
Go to the documentation of this file.
1 !> This module contains a set of subroutines that are required by NUOPC.
2 
3 module mom_cap_mod
4 
5 use constants_mod, only: constants_init
6 use diag_manager_mod, only: diag_manager_init, diag_manager_end
7 use field_manager_mod, only: field_manager_init, field_manager_end
8 use fms_mod, only: fms_init, fms_end, open_namelist_file, check_nml_error
9 use fms_mod, only: close_file, file_exist, uppercase
10 use fms_io_mod, only: fms_io_exit
11 use mpp_domains_mod, only: domain2d, mpp_get_compute_domain, mpp_get_compute_domains
12 use mpp_domains_mod, only: mpp_get_ntile_count, mpp_get_pelist, mpp_get_global_domain
13 use mpp_domains_mod, only: mpp_get_domain_npes
14 use mpp_io_mod, only: mpp_open, mpp_rdonly, mpp_ascii, mpp_overwr, mpp_append, mpp_close, mpp_single
15 use mpp_mod, only: stdlog, stdout, mpp_root_pe, mpp_clock_id
16 use mpp_mod, only: mpp_clock_begin, mpp_clock_end, mpp_clock_sync
17 use mpp_mod, only: mpp_clock_detailed, clock_component, maxpes
18 use time_interp_external_mod, only: time_interp_external_init
19 use time_manager_mod, only: set_calendar_type, time_type, increment_date
20 use time_manager_mod, only: set_time, set_date, get_time, get_date, month_name
21 use time_manager_mod, only: gregorian, julian, noleap, thirty_day_months, no_calendar
22 use time_manager_mod, only: operator( <= ), operator( < ), operator( >= )
23 use time_manager_mod, only: operator( + ), operator( - ), operator( / )
24 use time_manager_mod, only: operator( * ), operator( /= ), operator( > )
25 use time_manager_mod, only: date_to_string
26 use time_manager_mod, only: fms_get_calendar_type => get_calendar_type
27 use mom_domains, only: mom_infra_init, num_pes, root_pe, pe_here
30 use mom_domains, only: pass_var
31 use mom_error_handler, only: mom_error, fatal, is_root_pe
32 use mom_ocean_model_nuopc, only: ice_ocean_boundary_type
38 use mom_cap_time, only: alarminit
40 #ifdef CESMCOUPLED
41 use shr_file_mod, only: shr_file_setlogunit, shr_file_getlogunit
42 #endif
44 
45 use, intrinsic :: iso_fortran_env, only: output_unit
46 
47 use esmf, only: esmf_clockadvance, esmf_clockget, esmf_clockprint
48 use esmf, only: esmf_clockgetalarm, esmf_clockgetnexttime, esmf_clockadvance
49 use esmf, only: esmf_clockset, esmf_clock, esmf_geomtype_flag, esmf_logmsg_info
50 use esmf, only: esmf_grid, esmf_gridcreate, esmf_gridaddcoord
51 use esmf, only: esmf_gridgetcoord, esmf_gridadditem, esmf_gridgetitem
52 use esmf, only: esmf_gridcomp, esmf_gridcompsetentrypoint, esmf_gridcompget
53 use esmf, only: esmf_logfounderror, esmf_logwrite, esmf_logseterror
54 use esmf, only: esmf_logerr_passthru, esmf_kind_r8, esmf_rc_val_wrong
55 use esmf, only: esmf_geomtype_mesh, esmf_geomtype_grid, esmf_success
56 use esmf, only: esmf_method_initialize, esmf_methodremove, esmf_state
57 use esmf, only: esmf_logmsg_info, esmf_rc_arg_bad, esmf_vm, esmf_time
58 use esmf, only: esmf_timeinterval, esmf_maxstr, esmf_vmgetcurrent
59 use esmf, only: esmf_vmget, esmf_timeget, esmf_timeintervalget, esmf_meshget
60 use esmf, only: esmf_methodexecute, esmf_mesh, esmf_delayout, esmf_distgrid
61 use esmf, only: esmf_distgridconnection, esmf_stateitem_flag, esmf_kind_i4
62 use esmf, only: esmf_kind_i8, esmf_failure, esmf_distgridcreate, esmf_meshcreate
63 use esmf, only: esmf_fileformat_esmfmesh, esmf_delayoutcreate, esmf_distgridconnectionset
64 use esmf, only: esmf_distgridget, esmf_staggerloc_corner, esmf_griditem_mask
65 use esmf, only: esmf_typekind_i4, esmf_typekind_r8, esmf_staggerloc_center
66 use esmf, only: esmf_griditem_area, esmf_field, esmf_alarm, esmf_vmlogmeminfo
67 use esmf, only: esmf_alarmisringing, esmf_alarmringeroff, esmf_stateremove
68 use esmf, only: esmf_fieldcreate, esmf_logmsg_error, esmf_logmsg_warning
69 use esmf, only: esmf_coordsys_sph_deg, esmf_gridcreate, esmf_index_delocal
70 use esmf, only: esmf_meshloc_element, esmf_rc_val_outofrange, esmf_stateget
71 use esmf, only: esmf_timeprint, esmf_alarmset, esmf_fieldget, esmf_array
72 use esmf, only: esmf_arraycreate
73 use esmf, only: operator(==), operator(/=), operator(+), operator(-)
74 
75 ! TODO ESMF_GridCompGetInternalState does not have an explicit Fortran interface.
76 !! Model does not compile with "use ESMF, only: ESMF_GridCompGetInternalState"
77 !! Is this okay?
78 
79 use nuopc, only: nuopc_compderive, nuopc_compsetentrypoint, nuopc_compspecialize
80 use nuopc, only: nuopc_compfilterphasemap, nuopc_compattributeget, nuopc_compattributeadd
81 use nuopc, only: nuopc_advertise, nuopc_setattribute, nuopc_isupdated, nuopc_write
82 use nuopc, only: nuopc_isconnected, nuopc_realize, nuopc_compattributeset
83 use nuopc_model, only: nuopc_modelget
84 use nuopc_model, &
85  model_routine_ss => setservices, &
86  model_label_advance => label_advance, &
87  model_label_datainitialize => label_datainitialize, &
88  model_label_setrunclock => label_setrunclock, &
89  model_label_finalize => label_finalize
90 
91 implicit none; private
92 
93 public setservices
94 
95 !> Internal state type with pointers to three types defined by MOM.
97  type(ocean_public_type), pointer :: ocean_public_type_ptr
98  type(ocean_state_type), pointer :: ocean_state_type_ptr
99  type(ice_ocean_boundary_type), pointer :: ice_ocean_boundary_type_ptr
100 end type
101 
102 !> Wrapper-derived type required to associate an internal state instance
103 !! with the ESMF/NUOPC component
105  type(ocean_internalstate_type), pointer :: ptr
106 end type
107 
108 !> Contains field information
110  character(len=64) :: stdname
111  character(len=64) :: shortname
112  character(len=64) :: transferoffer
113 end type fld_list_type
114 
115 integer,parameter :: fldsmax = 100
116 integer :: fldstoocn_num = 0
118 integer :: fldsfrocn_num = 0
120 
121 integer :: debug = 0
122 integer :: import_slice = 1
123 integer :: export_slice = 1
124 character(len=256) :: tmpstr
125 logical :: write_diagnostics = .false.
126 logical :: overwrite_timeslice = .false.
127 character(len=32) :: runtype !< run type
128 integer :: logunit !< stdout logging unit number
129 logical :: profile_memory = .true.
130 logical :: grid_attach_area = .false.
131 character(len=128) :: scalar_field_name = ''
132 integer :: scalar_field_count = 0
135 character(len=*),parameter :: u_file_u = &
136  __file__
137 
138 #ifdef CESMCOUPLED
139 logical :: cesm_coupled = .true.
140 type(esmf_geomtype_flag) :: geomtype = esmf_geomtype_mesh
141 #else
142 logical :: cesm_coupled = .false.
143 type(esmf_geomtype_flag) :: geomtype = esmf_geomtype_grid
144 #endif
145 
146 contains
147 
148 !> NUOPC SetService method is the only public entry point.
149 !! SetServices registers all of the user-provided subroutines
150 !! in the module with the NUOPC layer.
151 !!
152 !! @param gcomp an ESMF_GridComp object
153 !! @param rc return code
154 subroutine setservices(gcomp, rc)
155 
156  type(esmf_gridcomp) :: gcomp !< an ESMF_GridComp object
157  integer, intent(out) :: rc !< return code
158 
159  ! local variables
160  character(len=*),parameter :: subname='(MOM_cap:SetServices)'
161 
162  rc = esmf_success
163 
164  ! the NUOPC model component will register the generic methods
165  call nuopc_compderive(gcomp, model_routine_ss, rc=rc)
166  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
167  line=__line__, &
168  file=__file__)) &
169  return ! bail out
170 
171  ! switching to IPD versions
172  call esmf_gridcompsetentrypoint(gcomp, esmf_method_initialize, &
173  userroutine=initializep0, phase=0, rc=rc)
174  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
175  line=__line__, &
176  file=__file__)) &
177  return ! bail out
178 
179  ! set entry point for methods that require specific implementation
180  call nuopc_compsetentrypoint(gcomp, esmf_method_initialize, &
181  phaselabellist=(/"IPDv03p1"/), userroutine=initializeadvertise, rc=rc)
182  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
183  line=__line__, &
184  file=__file__)) &
185  return ! bail out
186  call nuopc_compsetentrypoint(gcomp, esmf_method_initialize, &
187  phaselabellist=(/"IPDv03p3"/), userroutine=initializerealize, rc=rc)
188  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
189  line=__line__, &
190  file=__file__)) &
191  return ! bail out
192 
193  !------------------
194  ! attach specializing method(s)
195  !------------------
196 
197  call nuopc_compspecialize(gcomp, speclabel=model_label_datainitialize, &
198  specroutine=datainitialize, rc=rc)
199  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
200  line=__line__, &
201  file=__file__)) &
202  return ! bail out
203 
204  call nuopc_compspecialize(gcomp, speclabel=model_label_advance, &
205  specroutine=modeladvance, rc=rc)
206  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
207  line=__line__, &
208  file=__file__)) &
209  return ! bail out
210 
211  call esmf_methodremove(gcomp, label=model_label_setrunclock, rc=rc)
212  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
213  line=__line__, &
214  file=__file__)) &
215  return ! bail out
216  call nuopc_compspecialize(gcomp, speclabel=model_label_setrunclock, &
217  specroutine=modelsetrunclock, rc=rc)
218  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
219  line=__line__, &
220  file=__file__)) &
221  return ! bail out
222 
223  call nuopc_compspecialize(gcomp, speclabel=model_label_finalize, &
224  specroutine=ocean_model_finalize, rc=rc)
225  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
226  line=__line__, &
227  file=__file__)) &
228  return ! bail out
229 
230 end subroutine setservices
231 
232 !> First initialize subroutine called by NUOPC. The purpose
233 !! is to set which version of the Initialize Phase Definition (IPD)
234 !! to use.
235 !!
236 !! For this MOM cap, we are using IPDv01.
237 !!
238 !! @param gcomp an ESMF_GridComp object
239 !! @param importState an ESMF_State object for import fields
240 !! @param exportState an ESMF_State object for export fields
241 !! @param clock an ESMF_Clock object
242 !! @param rc return code
243 subroutine initializep0(gcomp, importState, exportState, clock, rc)
244  type(esmf_gridcomp) :: gcomp !< ESMF_GridComp object
245  type(esmf_state) :: importState, exportState !< ESMF_State object for
246  !! import/export fields
247  type(esmf_clock) :: clock !< ESMF_Clock object
248  integer, intent(out) :: rc !< return code
249 
250  ! local variables
251  logical :: isPresent, isSet
252  integer :: iostat
253  character(len=64) :: value, logmsg
254  character(len=*),parameter :: subname='(MOM_cap:InitializeP0)'
255 
256  rc = esmf_success
257 
258  ! Switch to IPDv03 by filtering all other phaseMap entries
259  call nuopc_compfilterphasemap(gcomp, esmf_method_initialize, &
260  acceptstringlist=(/"IPDv03p"/), rc=rc)
261  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
262  line=__line__, &
263  file=__file__)) &
264  return
265 
266  write_diagnostics = .false.
267  call nuopc_compattributeget(gcomp, name="DumpFields", value=value, &
268  ispresent=ispresent, isset=isset, rc=rc)
269  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
270  line=__line__, &
271  file=__file__)) &
272  return
273  if (ispresent .and. isset) write_diagnostics=(trim(value)=="true")
274 
275  write(logmsg,*) write_diagnostics
276  call esmf_logwrite('MOM_cap:DumpFields = '//trim(logmsg), esmf_logmsg_info, rc=rc)
277  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
278  line=__line__, &
279  file=__file__)) &
280  return
281 
282  overwrite_timeslice = .false.
283  call nuopc_compattributeget(gcomp, name="OverwriteSlice", value=value, &
284  ispresent=ispresent, isset=isset, rc=rc)
285  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
286  line=__line__, &
287  file=__file__)) &
288  return
289  if (ispresent .and. isset) overwrite_timeslice=(trim(value)=="true")
290  write(logmsg,*) overwrite_timeslice
291  call esmf_logwrite('MOM_cap:OverwriteSlice = '//trim(logmsg), esmf_logmsg_info, rc=rc)
292  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
293  line=__line__, &
294  file=__file__)) &
295  return
296 
297  profile_memory = .false.
298  call nuopc_compattributeget(gcomp, name="ProfileMemory", value=value, &
299  ispresent=ispresent, isset=isset, rc=rc)
300  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
301  line=__line__, &
302  file=__file__)) &
303  return
304  if (ispresent .and. isset) profile_memory=(trim(value)=="true")
305  write(logmsg,*) profile_memory
306  call esmf_logwrite('MOM_cap:ProfileMemory = '//trim(logmsg), esmf_logmsg_info, rc=rc)
307  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
308  line=__line__, &
309  file=__file__)) &
310  return
311 
312  grid_attach_area = .false.
313  call nuopc_compattributeget(gcomp, name="GridAttachArea", value=value, &
314  ispresent=ispresent, isset=isset, rc=rc)
315  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
316  line=__line__, &
317  file=__file__)) &
318  return
319  if (ispresent .and. isset) grid_attach_area=(trim(value)=="true")
320  write(logmsg,*) grid_attach_area
321  call esmf_logwrite('MOM_cap:GridAttachArea = '//trim(logmsg), esmf_logmsg_info, rc=rc)
322  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
323  line=__line__, &
324  file=__file__)) &
325  return
326 
327  scalar_field_name = ""
328  call nuopc_compattributeget(gcomp, name="ScalarFieldName", value=value, &
329  ispresent=ispresent, isset=isset, rc=rc)
330  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
331  line=__line__, &
332  file=__file__)) &
333  return
334  if (ispresent .and. isset) then
335  scalar_field_name = trim(value)
336  call esmf_logwrite('MOM_cap:ScalarFieldName = '//trim(scalar_field_name), esmf_logmsg_info, rc=rc)
337  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
338  line=__line__, &
339  file=__file__)) &
340  return
341  endif
342 
344  call nuopc_compattributeget(gcomp, name="ScalarFieldCount", value=value, &
345  ispresent=ispresent, isset=isset, rc=rc)
346  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
347  line=__line__, &
348  file=__file__)) &
349  return
350  if (ispresent .and. isset) then
351  read(value, '(i)', iostat=iostat) scalar_field_count
352  if (iostat /= 0) then
353  call esmf_logseterror(esmf_rc_arg_bad, &
354  msg=subname//": ScalarFieldCount not an integer: "//trim(value), &
355  line=__line__, file=__file__, rctoreturn=rc)
356  return
357  endif
358  write(logmsg,*) scalar_field_count
359  call esmf_logwrite('MOM_cap:ScalarFieldCount = '//trim(logmsg), esmf_logmsg_info, rc=rc)
360  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
361  line=__line__, &
362  file=__file__)) &
363  return
364  endif
365 
367  call nuopc_compattributeget(gcomp, name="ScalarFieldIdxGridNX", value=value, &
368  ispresent=ispresent, isset=isset, rc=rc)
369  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
370  line=__line__, &
371  file=__file__)) &
372  return
373  if (ispresent .and. isset) then
374  read(value, '(i)', iostat=iostat) scalar_field_idx_grid_nx
375  if (iostat /= 0) then
376  call esmf_logseterror(esmf_rc_arg_bad, &
377  msg=subname//": ScalarFieldIdxGridNX not an integer: "//trim(value), &
378  line=__line__, file=__file__, rctoreturn=rc)
379  return
380  endif
381  write(logmsg,*) scalar_field_idx_grid_nx
382  call esmf_logwrite('MOM_cap:ScalarFieldIdxGridNX = '//trim(logmsg), esmf_logmsg_info, rc=rc)
383  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
384  line=__line__, &
385  file=__file__)) &
386  return
387  endif
388 
390  call nuopc_compattributeget(gcomp, name="ScalarFieldIdxGridNY", value=value, &
391  ispresent=ispresent, isset=isset, rc=rc)
392  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
393  line=__line__, &
394  file=__file__)) &
395  return
396  if (ispresent .and. isset) then
397  read(value, '(i)', iostat=iostat) scalar_field_idx_grid_ny
398  if (iostat /= 0) then
399  call esmf_logseterror(esmf_rc_arg_bad, &
400  msg=subname//": ScalarFieldIdxGridNY not an integer: "//trim(value), &
401  line=__line__, file=__file__, rctoreturn=rc)
402  return
403  endif
404  write(logmsg,*) scalar_field_idx_grid_ny
405  call esmf_logwrite('MOM_cap:ScalarFieldIdxGridNY = '//trim(logmsg), esmf_logmsg_info, rc=rc)
406  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
407  line=__line__, &
408  file=__file__)) &
409  return
410  endif
411 
412  call nuopc_compattributeadd(gcomp, &
413  attrlist=(/'RestartFileToRead', 'RestartFileToWrite'/), rc=rc)
414  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
415  line=__line__, &
416  file=__file__)) &
417  return
418 
419 end subroutine
420 
421 !> Called by NUOPC to advertise import and export fields. "Advertise"
422 !! simply means that the standard names of all import and export
423 !! fields are supplied. The NUOPC layer uses these to match fields
424 !! between components in the coupled system.
425 !!
426 !! @param gcomp an ESMF_GridComp object
427 !! @param importState an ESMF_State object for import fields
428 !! @param exportState an ESMF_State object for export fields
429 !! @param clock an ESMF_Clock object
430 !! @param rc return code
431 subroutine initializeadvertise(gcomp, importState, exportState, clock, rc)
432  type(esmf_gridcomp) :: gcomp !< ESMF_GridComp object
433  type(esmf_state) :: importState, exportState !< ESMF_State object for
434  !! import/export fields
435  type(esmf_clock) :: clock !< ESMF_Clock object
436  integer, intent(out) :: rc !< return code
437 
438  ! local variables
439  type(esmf_vm) :: vm
440  type(esmf_time) :: MyTime
441  type(esmf_timeinterval) :: TINT
442  type (ocean_public_type), pointer :: ocean_public => null()
443  type (ocean_state_type), pointer :: ocean_state => null()
444  type(ice_ocean_boundary_type), pointer :: Ice_ocean_boundary => null()
445  type(ocean_internalstate_wrapper) :: ocean_internalstate
446  type(ocean_grid_type), pointer :: ocean_grid => null()
447  type(time_type) :: Run_len !< length of experiment
448  type(time_type) :: time0 !< Start time of coupled model's calendar.
449  type(time_type) :: time_start !< The time at which to initialize the ocean model
450  type(time_type) :: Time_restart
451  type(time_type) :: DT
452  integer :: DT_OCEAN
453  integer :: isc,iec,jsc,jec
454  integer :: year=0, month=0, day=0, hour=0, minute=0, second=0
455  integer :: mpi_comm_mom
456  integer :: i,n
457  character(len=256) :: stdname, shortname
458  character(len=32) :: starttype ! model start type
459  character(len=512) :: diro
460  character(len=512) :: logfile
461  character(ESMF_MAXSTR) :: cvalue
462  logical :: isPresent, isPresentDiro, isPresentLogfile, isSet
463  logical :: existflag
464  integer :: userRc
465  character(len=512) :: restartfile ! Path/Name of restart file
466  character(len=*), parameter :: subname='(MOM_cap:InitializeAdvertise)'
467  character(len=32) :: calendar
468 !--------------------------------
469 
470  rc = esmf_success
471 
472  call esmf_logwrite(subname//' enter', esmf_logmsg_info, rc=rc)
473  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
474  line=__line__, &
475  file=__file__)) &
476  return
477 
478  allocate(ice_ocean_boundary)
479  !allocate(ocean_state) ! ocean_model_init allocate this pointer
480  allocate(ocean_public)
481  allocate(ocean_internalstate%ptr)
482  ocean_internalstate%ptr%ice_ocean_boundary_type_ptr => ice_ocean_boundary
483  ocean_internalstate%ptr%ocean_public_type_ptr => ocean_public
484  ocean_internalstate%ptr%ocean_state_type_ptr => ocean_state
485 
486  call esmf_vmgetcurrent(vm, rc=rc)
487  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
488  line=__line__, &
489  file=__file__)) &
490  return ! bail out
491 
492  call esmf_vmget(vm, mpicommunicator=mpi_comm_mom, rc=rc)
493  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
494  line=__line__, &
495  file=__file__)) &
496  return ! bail out
497 
498  call esmf_clockget(clock, currtime=mytime, timestep=tint, rc=rc)
499  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
500  line=__line__, &
501  file=__file__)) &
502  return ! bail out
503 
504  call esmf_timeget (mytime, yy=year, mm=month, dd=day, h=hour, m=minute, s=second, rc=rc )
505  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
506  line=__line__, &
507  file=__file__)) &
508  return ! bail out
509 
510  CALL esmf_timeintervalget(tint, s=dt_ocean, rc=rc)
511  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
512  line=__line__, &
513  file=__file__)) &
514  return ! bail out
515 
516  call fms_init(mpi_comm_mom)
517  call constants_init
518  call field_manager_init
519 
520  ! determine the calendar
521  if (cesm_coupled) then
522  call nuopc_compattributeget(gcomp, name="calendar", value=cvalue, &
523  ispresent=ispresent, isset=isset, rc=rc)
524  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
525  line=__line__, &
526  file=__file__)) &
527  return ! bail out
528  if (ispresent .and. isset) then
529  read(cvalue,*) calendar
530  select case (trim(calendar))
531  case ("NO_LEAP")
532  call set_calendar_type (noleap)
533  case ("GREGORIAN")
534  call set_calendar_type (gregorian)
535  case default
536  call esmf_logseterror(esmf_rc_arg_bad, &
537  msg=subname//": Calendar not supported in MOM6: "//trim(calendar), &
538  line=__line__, file=__file__, rctoreturn=rc)
539  end select
540  else
541  call set_calendar_type (noleap)
542  endif
543 
544  else
545  call set_calendar_type (julian)
546  endif
547 
548  call diag_manager_init
549 
550  ! this ocean connector will be driven at set interval
551  dt = set_time(dt_ocean, 0)
552  ! get current time
553  time_start = set_date(year,month,day,hour,minute,second)
554 
555  if (is_root_pe()) then
556  write(logunit,*) subname//'current time: y,m,d-',year,month,day,'h,m,s=',hour,minute,second
557  endif
558 
559  ! get start/reference time
560  call esmf_clockget(clock, reftime=mytime, rc=rc)
561  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
562  line=__line__, &
563  file=__file__)) &
564  return ! bail out
565 
566  call esmf_timeget (mytime, yy=year, mm=month, dd=day, h=hour, m=minute, s=second, rc=rc )
567  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
568  line=__line__, &
569  file=__file__)) &
570  return ! bail out
571 
572  time0 = set_date(year,month,day,hour,minute,second)
573 
574  if (is_root_pe()) then
575  write(logunit,*) subname//'start time: y,m,d-',year,month,day,'h,m,s=',hour,minute,second
576  endif
577 
578  ! rsd need to figure out how to get this without share code
579  !call shr_nuopc_get_component_instance(gcomp, inst_suffix, inst_index)
580  !inst_name = "OCN"//trim(inst_suffix)
581 
582  ! reset shr logging to my log file
583  if (is_root_pe()) then
584  call nuopc_compattributeget(gcomp, name="diro", &
585  ispresent=ispresentdiro, rc=rc)
586  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
587  line=__line__, &
588  file=__file__)) &
589  return
590  call nuopc_compattributeget(gcomp, name="logfile", &
591  ispresent=ispresentlogfile, rc=rc)
592  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
593  line=__line__, &
594  file=__file__)) &
595  return
596  if (ispresentdiro .and. ispresentlogfile) then
597  call nuopc_compattributeget(gcomp, name="diro", value=diro, rc=rc)
598  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
599  line=__line__, &
600  file=__file__)) &
601  return
602  call nuopc_compattributeget(gcomp, name="logfile", value=logfile, rc=rc)
603  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
604  line=__line__, &
605  file=__file__)) &
606  return
607  open(newunit=logunit,file=trim(diro)//"/"//trim(logfile))
608  else
609  logunit = output_unit
610  endif
611  else
612  logunit = output_unit
613  endif
614 
615  starttype = ""
616  call nuopc_compattributeget(gcomp, name='start_type', value=cvalue, &
617  ispresent=ispresent, isset=isset, rc=rc)
618  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
619  line=__line__, &
620  file=__file__)) &
621  return
622  if (ispresent .and. isset) then
623  read(cvalue,*) starttype
624  else
625  call esmf_logwrite('MOM_cap:start_type unset - using input.nml for restart option', &
626  esmf_logmsg_info, rc=rc)
627  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
628  line=__line__, &
629  file=__file__)) &
630  return
631  endif
632 
633  runtype = ""
634  if (trim(starttype) == trim('startup')) then
635  runtype = "initial"
636  else if (trim(starttype) == trim('continue') ) then
637  runtype = "continue"
638  else if (trim(starttype) == trim('branch')) then
639  runtype = "continue"
640  else if (len_trim(starttype) > 0) then
641  call esmf_logseterror(esmf_rc_arg_bad, &
642  msg=subname//": unknown starttype - "//trim(starttype), &
643  line=__line__, file=__file__, rctoreturn=rc)
644  return
645  endif
646 
647  if (len_trim(runtype) > 0) then
648  call esmf_logwrite('MOM_cap:startup = '//trim(runtype), esmf_logmsg_info, rc=rc)
649  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
650  line=__line__, &
651  file=__file__)) &
652  return
653  endif
654 
655  restartfile = ""
656  if (runtype == "initial") then
657  ! startup (new run) - 'n' is needed below if we don't specify input_filename in input.nml
658  restartfile = "n"
659  else if (runtype == "continue") then ! hybrid or branch or continuos runs
660 
661  ! optionally call into system-specific implementation to get restart file name
662  call esmf_methodexecute(gcomp, label="GetRestartFileToRead", &
663  existflag=existflag, userrc=userrc, rc=rc)
664  if (esmf_logfounderror(rctocheck=rc, msg="Error executing user method to get restart filename", &
665  line=__line__, &
666  file=__file__)) &
667  return ! bail out
668  if (esmf_logfounderror(rctocheck=userrc, msg="Error in method to get restart filename", &
669  line=__line__, &
670  file=__file__)) &
671  return ! bail out
672  if (existflag) then
673  call esmf_logwrite('MOM_cap: called user GetRestartFileToRead', esmf_logmsg_info, rc=rc)
674  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
675  line=__line__, &
676  file=__file__)) &
677  return
678  endif
679 
680  call nuopc_compattributeget(gcomp, name='RestartFileToRead', &
681  value=cvalue, ispresent=ispresent, isset=isset, rc=rc)
682  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
683  line=__line__, &
684  file=__file__)) &
685  return
686  if (ispresent .and. isset) then
687  restartfile = trim(cvalue)
688  call esmf_logwrite('MOM_cap: RestartFileToRead = '//trim(restartfile), esmf_logmsg_info, rc=rc)
689  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
690  line=__line__, &
691  file=__file__)) &
692  return
693  else
694  call esmf_logwrite('MOM_cap: restart requested, no RestartFileToRead attribute provided-will use input.nml',&
695  esmf_logmsg_warning, rc=rc)
696  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
697  line=__line__, &
698  file=__file__)) &
699  return
700  endif
701 
702  endif
703 
704  ocean_public%is_ocean_pe = .true.
705  call ocean_model_init(ocean_public, ocean_state, time0, time_start, input_restart_file=trim(restartfile))
706 
707  call ocean_model_init_sfc(ocean_state, ocean_public)
708 
709  call mpp_get_compute_domain(ocean_public%domain, isc, iec, jsc, jec)
710 
711  allocate ( ice_ocean_boundary% u_flux (isc:iec,jsc:jec), &
712  ice_ocean_boundary% v_flux (isc:iec,jsc:jec), &
713  ice_ocean_boundary% t_flux (isc:iec,jsc:jec), &
714  ice_ocean_boundary% q_flux (isc:iec,jsc:jec), &
715  ice_ocean_boundary% salt_flux (isc:iec,jsc:jec), &
716  ice_ocean_boundary% lw_flux (isc:iec,jsc:jec), &
717  ice_ocean_boundary% sw_flux_vis_dir (isc:iec,jsc:jec), &
718  ice_ocean_boundary% sw_flux_vis_dif (isc:iec,jsc:jec), &
719  ice_ocean_boundary% sw_flux_nir_dir (isc:iec,jsc:jec), &
720  ice_ocean_boundary% sw_flux_nir_dif (isc:iec,jsc:jec), &
721  ice_ocean_boundary% lprec (isc:iec,jsc:jec), &
722  ice_ocean_boundary% fprec (isc:iec,jsc:jec), &
723  ice_ocean_boundary% seaice_melt_heat (isc:iec,jsc:jec),&
724  ice_ocean_boundary% seaice_melt (isc:iec,jsc:jec), &
725  ice_ocean_boundary% mi (isc:iec,jsc:jec), &
726  ice_ocean_boundary% p (isc:iec,jsc:jec), &
727  ice_ocean_boundary% lrunoff_hflx (isc:iec,jsc:jec), &
728  ice_ocean_boundary% frunoff_hflx (isc:iec,jsc:jec), &
729  ice_ocean_boundary% lrunoff (isc:iec,jsc:jec), &
730  ice_ocean_boundary% frunoff (isc:iec,jsc:jec))
731 
732  ice_ocean_boundary%u_flux = 0.0
733  ice_ocean_boundary%v_flux = 0.0
734  ice_ocean_boundary%t_flux = 0.0
735  ice_ocean_boundary%q_flux = 0.0
736  ice_ocean_boundary%salt_flux = 0.0
737  ice_ocean_boundary%lw_flux = 0.0
738  ice_ocean_boundary%sw_flux_vis_dir = 0.0
739  ice_ocean_boundary%sw_flux_vis_dif = 0.0
740  ice_ocean_boundary%sw_flux_nir_dir = 0.0
741  ice_ocean_boundary%sw_flux_nir_dif = 0.0
742  ice_ocean_boundary%lprec = 0.0
743  ice_ocean_boundary%fprec = 0.0
744  ice_ocean_boundary%seaice_melt = 0.0
745  ice_ocean_boundary%seaice_melt_heat= 0.0
746  ice_ocean_boundary%mi = 0.0
747  ice_ocean_boundary%p = 0.0
748  ice_ocean_boundary%lrunoff_hflx = 0.0
749  ice_ocean_boundary%frunoff_hflx = 0.0
750  ice_ocean_boundary%lrunoff = 0.0
751  ice_ocean_boundary%frunoff = 0.0
752 
753  ocean_internalstate%ptr%ocean_state_type_ptr => ocean_state
754  call esmf_gridcompsetinternalstate(gcomp, ocean_internalstate, rc)
755  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
756  line=__line__, &
757  file=__file__)) &
758  return ! bail out
759 
760  if (len_trim(scalar_field_name) > 0) then
761  call fld_list_add(fldstoocn_num, fldstoocn, trim(scalar_field_name), "will_provide")
762  call fld_list_add(fldsfrocn_num, fldsfrocn, trim(scalar_field_name), "will_provide")
763  end if
764 
765  if (cesm_coupled) then
766  !call fld_list_add(fldsToOcn_num, fldsToOcn, "Sw_lamult" , "will provide")
767  !call fld_list_add(fldsToOcn_num, fldsToOcn, "Sw_ustokes" , "will provide")
768  !call fld_list_add(fldsToOcn_num, fldsToOcn, "Sw_vstokes" , "will provide")
769  !call fld_list_add(fldsToOcn_num, fldsToOcn, "Sw_hstokes" , "will provide")
770  !call fld_list_add(fldsToOcn_num, fldsToOcn, "Fioi_melth" , "will provide")
771  !call fld_list_add(fldsToOcn_num, fldsToOcn, "Fioi_meltw" , "will provide")
772  !call fld_list_add(fldsFrOcn_num, fldsFrOcn, "So_fswpen" , "will provide")
773  else
774  !call fld_list_add(fldsToOcn_num, fldsToOcn, "mass_of_overlying_sea_ice" , "will provide")
775  !call fld_list_add(fldsFrOcn_num, fldsFrOcn, "sea_lev" , "will provide")
776  endif
777 
778  !--------- import fields -------------
779  call fld_list_add(fldstoocn_num, fldstoocn, "mean_salt_rate" , "will provide") ! from ice
780  call fld_list_add(fldstoocn_num, fldstoocn, "mean_zonal_moment_flx" , "will provide")
781  call fld_list_add(fldstoocn_num, fldstoocn, "mean_merid_moment_flx" , "will provide")
782  call fld_list_add(fldstoocn_num, fldstoocn, "mean_sensi_heat_flx" , "will provide")
783  call fld_list_add(fldstoocn_num, fldstoocn, "mean_evap_rate" , "will provide")
784  call fld_list_add(fldstoocn_num, fldstoocn, "mean_net_lw_flx" , "will provide")
785  call fld_list_add(fldstoocn_num, fldstoocn, "mean_net_sw_vis_dir_flx" , "will provide")
786  call fld_list_add(fldstoocn_num, fldstoocn, "mean_net_sw_vis_dif_flx" , "will provide")
787  call fld_list_add(fldstoocn_num, fldstoocn, "mean_net_sw_ir_dir_flx" , "will provide")
788  call fld_list_add(fldstoocn_num, fldstoocn, "mean_net_sw_ir_dif_flx" , "will provide")
789  call fld_list_add(fldstoocn_num, fldstoocn, "mean_prec_rate" , "will provide")
790  call fld_list_add(fldstoocn_num, fldstoocn, "mean_fprec_rate" , "will provide")
791  call fld_list_add(fldstoocn_num, fldstoocn, "inst_pres_height_surface" , "will provide")
792  call fld_list_add(fldstoocn_num, fldstoocn, "Foxx_rofl" , "will provide") !-> liquid runoff
793  call fld_list_add(fldstoocn_num, fldstoocn, "Foxx_rofi" , "will provide") !-> ice runoff
794  call fld_list_add(fldstoocn_num, fldstoocn, "mean_fresh_water_to_ocean_rate", "will provide")
795  call fld_list_add(fldstoocn_num, fldstoocn, "net_heat_flx_to_ocn" , "will provide")
796  !These are not currently used and changing requires a nuopc dictionary change
797  !call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_runoff_heat_flx" , "will provide")
798  !call fld_list_add(fldsToOcn_num, fldsToOcn, "mean_calving_heat_flx" , "will provide")
799 
800  !--------- export fields -------------
801  call fld_list_add(fldsfrocn_num, fldsfrocn, "ocean_mask" , "will provide")
802  call fld_list_add(fldsfrocn_num, fldsfrocn, "sea_surface_temperature" , "will provide")
803  call fld_list_add(fldsfrocn_num, fldsfrocn, "s_surf" , "will provide")
804  call fld_list_add(fldsfrocn_num, fldsfrocn, "ocn_current_zonal" , "will provide")
805  call fld_list_add(fldsfrocn_num, fldsfrocn, "ocn_current_merid" , "will provide")
806  call fld_list_add(fldsfrocn_num, fldsfrocn, "sea_surface_slope_zonal" , "will provide")
807  call fld_list_add(fldsfrocn_num, fldsfrocn, "sea_surface_slope_merid" , "will provide")
808  call fld_list_add(fldsfrocn_num, fldsfrocn, "freezing_melting_potential" , "will provide")
809  call fld_list_add(fldsfrocn_num, fldsfrocn, "So_bldepth" , "will provide")
810 
811  do n = 1,fldstoocn_num
812  call nuopc_advertise(importstate, standardname=fldstoocn(n)%stdname, name=fldstoocn(n)%shortname, rc=rc)
813  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
814  line=__line__, &
815  file=__file__)) &
816  return ! bail out
817  enddo
818 
819  do n = 1,fldsfrocn_num
820  call nuopc_advertise(exportstate, standardname=fldsfrocn(n)%stdname, name=fldsfrocn(n)%shortname, rc=rc)
821  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
822  line=__line__, &
823  file=__file__)) &
824  return ! bail out
825  enddo
826 
827 end subroutine initializeadvertise
828 
829 !> Called by NUOPC to realize import and export fields. "Realizing" a field
830 !! means that its grid has been defined and an ESMF_Field object has been
831 !! created and put into the import or export State.
832 !!
833 !! @param gcomp an ESMF_GridComp object
834 !! @param importState an ESMF_State object for import fields
835 !! @param exportState an ESMF_State object for export fields
836 !! @param clock an ESMF_Clock object
837 !! @param rc return code
838 subroutine initializerealize(gcomp, importState, exportState, clock, rc)
839  type(esmf_gridcomp) :: gcomp !< ESMF_GridComp object
840  type(esmf_state) :: importState, exportState !< ESMF_State object for
841  !! import/export fields
842  type(esmf_clock) :: clock !< ESMF_Clock object
843  integer, intent(out) :: rc !< return code
844 
845  ! Local Variables
846  type(esmf_vm) :: vm
847  type(esmf_grid) :: gridIn, gridOut
848  type(esmf_mesh) :: Emesh, EmeshTemp
849  type(esmf_delayout) :: delayout
850  type(esmf_distgrid) :: Distgrid
851  type(esmf_distgridconnection), allocatable :: connectionList(:)
852  type(esmf_stateitem_flag) :: itemFlag
853  type (ocean_public_type), pointer :: ocean_public => null()
854  type (ocean_state_type), pointer :: ocean_state => null()
855  type(ice_ocean_boundary_type), pointer :: Ice_ocean_boundary => null()
856  type(ocean_grid_type) , pointer :: ocean_grid
857  type(ocean_internalstate_wrapper) :: ocean_internalstate
858  integer :: npet, ntiles
859  integer :: nxg, nyg, cnt
860  integer :: isc,iec,jsc,jec
861  integer, allocatable :: xb(:),xe(:),yb(:),ye(:),pe(:)
862  integer, allocatable :: deBlockList(:,:,:)
863  integer, allocatable :: petMap(:)
864  integer, allocatable :: deLabelList(:)
865  integer, allocatable :: indexList(:)
866  integer :: ioff, joff
867  integer :: i, j, n, i1, j1, n1, jlast
868  integer :: lbnd1,ubnd1,lbnd2,ubnd2
869  integer :: lbnd3,ubnd3,lbnd4,ubnd4
870  integer :: nblocks_tot
871  logical :: found
872  integer(ESMF_KIND_I4), pointer :: dataPtr_mask(:,:)
873  real(ESMF_KIND_R8), pointer :: dataPtr_area(:,:)
874  real(ESMF_KIND_R8), pointer :: dataPtr_xcen(:,:)
875  real(ESMF_KIND_R8), pointer :: dataPtr_ycen(:,:)
876  real(ESMF_KIND_R8), pointer :: dataPtr_xcor(:,:)
877  real(ESMF_KIND_R8), pointer :: dataPtr_ycor(:,:)
878  integer :: mpicom
879  integer :: localPet
880  integer :: lsize
881  integer :: ig,jg, ni,nj,k
882  integer, allocatable :: gindex(:) ! global index space
883  character(len=128) :: fldname
884  character(len=256) :: cvalue
885  character(len=256) :: frmt ! format specifier for several error msgs
886  character(len=512) :: err_msg ! error messages
887  character(len=*), parameter :: subname='(MOM_cap:InitializeRealize)'
888  integer :: spatialDim
889  integer :: numOwnedElements
890  type(esmf_array) :: elemMaskArray
891  real(ESMF_KIND_R8) , pointer :: ownedElemCoords(:)
892  real(ESMF_KIND_R8) , pointer :: lat(:), latMesh(:)
893  real(ESMF_KIND_R8) , pointer :: lon(:), lonMesh(:)
894  integer(ESMF_KIND_I4) , pointer :: mask(:), maskMesh(:)
895  real(ESMF_KIND_R8) :: diff_lon, diff_lat
896  real :: eps_omesh
897  !--------------------------------
898 
899  rc = esmf_success
900 
902 
903  !----------------------------------------------------------------------------
904  ! Get pointers to ocean internal state
905  !----------------------------------------------------------------------------
906 
907  call esmf_gridcompgetinternalstate(gcomp, ocean_internalstate, rc)
908  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
909  line=__line__, &
910  file=__file__)) &
911  return ! bail out
912 
913  ice_ocean_boundary => ocean_internalstate%ptr%ice_ocean_boundary_type_ptr
914  ocean_public => ocean_internalstate%ptr%ocean_public_type_ptr
915  ocean_state => ocean_internalstate%ptr%ocean_state_type_ptr
916 
917  !----------------------------------------------------------------------------
918  ! Get mpi information
919  !----------------------------------------------------------------------------
920 
921  call esmf_vmgetcurrent(vm, rc=rc)
922  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
923  line=__line__, &
924  file=__file__)) &
925  return ! bail out
926 
927  call esmf_vmget(vm, petcount=npet, mpicommunicator=mpicom, localpet=localpet, rc=rc)
928  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
929  line=__line__, &
930  file=__file__)) &
931  return ! bail out
932 
933  !---------------------------------
934  ! global mom grid size
935  !---------------------------------
936 
937  call mpp_get_global_domain(ocean_public%domain, xsize=nxg, ysize=nyg)
938  write(tmpstr,'(a,2i6)') subname//' nxg,nyg = ',nxg,nyg
939  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
940  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
941  line=__line__, &
942  file=__file__)) &
943  return ! bail out
944 
945  !---------------------------------
946  ! number of tiles per PET, assumed to be 1, and number of pes (tiles) total
947  !---------------------------------
948 
949  ntiles=mpp_get_ntile_count(ocean_public%domain) ! this is tiles on this pe
950  if (ntiles /= 1) then
951  rc = esmf_failure
952  call esmf_logwrite(subname//' ntiles must be 1', esmf_logmsg_error, rc=rc)
953  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
954  line=__line__, &
955  file=__file__)) &
956  return
957  endif
958  ntiles=mpp_get_domain_npes(ocean_public%domain)
959  write(tmpstr,'(a,1i6)') subname//' ntiles = ',ntiles
960  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
961  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
962  line=__line__, &
963  file=__file__)) &
964  return
965 
966  !---------------------------------
967  ! get start and end indices of each tile and their PET
968  !---------------------------------
969 
970  allocate(xb(ntiles),xe(ntiles),yb(ntiles),ye(ntiles),pe(ntiles))
971  call mpp_get_compute_domains(ocean_public%domain, xbegin=xb, xend=xe, ybegin=yb, yend=ye)
972  call mpp_get_pelist(ocean_public%domain, pe)
973  if (debug > 0) then
974  do n = 1,ntiles
975  write(tmpstr,'(a,6i6)') subname//' tiles ',n,pe(n),xb(n),xe(n),yb(n),ye(n)
976  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
977  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
978  line=__line__, &
979  file=__file__)) &
980  return
981  enddo
982  endif
983 
984  !---------------------------------
985  ! Create either a grid or a mesh
986  !---------------------------------
987 
988  !Get the ocean grid and sizes of global and computational domains
989  call get_ocean_grid(ocean_state, ocean_grid)
990 
991  if (geomtype == esmf_geomtype_mesh) then
992 
993  !---------------------------------
994  ! Create a MOM6 mesh
995  !---------------------------------
996 
997  call get_global_grid_size(ocean_grid, ni, nj)
998  lsize = ( ocean_grid%iec - ocean_grid%isc + 1 ) * ( ocean_grid%jec - ocean_grid%jsc + 1 )
999 
1000  ! Create the global index space for the computational domain
1001  allocate(gindex(lsize))
1002  k = 0
1003  do j = ocean_grid%jsc, ocean_grid%jec
1004  jg = j + ocean_grid%jdg_offset
1005  do i = ocean_grid%isc, ocean_grid%iec
1006  ig = i + ocean_grid%idg_offset
1007  k = k + 1 ! Increment position within gindex
1008  gindex(k) = ni * (jg - 1) + ig
1009  enddo
1010  enddo
1011 
1012  distgrid = esmf_distgridcreate(arbseqindexlist=gindex, rc=rc)
1013  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1014  line=__line__, &
1015  file=__file__)) &
1016  return
1017 
1018  ! read in the mesh
1019  call nuopc_compattributeget(gcomp, name='mesh_ocn', value=cvalue, rc=rc)
1020  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1021  line=__line__, &
1022  file=__file__)) &
1023  return
1024 
1025  emeshtemp = esmf_meshcreate(filename=trim(cvalue), fileformat=esmf_fileformat_esmfmesh, rc=rc)
1026  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1027  line=__line__, &
1028  file=__file__)) &
1029  return
1030 
1031  if (localpet == 0) then
1032  write(logunit,*)'mesh file for mom6 domain is ',trim(cvalue)
1033  endif
1034 
1035  ! recreate the mesh using the above distGrid
1036  emesh = esmf_meshcreate(emeshtemp, elementdistgrid=distgrid, rc=rc)
1037  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1038  line=__line__, &
1039  file=__file__)) &
1040  return
1041 
1042  ! Check for consistency of lat, lon and mask between mesh and mom6 grid
1043  call esmf_meshget(emesh, spatialdim=spatialdim, numownedelements=numownedelements, rc=rc)
1044  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1045  line=__line__, &
1046  file=__file__)) &
1047  return
1048 
1049  allocate(ownedelemcoords(spatialdim*numownedelements))
1050  allocate(lonmesh(numownedelements), lon(numownedelements))
1051  allocate(latmesh(numownedelements), lat(numownedelements))
1052  allocate(maskmesh(numownedelements), mask(numownedelements))
1053 
1054  call esmf_meshget(emesh, ownedelemcoords=ownedelemcoords, rc=rc)
1055  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1056  line=__line__, &
1057  file=__file__)) &
1058  return
1059  do n = 1,numownedelements
1060  lonmesh(n) = ownedelemcoords(2*n-1)
1061  latmesh(n) = ownedelemcoords(2*n)
1062  end do
1063 
1064  elemmaskarray = esmf_arraycreate(distgrid, maskmesh, rc=rc)
1065  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1066  line=__line__, &
1067  file=__file__)) &
1068  return
1069  call esmf_meshget(emesh, elemmaskarray=elemmaskarray, rc=rc)
1070  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1071  line=__line__, &
1072  file=__file__)) &
1073  return
1074 
1075  call mpp_get_compute_domain(ocean_public%domain, isc, iec, jsc, jec)
1076  n = 0
1077  do j = jsc, jec
1078  jg = j + ocean_grid%jsc - jsc
1079  do i = isc, iec
1080  ig = i + ocean_grid%isc - isc
1081  n = n+1
1082  mask(n) = ocean_grid%mask2dT(ig,jg)
1083  lon(n) = ocean_grid%geolonT(ig,jg)
1084  lat(n) = ocean_grid%geolatT(ig,jg)
1085  end do
1086  end do
1087 
1088  eps_omesh = get_eps_omesh(ocean_state)
1089  do n = 1,numownedelements
1090  diff_lon = abs(mod(lonmesh(n) - lon(n),360.0))
1091  if (diff_lon > eps_omesh) then
1092  frmt = "('ERROR: Difference between ESMF Mesh and MOM6 domain coords is "//&
1093  "greater than parameter EPS_OMESH. n, lonMesh(n), lon(n), diff_lon, "//&
1094  "EPS_OMESH= ',i8,2(f21.13,3x),2(d21.5))"
1095  write(err_msg, frmt)n,lonmesh(n),lon(n), diff_lon, eps_omesh
1096  call mom_error(fatal, err_msg)
1097  end if
1098  diff_lat = abs(latmesh(n) - lat(n))
1099  if (diff_lat > eps_omesh) then
1100  frmt = "('ERROR: Difference between ESMF Mesh and MOM6 domain coords is"//&
1101  "greater than parameter EPS_OMESH. n, latMesh(n), lat(n), diff_lat, "//&
1102  "EPS_OMESH= ',i8,2(f21.13,3x),2(d21.5))"
1103  write(err_msg, frmt)n,latmesh(n),lat(n), diff_lat, eps_omesh
1104  call mom_error(fatal, err_msg)
1105  end if
1106  if (abs(maskmesh(n) - mask(n)) > 0) then
1107  frmt = "('ERROR: ESMF mesh and MOM6 domain masks are inconsistent! - "//&
1108  "MOM n, maskMesh(n), mask(n) = ',3(i8,2x))"
1109  write(err_msg, frmt)n,maskmesh(n),mask(n)
1110  call mom_error(fatal, err_msg)
1111  end if
1112  end do
1113 
1114  deallocate(ownedelemcoords)
1115  deallocate(lonmesh , lon )
1116  deallocate(latmesh , lat )
1117  deallocate(maskmesh, mask)
1118  ! realize the import and export fields using the mesh
1119  call mom_realizefields(importstate, fldstoocn_num, fldstoocn, "Ocn import", mesh=emesh, rc=rc)
1120  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1121  line=__line__, &
1122  file=__file__)) &
1123  return
1124 
1125  call mom_realizefields(exportstate, fldsfrocn_num, fldsfrocn, "Ocn export", mesh=emesh, rc=rc)
1126  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1127  line=__line__, &
1128  file=__file__)) &
1129  return
1130 
1131  else if (geomtype == esmf_geomtype_grid) then
1132 
1133  !---------------------------------
1134  ! create a MOM6 grid
1135  !---------------------------------
1136 
1137  ! generate delayout and dist_grid
1138 
1139  allocate(deblocklist(2,2,ntiles))
1140  allocate(petmap(ntiles))
1141  allocate(delabellist(ntiles))
1142 
1143  do n = 1, ntiles
1144  delabellist(n) = n
1145  deblocklist(1,1,n) = xb(n)
1146  deblocklist(1,2,n) = xe(n)
1147  deblocklist(2,1,n) = yb(n)
1148  deblocklist(2,2,n) = ye(n)
1149  petmap(n) = pe(n)
1150  ! write(tmpstr,'(a,3i8)') subname//' iglo = ',n,deBlockList(1,1,n),deBlockList(1,2,n)
1151  ! call ESMF_LogWrite(trim(tmpstr), ESMF_LOGMSG_INFO, rc=rc)
1152  ! write(tmpstr,'(a,3i8)') subname//' jglo = ',n,deBlockList(2,1,n),deBlockList(2,2,n)
1153  ! call ESMF_LogWrite(trim(tmpstr), ESMF_LOGMSG_INFO, rc=rc)
1154  ! write(tmpstr,'(a,2i8)') subname//' pe = ',n,petMap(n)
1155  ! call ESMF_LogWrite(trim(tmpstr), ESMF_LOGMSG_INFO, rc=rc)
1156  !--- assume a tile with starting index of 1 has an equivalent wraparound tile on the other side
1157  enddo
1158 
1159  delayout = esmf_delayoutcreate(petmap, rc=rc)
1160  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1161  line=__line__, &
1162  file=__file__)) &
1163  return ! bail out
1164 
1165  ! rsd this assumes tripole grid, but sometimes in CESM a bipole
1166  ! grid is used -- need to introduce conditional logic here
1167 
1168  allocate(connectionlist(2))
1169 
1170  ! bipolar boundary condition at top row: nyg
1171  call esmf_distgridconnectionset(connectionlist(1), tileindexa=1, &
1172  tileindexb=1, positionvector=(/nxg+1, 2*nyg+1/), &
1173  orientationvector=(/-1, -2/), rc=rc)
1174  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1175  line=__line__, &
1176  file=__file__)) &
1177  return ! bail out
1178 
1179  ! periodic boundary condition along first dimension
1180  call esmf_distgridconnectionset(connectionlist(2), tileindexa=1, &
1181  tileindexb=1, positionvector=(/nxg, 0/), rc=rc)
1182  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1183  line=__line__, &
1184  file=__file__)) &
1185  return
1186 
1187  distgrid = esmf_distgridcreate(minindex=(/1,1/), maxindex=(/nxg,nyg/), &
1188  ! indexflag = ESMF_INDEX_DELOCAL, &
1189  deblocklist=deblocklist, &
1190  ! deLabelList=deLabelList, &
1191  delayout=delayout, &
1192  connectionlist=connectionlist, &
1193  rc=rc)
1194  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1195  line=__line__, &
1196  file=__file__)) &
1197  return
1198 
1199  deallocate(xb,xe,yb,ye,pe)
1200  deallocate(connectionlist)
1201  deallocate(delabellist)
1202  deallocate(deblocklist)
1203  deallocate(petmap)
1204 
1205  call esmf_distgridget(distgrid=distgrid, localde=0, elementcount=cnt, rc=rc)
1206  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1207  line=__line__, &
1208  file=__file__)) &
1209  return
1210 
1211  allocate(indexlist(cnt))
1212  write(tmpstr,'(a,i8)') subname//' distgrid cnt= ',cnt
1213  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1214  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1215  line=__line__, &
1216  file=__file__)) &
1217  return
1218 
1219  call esmf_distgridget(distgrid=distgrid, localde=0, seqindexlist=indexlist, rc=rc)
1220  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1221  line=__line__, &
1222  file=__file__)) &
1223  return
1224 
1225  write(tmpstr,'(a,4i8)') subname//' distgrid list= ',&
1226  indexlist(1),indexlist(cnt),minval(indexlist), maxval(indexlist)
1227  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1228  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1229  line=__line__, &
1230  file=__file__)) &
1231  return
1232 
1233  deallocate(indexlist)
1234 
1235  ! create grid
1236 
1237  gridin = esmf_gridcreate(distgrid=distgrid, &
1238  gridedgelwidth=(/0,0/), gridedgeuwidth=(/0,1/), &
1239  coordsys = esmf_coordsys_sph_deg, &
1240  rc = rc)
1241  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1242  line=__line__, &
1243  file=__file__)) &
1244  return
1245 
1246 
1247  call esmf_gridaddcoord(gridin, staggerloc=esmf_staggerloc_center, rc=rc)
1248  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1249  line=__line__, &
1250  file=__file__)) &
1251  return
1252 
1253  call esmf_gridaddcoord(gridin, staggerloc=esmf_staggerloc_corner, rc=rc)
1254  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1255  line=__line__, &
1256  file=__file__)) &
1257  return
1258 
1259  call esmf_gridadditem(gridin, itemflag=esmf_griditem_mask, itemtypekind=esmf_typekind_i4, &
1260  staggerloc=esmf_staggerloc_center, rc=rc)
1261  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1262  line=__line__, &
1263  file=__file__)) &
1264  return
1265 
1266  ! Attach area to the Grid optionally. By default the cell areas are computed.
1267  if(grid_attach_area) then
1268  call esmf_gridadditem(gridin, itemflag=esmf_griditem_area, itemtypekind=esmf_typekind_r8, &
1269  staggerloc=esmf_staggerloc_center, rc=rc)
1270  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1271  line=__line__, &
1272  file=__file__)) &
1273  return
1274 
1275  endif
1276 
1277  call esmf_gridgetcoord(gridin, coorddim=1, &
1278  staggerloc=esmf_staggerloc_center, &
1279  farrayptr=dataptr_xcen, rc=rc)
1280  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1281  line=__line__, &
1282  file=__file__)) &
1283  return
1284 
1285  call esmf_gridgetcoord(gridin, coorddim=2, &
1286  staggerloc=esmf_staggerloc_center, &
1287  farrayptr=dataptr_ycen, rc=rc)
1288  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1289  line=__line__, &
1290  file=__file__)) &
1291  return
1292 
1293 
1294  call esmf_gridgetcoord(gridin, coorddim=1, &
1295  staggerloc=esmf_staggerloc_corner, &
1296  farrayptr=dataptr_xcor, rc=rc)
1297  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1298  line=__line__, &
1299  file=__file__)) &
1300  return
1301 
1302  call esmf_gridgetcoord(gridin, coorddim=2, &
1303  staggerloc=esmf_staggerloc_corner, &
1304  farrayptr=dataptr_ycor, rc=rc)
1305  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1306  line=__line__, &
1307  file=__file__)) &
1308  return
1309 
1310  call esmf_gridgetitem(gridin, itemflag=esmf_griditem_mask, &
1311  staggerloc=esmf_staggerloc_center, &
1312  farrayptr=dataptr_mask, rc=rc)
1313  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1314  line=__line__, &
1315  file=__file__)) &
1316  return
1317 
1318  if(grid_attach_area) then
1319  call esmf_gridgetitem(gridin, itemflag=esmf_griditem_area, &
1320  staggerloc=esmf_staggerloc_center, &
1321  farrayptr=dataptr_area, rc=rc)
1322  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1323  line=__line__, &
1324  file=__file__)) &
1325  return
1326  endif
1327 
1328  ! load up area, mask, center and corner values
1329  ! area, mask, and centers should be same size in mom and esmf grid
1330  ! corner points may not be, need to offset corner points by 1 in i and j
1331  ! retrieve these values directly from ocean_grid, which contains halo
1332  ! values for j=0 and wrap-around in i. on tripole seam, decomposition
1333  ! domains are 1 larger in j; to load corner values need to loop one extra row
1334 
1335  call mpp_get_compute_domain(ocean_public%domain, isc, iec, jsc, jec)
1336 
1337  lbnd1 = lbound(dataptr_mask,1)
1338  ubnd1 = ubound(dataptr_mask,1)
1339  lbnd2 = lbound(dataptr_mask,2)
1340  ubnd2 = ubound(dataptr_mask,2)
1341 
1342  lbnd3 = lbound(dataptr_xcor,1)
1343  ubnd3 = ubound(dataptr_xcor,1)
1344  lbnd4 = lbound(dataptr_xcor,2)
1345  ubnd4 = ubound(dataptr_xcor,2)
1346 
1347  write(tmpstr,*) subname//' iscjsc = ',isc,iec,jsc,jec
1348  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1349 
1350  write(tmpstr,*) subname//' lbub12 = ',lbnd1,ubnd1,lbnd2,ubnd2
1351  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1352 
1353  write(tmpstr,*) subname//' lbub34 = ',lbnd3,ubnd3,lbnd4,ubnd4
1354  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1355 
1356  if (iec-isc /= ubnd1-lbnd1 .or. jec-jsc /= ubnd2-lbnd2) then
1357  call esmf_logseterror(esmf_rc_arg_bad, &
1358  msg=subname//": fld and grid do not have the same size.", &
1359  line=__line__, file=__file__, rctoreturn=rc)
1360  return
1361  endif
1362 
1363  do j = jsc, jec
1364  j1 = j + lbnd2 - jsc
1365  jg = j + ocean_grid%jsc - jsc
1366  do i = isc, iec
1367  i1 = i + lbnd1 - isc
1368  ig = i + ocean_grid%isc - isc
1369  dataptr_mask(i1,j1) = ocean_grid%mask2dT(ig,jg)
1370  dataptr_xcen(i1,j1) = ocean_grid%geolonT(ig,jg)
1371  dataptr_ycen(i1,j1) = ocean_grid%geolatT(ig,jg)
1372  if(grid_attach_area) then
1373  dataptr_area(i1,j1) = ocean_grid%US%L_to_m**2 * ocean_grid%areaT(ig,jg)
1374  endif
1375  enddo
1376  enddo
1377 
1378  jlast = jec
1379  if(jec == nyg)jlast = jec+1
1380 
1381  do j = jsc, jlast
1382  j1 = j + lbnd4 - jsc
1383  jg = j + ocean_grid%jsc - jsc - 1
1384  do i = isc, iec
1385  i1 = i + lbnd3 - isc
1386  ig = i + ocean_grid%isc - isc - 1
1387  dataptr_xcor(i1,j1) = ocean_grid%geolonBu(ig,jg)
1388  dataptr_ycor(i1,j1) = ocean_grid%geolatBu(ig,jg)
1389  enddo
1390  enddo
1391 
1392  write(tmpstr,*) subname//' mask = ',minval(dataptr_mask),maxval(dataptr_mask)
1393  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1394 
1395  if(grid_attach_area) then
1396  write(tmpstr,*) subname//' area = ',minval(dataptr_area),maxval(dataptr_area)
1397  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1398  endif
1399 
1400  write(tmpstr,*) subname//' xcen = ',minval(dataptr_xcen),maxval(dataptr_xcen)
1401  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1402 
1403  write(tmpstr,*) subname//' ycen = ',minval(dataptr_ycen),maxval(dataptr_ycen)
1404  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1405 
1406  write(tmpstr,*) subname//' xcor = ',minval(dataptr_xcor),maxval(dataptr_xcor)
1407  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1408 
1409  write(tmpstr,*) subname//' ycor = ',minval(dataptr_ycor),maxval(dataptr_ycor)
1410  call esmf_logwrite(trim(tmpstr), esmf_logmsg_info, rc=rc)
1411 
1412  gridout = gridin ! for now out same as in
1413 
1414  call mom_realizefields(importstate, fldstoocn_num, fldstoocn, "Ocn import", grid=gridin, rc=rc)
1415  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1416  line=__line__, &
1417  file=__file__)) &
1418  return
1419 
1420  call mom_realizefields(exportstate, fldsfrocn_num, fldsfrocn, "Ocn export", grid=gridout, rc=rc)
1421  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1422  line=__line__, &
1423  file=__file__)) &
1424  return
1425 
1426  endif
1427 
1428  !---------------------------------
1429  ! set scalar data in export state
1430  !---------------------------------
1431 
1432  if (len_trim(scalar_field_name) > 0) then
1433  call state_setscalar(dble(nxg),scalar_field_idx_grid_nx, exportstate, localpet, &
1435  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1436  line=__line__, &
1437  file=__file__)) &
1438  return
1439 
1440  call state_setscalar(dble(nyg),scalar_field_idx_grid_ny, exportstate, localpet, &
1442  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1443  line=__line__, &
1444  file=__file__)) &
1445  return
1446 
1447  endif
1448 
1449  !---------------------------------
1450  ! Set module variable geomtype in MOM_cap_methods
1451  !---------------------------------
1453 
1454  !---------------------------------
1455  ! write out diagnostics
1456  !---------------------------------
1457 
1458  !call NUOPC_Write(exportState, fileNamePrefix='post_realize_field_ocn_export_', &
1459  ! timeslice=1, relaxedFlag=.true., rc=rc)
1460  !if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
1461  ! line=__LINE__, &
1462  ! file=__FILE__)) &
1463  ! return ! bail out
1464 
1465 end subroutine initializerealize
1466 
1467 !> TODO
1468 !!
1469 !! @param gcomp an ESMF_GridComp object
1470 !! @param rc return code
1471 subroutine datainitialize(gcomp, rc)
1472  type(esmf_gridcomp) :: gcomp !< ESMF_GridComp object
1473  integer, intent(out) :: rc !< return code
1474 
1475  ! local variables
1476  type(esmf_clock) :: clock
1477  type(esmf_state) :: importState, exportState
1478  type (ocean_public_type), pointer :: ocean_public => null()
1479  type (ocean_state_type), pointer :: ocean_state => null()
1480  type(ice_ocean_boundary_type), pointer :: Ice_ocean_boundary => null()
1481  type(ocean_internalstate_wrapper) :: ocean_internalstate
1482  type(ocean_grid_type), pointer :: ocean_grid
1483  character(240) :: msgString
1484  integer :: fieldCount, n
1485  type(esmf_field) :: field
1486  character(len=64),allocatable :: fieldNameList(:)
1487  character(len=*),parameter :: subname='(MOM_cap:DataInitialize)'
1488  !--------------------------------
1489 
1490  ! query the Component for its clock, importState and exportState
1491  call esmf_gridcompget(gcomp, clock=clock, importstate=importstate, exportstate=exportstate, rc=rc)
1492  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1493  line=__line__, &
1494  file=__file__)) &
1495  return ! bail out
1496 
1497  call esmf_gridcompgetinternalstate(gcomp, ocean_internalstate, rc)
1498  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1499  line=__line__, &
1500  file=__file__)) &
1501  return ! bail out
1502 
1503  ice_ocean_boundary => ocean_internalstate%ptr%ice_ocean_boundary_type_ptr
1504  ocean_public => ocean_internalstate%ptr%ocean_public_type_ptr
1505  ocean_state => ocean_internalstate%ptr%ocean_state_type_ptr
1506  call get_ocean_grid(ocean_state, ocean_grid)
1507 
1508  call mom_export(ocean_public, ocean_grid, ocean_state, exportstate, clock, rc=rc)
1509  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1510  line=__line__, &
1511  file=__file__)) &
1512  return ! bail out
1513 
1514  call esmf_stateget(exportstate, itemcount=fieldcount, rc=rc)
1515  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1516  line=__line__, &
1517  file=__file__)) &
1518  return ! bail out
1519 
1520  allocate(fieldnamelist(fieldcount))
1521  call esmf_stateget(exportstate, itemnamelist=fieldnamelist, rc=rc)
1522  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1523  line=__line__, &
1524  file=__file__)) &
1525  return ! bail out
1526 
1527  do n=1, fieldcount
1528  call esmf_stateget(exportstate, itemname=fieldnamelist(n), field=field, rc=rc)
1529  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1530  line=__line__, &
1531  file=__file__)) &
1532  return ! bail out
1533 
1534  call nuopc_setattribute(field, name="Updated", value="true", rc=rc)
1535  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1536  line=__line__, &
1537  file=__file__)) &
1538  return ! bail out
1539  enddo
1540  deallocate(fieldnamelist)
1541 
1542  ! check whether all Fields in the exportState are "Updated"
1543  if (nuopc_isupdated(exportstate)) then
1544  call nuopc_compattributeset(gcomp, name="InitializeDataComplete", value="true", rc=rc)
1545 
1546  call esmf_logwrite("MOM6 - Initialize-Data-Dependency SATISFIED!!!", esmf_logmsg_info, rc=rc)
1547  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1548  line=__line__, &
1549  file=__file__)) &
1550  return ! bail out
1551  endif
1552 
1553  if(write_diagnostics) then
1554  call nuopc_write(exportstate, filenameprefix='field_init_ocn_export_', &
1555  overwrite=overwrite_timeslice,timeslice=import_slice, relaxedflag=.true., rc=rc)
1556  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1557  line=__line__, &
1558  file=__file__)) &
1559  return ! bail out
1560  endif
1561 
1562 end subroutine datainitialize
1563 
1564 !> Called by NUOPC to advance the model a single timestep.
1565 !!
1566 !! @param gcomp an ESMF_GridComp object
1567 !! @param rc return code
1568 subroutine modeladvance(gcomp, rc)
1569  type(esmf_gridcomp) :: gcomp !< ESMF_GridComp object
1570  integer, intent(out) :: rc !< return code
1571 
1572  ! local variables
1573  integer :: userRc
1574  logical :: existflag, isPresent, isSet
1575  logical :: do_advance = .true.
1576  type(esmf_clock) :: clock!< ESMF Clock class definition
1577  type(esmf_alarm) :: alarm
1578  type(esmf_state) :: importState, exportState
1579  type(esmf_time) :: currTime
1580  type(esmf_timeinterval) :: timeStep
1581  type(esmf_time) :: startTime
1582  type(esmf_timeinterval) :: time_elapsed
1583  integer(ESMF_KIND_I8) :: n_interval, time_elapsed_sec
1584  character(len=64) :: timestamp
1585  type (ocean_public_type), pointer :: ocean_public => null()
1586  type (ocean_state_type), pointer :: ocean_state => null()
1587  type(ice_ocean_boundary_type), pointer :: Ice_ocean_boundary => null()
1588  type(ocean_internalstate_wrapper) :: ocean_internalstate
1589  type(ocean_grid_type) , pointer :: ocean_grid
1590  type(time_type) :: Time
1591  type(time_type) :: Time_step_coupled
1592  type(time_type) :: Time_restart_current
1593  integer :: dth, dtm, dts
1594  integer :: nc
1595  type(esmf_time) :: MyTime
1596  integer :: seconds, day, year, month, hour, minute
1597  character(ESMF_MAXSTR) :: restartname, cvalue
1598  character(240) :: msgString
1599  character(len=*),parameter :: subname='(MOM_cap:ModelAdvance)'
1600 
1601  rc = esmf_success
1602  if(profile_memory) call esmf_vmlogmeminfo("Entering MOM Model_ADVANCE: ")
1603 
1605 
1606  ! query the Component for its clock, importState and exportState
1607  call esmf_gridcompget(gcomp, clock=clock, importstate=importstate, &
1608  exportstate=exportstate, rc=rc)
1609  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1610  line=__line__, &
1611  file=__file__)) &
1612  return ! bail out
1613 
1614  ! HERE THE MODEL ADVANCES: currTime -> currTime + timeStep
1615 
1616  call esmf_clockprint(clock, options="currTime", &
1617  prestring="------>Advancing OCN from: ", unit=msgstring, rc=rc)
1618  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1619  line=__line__, &
1620  file=__file__)) &
1621  return ! bail out
1622  call esmf_logwrite(subname//trim(msgstring), esmf_logmsg_info, rc=rc)
1623  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1624  line=__line__, &
1625  file=__file__)) &
1626  return ! bail out
1627 
1628  call esmf_clockget(clock, starttime=starttime, currtime=currtime, &
1629  timestep=timestep, rc=rc)
1630  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1631  line=__line__, &
1632  file=__file__)) &
1633  return ! bail out
1634 
1635  call esmf_timeprint(currtime + timestep, &
1636  prestring="--------------------------------> to: ", unit=msgstring, rc=rc)
1637  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1638  line=__line__, &
1639  file=__file__)) &
1640  return ! bail out
1641  call esmf_logwrite(trim(msgstring), esmf_logmsg_info, rc=rc)
1642  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1643  line=__line__, &
1644  file=__file__)) &
1645  return ! bail out
1646 
1647  time_step_coupled = esmf2fms_time(timestep)
1648  time = esmf2fms_time(currtime)
1649 
1650  !---------------
1651  ! Apply ocean lag for startup runs:
1652  !---------------
1653 
1654  if (cesm_coupled) then
1655  if (trim(runtype) == "initial") then
1656 
1657  ! Do not call MOM6 timestepping routine if the first cpl tstep of a startup run
1658  if (currtime == starttime) then
1659  call esmf_logwrite("MOM6 - Skipping the first coupling timestep", esmf_logmsg_info, rc=rc)
1660  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1661  line=__line__, &
1662  file=__file__)) &
1663  return ! bail out
1664  do_advance = .false.
1665  else
1666  do_advance = .true.
1667  endif
1668 
1669  if (do_advance) then
1670  ! If the second cpl tstep of a startup run, step back a cpl tstep and advance for two cpl tsteps
1671  if (currtime == starttime + timestep) then
1672  call esmf_logwrite("MOM6 - Stepping back one coupling timestep", esmf_logmsg_info, rc=rc)
1673  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1674  line=__line__, &
1675  file=__file__)) &
1676  return ! bail out
1677  time = esmf2fms_time(currtime-timestep) ! i.e., startTime
1678 
1679  call esmf_logwrite("MOM6 - doubling the coupling timestep", esmf_logmsg_info, rc=rc)
1680  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1681  line=__line__, &
1682  file=__file__)) &
1683  return ! bail out
1684  time_step_coupled = 2 * esmf2fms_time(timestep)
1685  endif
1686  end if
1687 
1688  endif
1689  endif
1690 
1691  if (do_advance) then
1692 
1693  call esmf_gridcompgetinternalstate(gcomp, ocean_internalstate, rc)
1694  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1695  line=__line__, &
1696  file=__file__)) &
1697  return ! bail out
1698 
1699  ice_ocean_boundary => ocean_internalstate%ptr%ice_ocean_boundary_type_ptr
1700  ocean_public => ocean_internalstate%ptr%ocean_public_type_ptr
1701  ocean_state => ocean_internalstate%ptr%ocean_state_type_ptr
1702 
1703  !---------------
1704  ! Write diagnostics for import
1705  !---------------
1706 
1707  if (write_diagnostics) then
1708  call nuopc_write(importstate, filenameprefix='field_ocn_import_', &
1709  overwrite=overwrite_timeslice,timeslice=import_slice, relaxedflag=.true., rc=rc)
1710  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1711  line=__line__, &
1712  file=__file__)) &
1713  return ! bail out
1715  endif
1716 
1717  !---------------
1718  ! Get ocean grid
1719  !---------------
1720 
1721  call get_ocean_grid(ocean_state, ocean_grid)
1722 
1723  !---------------
1724  ! Import data
1725  !---------------
1726 
1727  call mom_import(ocean_public, ocean_grid, importstate, ice_ocean_boundary, rc=rc)
1728  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1729  line=__line__, &
1730  file=__file__)) &
1731  return ! bail out
1732 
1733  !---------------
1734  ! Update MOM6
1735  !---------------
1736 
1737  if(profile_memory) call esmf_vmlogmeminfo("Entering MOM update_ocean_model: ")
1738  call update_ocean_model(ice_ocean_boundary, ocean_state, ocean_public, time, time_step_coupled)
1739  if(profile_memory) call esmf_vmlogmeminfo("Leaving MOM update_ocean_model: ")
1740 
1741  !---------------
1742  ! Export Data
1743  !---------------
1744 
1745  call mom_export(ocean_public, ocean_grid, ocean_state, exportstate, clock, rc=rc)
1746  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1747  line=__line__, &
1748  file=__file__)) &
1749  return ! bail out
1750 
1751  endif
1752 
1753  !---------------
1754  ! If restart alarm is ringing - write restart file
1755  !---------------
1756 
1757  call esmf_clockgetalarm(clock, alarmname='alarm_restart', alarm=alarm, rc=rc)
1758  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1759  line=__line__, &
1760  file=__file__)) &
1761  return ! bail out
1762 
1763  if (esmf_alarmisringing(alarm, rc=rc)) then
1764  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1765  line=__line__, &
1766  file=__file__)) &
1767  return ! bail out
1768 
1769  call esmf_alarmringeroff(alarm, rc=rc )
1770  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1771  line=__line__, &
1772  file=__file__)) &
1773  return ! bail out
1774 
1775  ! call into system specific method to get desired restart filename
1776  restartname = ""
1777  call esmf_methodexecute(gcomp, label="GetRestartFileToWrite", &
1778  existflag=existflag, userrc=userrc, rc=rc)
1779  if (esmf_logfounderror(rctocheck=rc, msg="Error executing user method to get restart filename", &
1780  line=__line__, &
1781  file=__file__)) &
1782  return ! bail out
1783 
1784  if (esmf_logfounderror(rctocheck=userrc, msg="Error in method to get restart filename", &
1785  line=__line__, &
1786  file=__file__)) &
1787  return ! bail out
1788  if (existflag) then
1789  call esmf_logwrite("MOM_cap: called user GetRestartFileToWrite method", esmf_logmsg_info, rc=rc)
1790  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1791  line=__line__, &
1792  file=__file__)) &
1793  return ! bail out
1794  call nuopc_compattributeget(gcomp, name='RestartFileToWrite', &
1795  ispresent=ispresent, isset=isset, value=cvalue, rc=rc)
1796  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1797  line=__line__, &
1798  file=__file__)) &
1799  return ! bail out
1800  if (ispresent .and. isset) then
1801  restartname = trim(cvalue)
1802  call esmf_logwrite("MOM_cap: User RestartFileToWrite: "//trim(restartname), esmf_logmsg_info, rc=rc)
1803  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1804  line=__line__, &
1805  file=__file__)) &
1806  return ! bail out
1807  endif
1808  endif
1809 
1810  if (len_trim(restartname) == 0) then
1811  ! none provided, so use a default restart filename
1812  call esmf_clockgetnexttime(clock, mytime, rc=rc)
1813  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1814  line=__line__, &
1815  file=__file__)) &
1816  return ! bail out
1817  call esmf_timeget (mytime, yy=year, mm=month, dd=day, &
1818  h=hour, m=minute, s=seconds, rc=rc )
1819  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1820  line=__line__, &
1821  file=__file__)) &
1822  return ! bail out
1823  write(restartname,'(A,".mom6.r.",I4.4,"-",I2.2,"-",I2.2,"-",I2.2,"-",I2.2,"-",I2.2)') &
1824  "ocn", year, month, day, hour, minute, seconds
1825  call esmf_logwrite("MOM_cap: Using default restart filename: "//trim(restartname), esmf_logmsg_info, rc=rc)
1826  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1827  line=__line__, &
1828  file=__file__)) &
1829  return ! bail out
1830  endif
1831 
1832  ! TODO: address if this requirement is being met for the DA group
1833  ! Optionally write restart files when currTime-startTime is integer multiples of restart_interval
1834  ! if (restart_interval > 0 ) then
1835  ! time_elapsed = currTime - startTime
1836  ! call ESMF_TimeIntervalGet(time_elapsed, s_i8=time_elapsed_sec, rc=rc)
1837  ! if (ESMF_LogFoundError(rcToCheck=rc, msg=ESMF_LOGERR_PASSTHRU, &
1838  ! line=__LINE__, &
1839  ! file=__FILE__)) &
1840  ! return ! bail out
1841  ! n_interval = time_elapsed_sec / restart_interval
1842  ! if ((n_interval .gt. 0) .and. (n_interval*restart_interval == time_elapsed_sec)) then
1843  ! time_restart_current = esmf2fms_time(currTime)
1844  ! timestamp = date_to_string(time_restart_current)
1845  ! call ESMF_LogWrite("MOM: Writing restart at "//trim(timestamp), ESMF_LOGMSG_INFO, rc=rc)
1846  ! write(*,*) 'calling ocean_model_restart'
1847  ! call ocean_model_restart(ocean_state, timestamp)
1848  ! endif
1849  ! endif
1850 
1851  ! write restart file(s)
1852  call ocean_model_restart(ocean_state, restartname=restartname)
1853 
1854  if (is_root_pe()) then
1855  write(logunit,*) subname//' writing restart file ',trim(restartname)
1856  endif
1857  endif
1858 
1859  !---------------
1860  ! Write diagnostics
1861  !---------------
1862 
1863  if (write_diagnostics) then
1864  call nuopc_write(exportstate, filenameprefix='field_ocn_export_', &
1865  overwrite=overwrite_timeslice,timeslice=export_slice, relaxedflag=.true., rc=rc)
1866  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1867  line=__line__, &
1868  file=__file__)) &
1869  return ! bail out
1871  endif
1872 
1873  if(profile_memory) call esmf_vmlogmeminfo("Leaving MOM Model_ADVANCE: ")
1874 
1875 end subroutine modeladvance
1876 
1877 
1878 subroutine modelsetrunclock(gcomp, rc)
1879  type(esmf_gridcomp) :: gcomp
1880  integer, intent(out) :: rc
1881 
1882  ! local variables
1883  type(esmf_clock) :: mclock, dclock
1884  type(esmf_time) :: mcurrtime, dcurrtime
1885  type(esmf_time) :: mstoptime
1886  type(esmf_timeinterval) :: mtimestep, dtimestep
1887  character(len=128) :: mtimestring, dtimestring
1888  character(len=256) :: cvalue
1889  character(len=256) :: restart_option ! Restart option units
1890  integer :: restart_n ! Number until restart interval
1891  integer :: restart_ymd ! Restart date (YYYYMMDD)
1892  type(esmf_alarm) :: restart_alarm
1893  logical :: isPresent, isSet
1894  logical :: first_time = .true.
1895  character(len=*),parameter :: subname='MOM_cap:(ModelSetRunClock) '
1896  !--------------------------------
1897 
1898  rc = esmf_success
1899 
1900  ! query the Component for its clock, importState and exportState
1901  call nuopc_modelget(gcomp, driverclock=dclock, modelclock=mclock, rc=rc)
1902  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1903  line=__line__, &
1904  file=__file__)) &
1905  return ! bail out
1906 
1907  call esmf_clockget(dclock, currtime=dcurrtime, timestep=dtimestep, rc=rc)
1908  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1909  line=__line__, &
1910  file=__file__)) &
1911  return ! bail out
1912 
1913  call esmf_clockget(mclock, currtime=mcurrtime, timestep=mtimestep, rc=rc)
1914  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1915  line=__line__, &
1916  file=__file__)) &
1917  return ! bail out
1918 
1919  !--------------------------------
1920  ! check that the current time in the model and driver are the same
1921  !--------------------------------
1922 
1923  if (mcurrtime /= dcurrtime) then
1924  call esmf_timeget(dcurrtime, timestring=dtimestring, rc=rc)
1925  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1926  line=__line__, &
1927  file=__file__)) &
1928  return ! bail out
1929 
1930  call esmf_timeget(mcurrtime, timestring=mtimestring, rc=rc)
1931  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1932  line=__line__, &
1933  file=__file__)) &
1934  return ! bail out
1935 
1936  call esmf_logseterror(esmf_rc_val_wrong, &
1937  msg=subname//": ERROR in time consistency: "//trim(dtimestring)//" != "//trim(mtimestring), &
1938  line=__line__, file=__file__, rctoreturn=rc)
1939  return
1940  endif
1941 
1942  !--------------------------------
1943  ! force model clock currtime and timestep to match driver and set stoptime
1944  !--------------------------------
1945 
1946  mstoptime = mcurrtime + dtimestep
1947 
1948  call esmf_clockset(mclock, currtime=dcurrtime, timestep=dtimestep, stoptime=mstoptime, rc=rc)
1949  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1950  line=__line__, &
1951  file=__file__)) &
1952  return ! bail out
1953 
1954  if (first_time) then
1955  !--------------------------------
1956  ! set restart alarm
1957  !--------------------------------
1958 
1959  ! defaults
1960  restart_n = 0
1961  restart_ymd = 0
1962 
1963  call nuopc_compattributeget(gcomp, name="restart_option", ispresent=ispresent, &
1964  isset=isset, value=restart_option, rc=rc)
1965  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1966  line=__line__, &
1967  file=__file__)) &
1968  return ! bail out
1969  if (ispresent .and. isset) then
1970  call nuopc_compattributeget(gcomp, name="restart_n", value=cvalue, &
1971  ispresent=ispresent, isset=isset, rc=rc)
1972  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1973  line=__line__, &
1974  file=__file__)) &
1975  return ! bail out
1976  if (ispresent .and. isset) then
1977  read(cvalue,*) restart_n
1978  endif
1979  call nuopc_compattributeget(gcomp, name="restart_ymd", value=cvalue, &
1980  ispresent=ispresent, isset=isset, rc=rc)
1981  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
1982  line=__line__, &
1983  file=__file__)) &
1984  return ! bail out
1985  if (ispresent .and. isset) then
1986  read(cvalue,*) restart_ymd
1987  endif
1988  else
1989  restart_option = "none"
1990  endif
1991 
1992  call alarminit(mclock, &
1993  alarm = restart_alarm, &
1994  option = trim(restart_option), &
1995  opt_n = restart_n, &
1996  opt_ymd = restart_ymd, &
1997  reftime = mcurrtime, &
1998  alarmname = 'alarm_restart', rc=rc)
1999  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2000  line=__line__, &
2001  file=__file__)) &
2002  return ! bail out
2003 
2004  call esmf_alarmset(restart_alarm, clock=mclock, rc=rc)
2005  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2006  line=__line__, &
2007  file=__file__)) &
2008  return ! bail out
2009  first_time = .false.
2010 
2011  call esmf_logwrite(subname//" Set restart option = "//restart_option, &
2012  esmf_logmsg_info, rc=rc)
2013  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2014  line=__line__, &
2015  file=__file__)) &
2016  return ! bail out
2017 
2018  endif
2019 
2020  !--------------------------------
2021  ! Advance model clock to trigger alarms then reset model clock back to currtime
2022  !--------------------------------
2023 
2024  call esmf_clockadvance(mclock,rc=rc)
2025  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2026  line=__line__, &
2027  file=__file__)) &
2028  return ! bail out
2029 
2030  call esmf_clockset(mclock, currtime=dcurrtime, timestep=dtimestep, stoptime=mstoptime, rc=rc)
2031  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2032  line=__line__, &
2033  file=__file__)) &
2034  return ! bail out
2035 
2036 end subroutine modelsetrunclock
2037 
2038 
2039 !===============================================================================
2040 
2041 !> Called by NUOPC at the end of the run to clean up.
2042 !!
2043 !! @param gcomp an ESMF_GridComp object
2044 !! @param rc return code
2045 subroutine ocean_model_finalize(gcomp, rc)
2047  type(esmf_gridcomp) :: gcomp !< ESMF_GridComp object
2048  integer, intent(out) :: rc !< return code
2049 
2050  ! local variables
2051  type (ocean_public_type), pointer :: ocean_public
2052  type (ocean_state_type), pointer :: ocean_state
2053  type(ocean_internalstate_wrapper) :: ocean_internalstate
2054  type(time_type) :: Time
2055  type(esmf_clock) :: clock
2056  type(esmf_time) :: currTime
2057  character(len=64) :: timestamp
2058  character(len=*),parameter :: subname='(MOM_cap:ocean_model_finalize)'
2059 
2060  write(*,*) 'MOM: --- finalize called ---'
2061  rc = esmf_success
2062 
2063  call esmf_gridcompgetinternalstate(gcomp, ocean_internalstate, rc)
2064  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2065  line=__line__, &
2066  file=__file__)) &
2067  return ! bail out
2068 
2069  ocean_public => ocean_internalstate%ptr%ocean_public_type_ptr
2070  ocean_state => ocean_internalstate%ptr%ocean_state_type_ptr
2071 
2072  call nuopc_modelget(gcomp, modelclock=clock, rc=rc)
2073  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2074  line=__line__, &
2075  file=__file__)) &
2076  return ! bail out
2077 
2078  call esmf_clockget(clock, currtime=currtime, rc=rc)
2079  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2080  line=__line__, &
2081  file=__file__)) &
2082  return ! bail out
2083  time = esmf2fms_time(currtime)
2084 
2085  if (cesm_coupled) then
2086  call ocean_model_end(ocean_public, ocean_state, time, write_restart=.false.)
2087  else
2088  call ocean_model_end(ocean_public, ocean_state, time, write_restart=.true.)
2089  endif
2090  call field_manager_end()
2091 
2092  call fms_io_exit()
2093  call fms_end()
2094 
2095  write(*,*) 'MOM: --- completed ---'
2096 
2097 end subroutine ocean_model_finalize
2098 
2099 
2100 !> Set scalar data from state for a particula name
2101 subroutine state_setscalar(value, scalar_id, State, mytask, scalar_name, scalar_count, rc)
2102  real(ESMF_KIND_R8),intent(in) :: value
2103  integer, intent(in) :: scalar_id
2104  type(esmf_state), intent(inout) :: State
2105  integer, intent(in) :: mytask
2106  character(len=*), intent(in) :: scalar_name
2107  integer, intent(in) :: scalar_count
2108  integer, intent(inout) :: rc !< return code
2109 
2110  ! local variables
2111  type(esmf_field) :: field
2112  real(ESMF_KIND_R8), pointer :: farrayptr(:,:)
2113  character(len=*), parameter :: subname='(MOM_cap:State_SetScalar)'
2114  !--------------------------------------------------------
2115 
2116  rc = esmf_success
2117 
2118  call esmf_stateget(state, itemname=trim(scalar_name), field=field, rc=rc)
2119  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, line=__line__, file=u_file_u)) return
2120 
2121  if (mytask == 0) then
2122  call esmf_fieldget(field, farrayptr=farrayptr, rc=rc)
2123  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, line=__line__, file=u_file_u)) return
2124 
2125  if (scalar_id < 0 .or. scalar_id > scalar_count) then
2126  call esmf_logseterror(esmf_rc_arg_bad, &
2127  msg=subname//": ERROR in scalar_id", &
2128  line=__line__, file=__file__, rctoreturn=rc)
2129  return
2130  endif
2131 
2132  farrayptr(scalar_id,1) = value
2133  endif
2134 
2135 end subroutine state_setscalar
2136 
2137 !> Realize the import and export fields using either a grid or a mesh.
2138 subroutine mom_realizefields(state, nfields, field_defs, tag, grid, mesh, rc)
2139  type(esmf_state) , intent(inout) :: state !< ESMF_State object for
2140  !! import/export fields.
2141  integer , intent(in) :: nfields !< Number of fields.
2142  type(fld_list_type) , intent(inout) :: field_defs(:) !< Structure with field's
2143  !! information.
2144  character(len=*) , intent(in) :: tag !< Import or export.
2145  type(esmf_grid) , intent(in), optional :: grid!< ESMF grid.
2146  type(esmf_mesh) , intent(in), optional :: mesh!< ESMF mesh.
2147  integer , intent(inout) :: rc !< Return code.
2148 
2149  ! local variables
2150  integer :: i
2151  type(esmf_field) :: field
2152  real(ESMF_KIND_R8), pointer :: fldptr1d(:) ! for mesh
2153  real(ESMF_KIND_R8), pointer :: fldptr2d(:,:) ! for grid
2154  character(len=*),parameter :: subname='(MOM_cap:MOM_RealizeFields)'
2155  !--------------------------------------------------------
2156 
2157  rc = esmf_success
2158 
2159  do i = 1, nfields
2160 
2161  if (nuopc_isconnected(state, fieldname=field_defs(i)%shortname)) then
2162 
2163  if (field_defs(i)%shortname == scalar_field_name) then
2164 
2165  call esmf_logwrite(subname // tag // " Field "// trim(field_defs(i)%stdname) // " is connected on root pe.", &
2166  esmf_logmsg_info, &
2167  line=__line__, &
2168  file=__file__, &
2169  rc=rc)
2170 
2171  call setscalarfield(field, rc)
2172  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2173  line=__line__, &
2174  file=__file__)) &
2175  return ! bail out
2176 
2177  else
2178 
2179  call esmf_logwrite(subname // tag // " Field "// trim(field_defs(i)%stdname) // " is connected.", &
2180  esmf_logmsg_info, &
2181  line=__line__, &
2182  file=__file__, &
2183  rc=rc)
2184 
2185  if (present(grid)) then
2186 
2187  field = esmf_fieldcreate(grid, esmf_typekind_r8, indexflag=esmf_index_delocal, &
2188  name=field_defs(i)%shortname, rc=rc)
2189  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2190  line=__line__, &
2191  file=__file__)) &
2192  return ! bail out
2193 
2194  ! initialize fldptr to zero
2195  call esmf_fieldget(field, farrayptr=fldptr2d, rc=rc)
2196  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2197  line=__line__, &
2198  file=__file__)) &
2199  return ! bail out
2200  fldptr2d(:,:) = 0.0
2201 
2202  else if (present(mesh)) then
2203 
2204  field = esmf_fieldcreate(mesh=mesh, typekind=esmf_typekind_r8, meshloc=esmf_meshloc_element, &
2205  name=field_defs(i)%shortname, rc=rc)
2206  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2207  line=__line__, &
2208  file=__file__)) &
2209  return ! bail out
2210 
2211  ! initialize fldptr to zero
2212  call esmf_fieldget(field, farrayptr=fldptr1d, rc=rc)
2213  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2214  line=__line__, &
2215  file=__file__)) &
2216  return ! bail out
2217  fldptr1d(:) = 0.0
2218 
2219  endif
2220 
2221  endif
2222 
2223  ! Realize connected field
2224  call nuopc_realize(state, field=field, rc=rc)
2225  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2226  line=__line__, &
2227  file=__file__)) &
2228  return ! bail out
2229 
2230  else ! field is not connected
2231 
2232  call esmf_logwrite(subname // tag // " Field "// trim(field_defs(i)%stdname) // " is not connected.", &
2233  esmf_logmsg_info, &
2234  line=__line__, &
2235  file=__file__, &
2236  rc=rc)
2237  ! remove a not connected Field from State
2238  call esmf_stateremove(state, (/field_defs(i)%shortname/), rc=rc)
2239  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2240  line=__line__, &
2241  file=__file__)) &
2242  return ! bail out
2243 
2244  endif
2245 
2246  enddo
2247 
2248 contains !- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2249 
2250  subroutine setscalarfield(field, rc)
2252  ! create a field with scalar data on the root pe
2253  type(esmf_field), intent(inout) :: field
2254  integer, intent(inout) :: rc
2255 
2256  ! local variables
2257  type(esmf_distgrid) :: distgrid
2258  type(esmf_grid) :: grid
2259  character(len=*), parameter :: subname='(MOM_cap:SetScalarField)'
2260 
2261  rc = esmf_success
2262 
2263  ! create a DistGrid with a single index space element, which gets mapped onto DE 0.
2264  distgrid = esmf_distgridcreate(minindex=(/1/), maxindex=(/1/), rc=rc)
2265  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2266  line=__line__, &
2267  file=__file__)) &
2268  return ! bail out
2269 
2270  grid = esmf_gridcreate(distgrid, rc=rc)
2271  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2272  line=__line__, &
2273  file=__file__)) &
2274  return ! bail out
2275 
2276  ! num of scalar values
2277  field = esmf_fieldcreate(name=trim(scalar_field_name), grid=grid, typekind=esmf_typekind_r8, &
2278  ungriddedlbound=(/1/), ungriddedubound=(/scalar_field_count/), gridtofieldmap=(/2/), rc=rc)
2279  if (esmf_logfounderror(rctocheck=rc, msg=esmf_logerr_passthru, &
2280  line=__line__, &
2281  file=__file__)) &
2282  return ! bail out
2283 
2284  end subroutine setscalarfield
2285 
2286 end subroutine mom_realizefields
2287 
2288 !===============================================================================
2289 
2290 !> Set up list of field information
2291 subroutine fld_list_add(num, fldlist, stdname, transferOffer, shortname)
2292  integer, intent(inout) :: num
2293  type(fld_list_type), intent(inout) :: fldlist(:)
2294  character(len=*), intent(in) :: stdname
2295  character(len=*), intent(in) :: transferOffer
2296  character(len=*), optional, intent(in) :: shortname
2297 
2298  ! local variables
2299  integer :: rc
2300  character(len=*), parameter :: subname='(MOM_cap:fld_list_add)'
2301 
2302  ! fill in the new entry
2303  num = num + 1
2304  if (num > fldsmax) then
2305  call esmf_logseterror(esmf_rc_val_outofrange, &
2306  msg=trim(subname)//": ERROR number of field exceeded fldsMax: "//trim(stdname), &
2307  line=__line__, file=__file__, rctoreturn=rc)
2308  return
2309  endif
2310 
2311  fldlist(num)%stdname = trim(stdname)
2312  if (present(shortname)) then
2313  fldlist(num)%shortname = trim(shortname)
2314  else
2315  fldlist(num)%shortname = trim(stdname)
2316  endif
2317  fldlist(num)%transferOffer = trim(transferoffer)
2318 
2319 end subroutine fld_list_add
2320 
2321 
2322 #ifndef CESMCOUPLED
2323 subroutine shr_file_setlogunit(nunit)
2324  integer, intent(in) :: nunit
2325  ! do nothing for this stub - its just here to replace
2326  ! having cppdefs in the main program
2327 end subroutine shr_file_setlogunit
2328 
2329 subroutine shr_file_getlogunit(nunit)
2330  integer, intent(in) :: nunit
2331  ! do nothing for this stub - its just here to replace
2332  ! having cppdefs in the main program
2333 end subroutine shr_file_getlogunit
2334 #endif
2335 
2336 !>
2337 !! @page nuopc_cap NUOPC Cap
2338 !! @author Fei Liu (fei.liu@gmail.com)
2339 !! @date 5/10/13 Original documentation
2340 !! @author Rocky Dunlap (rocky.dunlap@noaa.gov)
2341 !! @date 1/12/17 Moved to doxygen
2342 !! @date 2/28/19 Rewrote for unified cap
2343 !! @tableofcontents
2344 !!
2345 !! @section Overview Overview
2346 !!
2347 !! **This MOM cap has been tested with MOM6.**
2348 !!
2349 !! This document describes the MOM NUOPC "cap", which is a light weight software layer that is
2350 !! required when the [MOM ocean model](https://github.com/NOAA-GFDL/MOM6/tree/dev/master)
2351 !! is used in [National Unified Operation Prediction Capability]
2352 !! (http://www.earthsystemcog.org/projects/nuopc) (NUOPC) coupled systems. Also see the
2353 !! [MOM wiki](https://github.com/NOAA-GFDL/MOM6-Examples/wiki) for more documentation.
2354 !!
2355 !! NUOPC is a software layer built on top of the [Earth System Modeling
2356 !! Framework] (https://www.earthsystemcog.org/projects/esmf) (ESMF).
2357 !! ESMF is a high-performance modeling framework that provides
2358 !! data structures, interfaces, and operations suited for building coupled models
2359 !! from a set of components. NUOPC refines the capabilities of ESMF by providing
2360 !! a more precise definition of what it means for a model to be a component and
2361 !! how components should interact and share data in a coupled system. The NUOPC
2362 !! Layer software is designed to work with typical high-performance models in the
2363 !! Earth sciences domain, most of which are written in Fortran and are based on a
2364 !! distributed memory model of parallelism (MPI).
2365 !!
2366 !! A NUOPC "cap" is a Fortran module that serves as the interface to a model
2367 !! when it's used in a NUOPC-based coupled system.
2368 !! The term "cap" is used because it is a light weight software layer that sits on top
2369 !! of model code, making calls into it and exposing model data structures in a
2370 !! standard way.
2371 !!
2372 !! The MOM cap package includes the cap code itself (MOM_cap.F90, MOM_cap_methods.F90
2373 !! and MOM_cap_time.F90), a set of time utilities (time_utils.F90) for converting between ESMF and FMS
2374 !! time type and two modules MOM_ocean_model_nuopc.F90 and MOM_surface_forcing_nuopc.F90. MOM_surface_forcing_nuopc.F90
2375 !! converts the input ESMF data (import data) to a MOM-specific data type (surface_forcing_CS).
2376 !! MOM_ocean_model_nuopc.F90 contains routines for initialization, update and finalization of the ocean model state.
2377 !!
2378 !! @subsection CapSubroutines Cap Subroutines
2379 !!
2380 !! The MOM cap modules contains a set of subroutines that are required
2381 !! by NUOPC. These subroutines are called by the NUOPC infrastructure according
2382 !! to a predefined calling sequence. Some subroutines are called during
2383 !! initialization of the coupled system, some during the run of the coupled
2384 !! system, and some during finalization of the coupled system.
2385 !!
2386 !! The initialization sequence is the most complex and is governed by the NUOPC technical rules.
2387 !! Details about the initialization sequence can be found in the [NUOPC Reference Manual]
2388 !! (http://www.earthsystemmodeling.org/esmf_releases/last_built/NUOPC_refdoc/).
2389 !! The cap requires beta snapshot ESMF v8.0.0bs16 or later.
2390 !!
2391 !! The following table summarizes the NUOPC-required subroutines that appear in the
2392 !! MOM cap. The "Phase" column says whether the subroutine is called during the
2393 !! initialization, run, or finalize part of the coupled system run.
2394 !!
2395 !!<table>
2396 !!<tr><th> Phase <th> MOM Cap Subroutine <th> Description
2397 !!<tr>
2398 !! <td> Init
2399 !! <td> [InitializeP0] (@ref MOM_cap_mod::initializep0)
2400 !! <td> Sets the Initialize Phase Definition (IPD) version to use
2401 !!<tr>
2402 !! <td> Init
2403 !! <td> [InitializeAdvertise] (@ref MOM_cap_mod::initializeadvertise)
2404 !! <td> Advertises standard names of import and export fields
2405 !!<tr>
2406 !! <td> Init
2407 !! <td> [InitializeRealize] (@ref MOM_cap_mod::initializerealize)
2408 !! <td> Creates an ESMF_Grid or ESMF_Mesh as well as ESMF_Fields for import and export fields
2409 !!<tr>
2410 !! <td> Run
2411 !! <td> [ModelAdvance] (@ref MOM_cap_mod::modeladvance)
2412 !! <td> Advances the model by a timestep
2413 !!<tr>
2414 !! <td> Final
2415 !! <td> [Finalize] (@ref MOM_cap_mod::ocean_model_finalize)
2416 !! <td> Cleans up
2417 !!</table>
2418 !!
2419 !!
2420 !! @section UnderlyingModelInterfaces Underlying Model Interfaces
2421 !!
2422 !!
2423 !! @subsection DomainCreation Domain Creation
2424 !!
2425 !! The cap can accomodate a MOM tripolar grid which is represented either as a 2D `ESMF_Grid` or
2426 !! as a 1D `ESMF_Mesh`. Other MOM grids (e.g. a bipolar grid) can be represented as a 1d `ESMF_Mesh` only.
2427 !! Coupling fields are placed on either the `ESMF_Grid` or `ESMF_Mesh`.
2428 !! Note that for either the `ESMF_Grid` or `ESMF_Mesh` representation, the fields are translated into
2429 !! a 2D MOM specific surface boundary type and the distinction between the two is no longer there.
2430 !! Calls related to creating the grid are located in the [InitializeRealize]
2431 !! (@ref MOM_cap_mod::initializerealize) subroutine, which is called by the NUOPC infrastructure
2432 !! during the intialization sequence.
2433 !!
2434 !! The cap determines parameters for setting up the grid by calling subroutines in the
2435 !! `mpp_domains_mod` module. The global domain size is determined by calling `mpp_get_global_domain()`.
2436 !! A check is in place to ensure that there is only a single tile in the domain (the
2437 !! cap is currently limited to one tile; multi-tile mosaics are not supported). The
2438 !! decomposition across processors is determined via calls to `mpp_get_compute_domains()`
2439 !! (to retrieve decomposition block indices) and `mpp_get_pelist()` (to determine how
2440 !! blocks are assigned to processors).
2441 !!
2442 !! The `ESMF_Grid` is created in several steps:
2443 !! - an `ESMF_DELayout` is created based on the pelist from MOM
2444 !! - an `ESMF_DistGrid` is created over the global index space. Connections are set
2445 !! up so that the index space is periodic in the first dimension and has a
2446 !! fold at the top for the bipole. The decompostion blocks are also passed in
2447 !! along with the `ESMF_DELayout` mentioned above.
2448 !! - an `ESMF_Grid` is then created by passing in the above `ESMF_DistGrid`.
2449 !! - masks, areas, center (tlat, tlon), and corner (ulat, ulon) coordinates are then added to the `ESMF_Grid`
2450 !! by retrieving those fields from the MOM datatype `ocean_grid` elements.
2451 !!
2452 !! The `ESMF_Mesh` is also created in several steps:
2453 !! - the target mesh is generated offline.
2454 !! - a temporary mesh is created from an input file specified by the config variable `mesh_ocn`.
2455 !! the mesh has a distribution that is automatically generated by ESMF when reading in the mesh
2456 !! - an `ESMF_DistGrid` is created from the global index space for the computational domain.
2457 !! - the final `ESMF_Mesh` is then created by distributing the temporary mesh using the created `ESMF_DistGrid`.
2458 !!
2459 !!
2460 !! @subsection Initialization Initialization
2461 !!
2462 !! During the [InitializeAdvertise] (@ref MOM_cap_mod::initializeadvertise) phase, calls are
2463 !! made to MOM's native initialization subroutines, including `fms_init()`, `constants_init()`,
2464 !! `field_manager_init()`, `diag_manager_init()`, and `set_calendar_type()`. The MPI communicator
2465 !! is pulled in through the ESMF VM object for the MOM component. The dt and start time are set
2466 !! from parameters from the incoming ESMF clock with calls to `set_time()` and `set_date().`
2467 !!
2468 !!
2469 !! @subsection Run Run
2470 !!
2471 !! The [ModelAdvance] (@ref MOM_cap_mod::modeladvance) subroutine is called by the NUOPC
2472 !! infrastructure when it's time for MOM to advance in time. During this subroutine, there is a
2473 !! call into the MOM update routine:
2474 !!
2475 !! call update_ocean_model(Ice_ocean_boundary, Ocean_state, Ocean_public, Time, Time_step_coupled)
2476 !!
2477 !! Priori to the call to `update_ocean_model()`, the cap performs these steps
2478 !! - the `Time` and `Time_step_coupled` parameters, based on FMS types, are derived from the incoming ESMF clock
2479 !! - diagnostics are optionally written to files `field_ocn_import_*`, one for each import field
2480 !! - mom_import is called and translates to the ESMF input data to a MOM specific data type
2481 !! - momentum flux vectors are rotated to internal grid
2482 !!
2483 !! After the call to `update_ocean_model()`, the cap performs these steps:
2484 !! - mom_export is called
2485 !! - the `ocean_mask` export is set to match that of the internal MOM mask
2486 !! - the `freezing_melting_potential` export is converted from J m-2 to W m-2 by dividing by the coupling interval
2487 !! - vector rotations are applied to the `ocean_current_zonal` and `ocean_current_merid` exports, back to lat-lon grid
2488 !! - diagnostics are optionally written to files `field_ocn_export_*`, one for each export field
2489 !! - optionally, a call is made to `ocean_model_restart()` at the interval `restart_interval`
2490 !!
2491 !! @subsubsection VectorRotations Vector Rotations
2492 !!
2493 !! Vector rotations are applied to incoming momentum fluxes (from regular lat-lon to tripolar grid) and
2494 !! outgoing ocean currents (from tripolar to regular lat-lon). The rotation angles are provided
2495 !! from the native MOM grid by a call to `get_ocean_grid(Ocean_grid)`.
2496 !! The cosine and sine of the rotation angle are:
2497 !!
2498 !! ocean_grid%cos_rot(i,j)
2499 !! ocean_grid%sin_rot(i,j)
2500 !!
2501 !! The rotation of momentum flux from regular lat-lon to tripolar is:
2502 !! \f[
2503 !! \begin{bmatrix}
2504 !! \tau_x' \\
2505 !! \tau_y'
2506 !! \end{bmatrix} =
2507 !! \begin{bmatrix}
2508 !! cos \theta & sin \theta \\
2509 !! -sin \theta & cos \theta
2510 !! \end{bmatrix} *
2511 !! \begin{bmatrix}
2512 !! \tau_x \\
2513 !! \tau_y
2514 !! \end{bmatrix}
2515 !! \f]
2516 !!
2517 !! The rotation of ocean current from tripolar to regular lat-lon is:
2518 !! \f[
2519 !! \begin{bmatrix}
2520 !! u' \\
2521 !! v'
2522 !! \end{bmatrix} =
2523 !! \begin{bmatrix}
2524 !! cos \theta & -sin \theta \\
2525 !! sin \theta & cos \theta
2526 !! \end{bmatrix} *
2527 !! \begin{bmatrix}
2528 !! u \\
2529 !! v
2530 !! \end{bmatrix}
2531 !! \f]
2532 !! @subsection Finalization Finalization
2533 !!
2534 !! NUOPC infrastructure calls [ocean_model_finalize] (@ref MOM_cap_mod::ocean_model_finalize)
2535 !! at the end of the run. This subroutine is a hook to call into MOM's native shutdown
2536 !! procedures:
2537 !!
2538 !! call ocean_model_end (ocean_public, ocean_State, Time)
2539 !! call diag_manager_end(Time )
2540 !! call field_manager_end
2541 !! call fms_io_exit
2542 !! call fms_end
2543 !!
2544 !! @section ModelFields Model Fields
2545 !!
2546 !! The following tables list the import and export fields currently set up in the MOM cap.
2547 !!
2548 !! @subsection ImportFields Import Fields
2549 !!
2550 !! <table>
2551 !! <tr>
2552 !! <th>Standard Name</td>
2553 !! <th>Units</td>
2554 !! <th>Model Variable</td>
2555 !! <th>Description</td>
2556 !! <th>Notes</td>
2557 !! <tr>
2558 !! <td>inst_pres_height_surface</td>
2559 !! <td>Pa</td>
2560 !! <td>p</td>
2561 !! <td>pressure of overlying sea ice and atmosphere</td>
2562 !! <td></td>
2563 !! </tr>
2564 !! <tr>
2565 !! <td>mass_of_overlying_sea_ice</td>
2566 !! <td>kg</td>
2567 !! <td>mi</td>
2568 !! <td>mass of overlying sea ice</td>
2569 !! <td></td>
2570 !! </tr>
2571 !! <tr>
2572 !! <td>seaice_melt_heat</td>
2573 !! <td>W m-2</td>
2574 !! <td>seaice_melt_heat</td>
2575 !! <td>sea ice and snow melt heat flux</td>
2576 !! <td></td>
2577 !! </tr>
2578 !! <tr>
2579 !! <td>seaice_melt</td>
2580 !! <td>kg m-2 s-1</td>
2581 !! <td>seaice_melt</td>
2582 !! <td>water flux due to sea ice and snow melting</td>
2583 !! <td></td>
2584 !! </tr>
2585 !! <tr>
2586 !! <td>mean_calving_heat_flx</td>
2587 !! <td>W m-2</td>
2588 !! <td>calving_hflx</td>
2589 !! <td>heat flux, relative to 0C, of frozen land water into ocean</td>
2590 !! <td></td>
2591 !! </tr>
2592 !! <tr>
2593 !! <td>mean_calving_rate</td>
2594 !! <td>kg m-2 s-1</td>
2595 !! <td>calving</td>
2596 !! <td>mass flux of frozen runoff</td>
2597 !! <td></td>
2598 !! </tr>
2599 !! <tr>
2600 !! <td>mean_evap_rate</td>
2601 !! <td>kg m-2 s-1</td>
2602 !! <td>q_flux</td>
2603 !! <td>specific humidity flux</td>
2604 !! <td></td>
2605 !! </tr>
2606 !! <tr>
2607 !! <td>mean_fprec_rate</td>
2608 !! <td>kg m-2 s-1</td>
2609 !! <td>fprec</td>
2610 !! <td>mass flux of frozen precip</td>
2611 !! <td></td>
2612 !! </tr>
2613 !! <tr>
2614 !! <td>mean_merid_moment_flx</td>
2615 !! <td>Pa</td>
2616 !! <td>v_flux</td>
2617 !! <td>j-directed wind stress into ocean</td>
2618 !! <td>[vector rotation] (@ref VectorRotations) applied - lat-lon to tripolar</td>
2619 !! </tr>
2620 !! <tr>
2621 !! <td>mean_net_lw_flx</td>
2622 !! <td>W m-2</td>
2623 !! <td>lw_flux</td>
2624 !! <td>long wave radiation</td>
2625 !! <td></td>
2626 !! </tr>
2627 !! <tr>
2628 !! <td>mean_net_sw_ir_dif_flx</td>
2629 !! <td>W m-2</td>
2630 !! <td>sw_flux_nir_dif</td>
2631 !! <td>diffuse near IR shortwave radiation</td>
2632 !! <td></td>
2633 !! </tr>
2634 !! <tr>
2635 !! <td>mean_net_sw_ir_dir_flx</td>
2636 !! <td>W m-2</td>
2637 !! <td>sw_flux_nir_dir</td>
2638 !! <td>direct near IR shortwave radiation</td>
2639 !! <td></td>
2640 !! </tr>
2641 !! <tr>
2642 !! <td>mean_net_sw_vis_dif_flx</td>
2643 !! <td>W m-2</td>
2644 !! <td>sw_flux_vis_dif</td>
2645 !! <td>diffuse visible shortware radiation</td>
2646 !! <td></td>
2647 !! </tr>
2648 !! <tr>
2649 !! <td>mean_net_sw_vis_dir_flx</td>
2650 !! <td>W m-2</td>
2651 !! <td>sw_flux_vis_dir</td>
2652 !! <td>direct visible shortware radiation</td>
2653 !! <td></td>
2654 !! </tr>
2655 !! <tr>
2656 !! <td>mean_prec_rate</td>
2657 !! <td>kg m-2 s-1</td>
2658 !! <td>lprec</td>
2659 !! <td>mass flux of liquid precip</td>
2660 !! <td></td>
2661 !! </tr>
2662 !! <tr>
2663 !! <td>mean_runoff_heat_flx</td>
2664 !! <td>W m-2</td>
2665 !! <td>runoff_hflx</td>
2666 !! <td>heat flux, relative to 0C, of liquid land water into ocean</td>
2667 !! <td></td>
2668 !! </tr>
2669 !! <tr>
2670 !! <td>mean_runoff_rate</td>
2671 !! <td>kg m-2 s-1</td>
2672 !! <td>runoff</td>
2673 !! <td>mass flux of liquid runoff</td>
2674 !! <td></td>
2675 !! </tr>
2676 !! <tr>
2677 !! <td>mean_salt_rate</td>
2678 !! <td>kg m-2 s-1</td>
2679 !! <td>salt_flux</td>
2680 !! <td>salt flux</td>
2681 !! <td></td>
2682 !! </tr>
2683 !! <tr>
2684 !! <td>mean_sensi_heat_flx</td>
2685 !! <td>W m-2</td>
2686 !! <td>t_flux</td>
2687 !! <td>sensible heat flux into ocean</td>
2688 !! <td></td>
2689 !! </tr>
2690 !! <tr>
2691 !! <td>mean_zonal_moment_flx</td>
2692 !! <td>Pa</td>
2693 !! <td>u_flux</td>
2694 !! <td>i-directed wind stress into ocean</td>
2695 !! <td>[vector rotation] (@ref VectorRotations) applied - lat-lon to tripolar</td>
2696 !! </tr>
2697 !! </table>
2698 !!
2699 !! @subsection ExportField Export Fields
2700 !!
2701 !! Export fields are populated from the `ocean_public` parameter (type `ocean_public_type`)
2702 !! after the call to `update_ocean_model()`.
2703 !!
2704 !! <table>
2705 !! <tr>
2706 !! <th>Standard Name</th>
2707 !! <th>Units</th>
2708 !! <th>Model Variable</th>
2709 !! <th>Description</th>
2710 !! <th>Notes</th>
2711 !! </tr>
2712 !! <tr>
2713 !! <td>freezing_melting_potential</td>
2714 !! <td>W m-2</td>
2715 !! <td>combination of frazil and melt_potential</td>
2716 !! <td>cap converts model units (J m-2) to (W m-2) for export</td>
2717 !! <td></td>
2718 !! </tr>
2719 !! <tr>
2720 !! <td>ocean_mask</td>
2721 !! <td></td>
2722 !! <td></td>
2723 !! <td>ocean mask</td>
2724 !! <td></td>
2725 !! </tr>
2726 !! <tr>
2727 !! <td>ocn_current_merid</td>
2728 !! <td>m s-1</td>
2729 !! <td>v_surf</td>
2730 !! <td>j-directed surface velocity on u-cell</td>
2731 !! <td>[vector rotation] (@ref VectorRotations) applied - tripolar to lat-lon</td>
2732 !! </tr>
2733 !! <tr>
2734 !! <td>ocn_current_zonal</td>
2735 !! <td>m s-1</td>
2736 !! <td>u_surf</td>
2737 !! <td>i-directed surface velocity on u-cell</td>
2738 !! <td>[vector rotation] (@ref VectorRotations) applied - tripolar to lat-lon</td>
2739 !! </tr>
2740 !! <tr>
2741 !! <td>s_surf</td>
2742 !! <td>psu</td>
2743 !! <td>s_surf</td>
2744 !! <td>sea surface salinity on t-cell</td>
2745 !! <td></td>
2746 !! </tr>
2747 !! <tr>
2748 !! <td>sea_surface_temperature</td>
2749 !! <td>K</td>
2750 !! <td>t_surf</td>
2751 !! <td>sea surface temperature on t-cell</td>
2752 !! <td></td>
2753 !! </tr>
2754 !! <tr>
2755 !! <td>sea_surface_slope_zonal</td>
2756 !! <td>unitless</td>
2757 !! <td>created from ssh</td>
2758 !! <td>sea surface zonal slope</td>
2759 !! <td></td>
2760 !! </tr>
2761 !! <tr>
2762 !! <td>sea_surface_slope_merid</td>
2763 !! <td>unitless</td>
2764 !! <td>created from ssh</td>
2765 !! <td>sea surface meridional slope</td>
2766 !! <td></td>
2767 !! </tr>
2768 !! <tr>
2769 !! <td>so_bldepth</td>
2770 !! <td>m</td>
2771 !! <td>obld</td>
2772 !! <td>ocean surface boundary layer depth</td>
2773 !! <td></td>
2774 !! </tr>
2775 !! </table>
2776 !!
2777 !! @subsection MemoryManagement Memory Management
2778 !!
2779 !! The MOM cap has an internal state type with pointers to three
2780 !! types defined by MOM. There is also a small wrapper derived type
2781 !! required to associate an internal state instance
2782 !! with the ESMF/NUOPC component:
2783 !!
2784 !! type ocean_internalstate_type
2785 !! type(ocean_public_type), pointer :: ocean_public_type_ptr
2786 !! type(ocean_state_type), pointer :: ocean_state_type_ptr
2787 !! type(ice_ocean_boundary_type), pointer :: ice_ocean_boundary_type_ptr
2788 !! end type
2789 !!
2790 !! type ocean_internalstate_wrapper
2791 !! type(ocean_internalstate_type), pointer :: ptr
2792 !! end type
2793 !!
2794 !! The member of type `ocean_public_type` stores ocean surface fields used during the coupling.
2795 !! The member of type `ocean_state_type` is required by the ocean driver,
2796 !! although its internals are private (not to be used by the coupling directly).
2797 !! This type is passed to the ocean init and update routines
2798 !! so that it can maintain state there if desired.
2799 !! The member of type `ice_ocean_boundary_type` is populated by this cap
2800 !! with incoming coupling fields from other components. These three derived types are allocated during the
2801 !! [InitializeAdvertise] (@ref MOM_cap_mod::initializeadvertise) phase. Also during that
2802 !! phase, the `ice_ocean_boundary` type members are all allocated using bounds retrieved
2803 !! from `mpp_get_compute_domain()`.
2804 !!
2805 !! During the [InitializeRealize] (@ref MOM_cap_mod::initializerealize) phase,
2806 !! `ESMF_Field`s are created for each of the coupling fields in the `ice_ocean_boundary`
2807 !! and `ocean_public_type` members of the internal state. These fields directly reference into the members of
2808 !! the `ice_ocean_boundary` and `ocean_public_type` so that memory-to-memory copies are not required to move
2809 !! data from the cap's import and export states to the memory areas used internally
2810 !! by MOM.
2811 !!
2812 !! @subsection IO I/O
2813 !!
2814 !! The cap can optionally output coupling fields for diagnostic purposes if the ESMF attribute
2815 !! "DumpFields" has been set to "true". In this case the cap will write out NetCDF files
2816 !! with names "field_ocn_import_<fieldname>.nc" and "field_ocn_export_<fieldname>.nc".
2817 !! Additionally, calls will be made to the cap subroutine [dumpMomInternal]
2818 !! (@ref MOM_cap_mod::dumpmominternal) to write out model internal fields to files
2819 !! named "field_ocn_internal_<fieldname>.nc". In all cases these NetCDF files will
2820 !! contain a time series of field data.
2821 !!
2822 !! @section RuntimeConfiguration Runtime Configuration
2823 !!
2824 !! At runtime, the MOM cap can be configured with several options provided
2825 !! as ESMF attributes. Attributes can be set in the cap by the NUOPC Driver
2826 !! above this cap, or in some systems ESMF attributes are set by
2827 !! reading in from a configuration file. The available attributes are:
2828 !!
2829 !! * `DumpFields` - when set to "true", write out diagnostic NetCDF files for import/export/internal fields
2830 !! * `ProfileMemory` - when set to "true", write out memory usage information to the ESMF log files; this
2831 !! information is written when entering and leaving the [ModelAdvance]
2832 !! (@ref MOM_cap_mod::modeladvance) subroutine and before and after the call to
2833 !! `update_ocean_model()`.
2834 !! * `restart_interval` - integer number of seconds indicating the interval at
2835 !! which to call `ocean_model_restart()`; no restarts written if set to 0
2836 
2837 end module mom_cap_mod
mom_cap_mod::fldsfrocn
type(fld_list_type), dimension(fldsmax) fldsfrocn
Definition: mom_cap.F90:119
mom_cap_mod
This module contains a set of subroutines that are required by NUOPC.
Definition: mom_cap.F90:3
mom_cap_mod::runtype
character(len=32) runtype
run type
Definition: mom_cap.F90:127
mom_cap_mod::cesm_coupled
logical cesm_coupled
Definition: mom_cap.F90:142
mom_cap_mod::modeladvance
subroutine modeladvance(gcomp, rc)
Called by NUOPC to advance the model a single timestep.
Definition: mom_cap.F90:1569
mom_cap_mod::export_slice
integer export_slice
Definition: mom_cap.F90:123
mom_cap_mod::logunit
integer logunit
stdout logging unit number
Definition: mom_cap.F90:128
mom_cap_mod::shr_file_setlogunit
subroutine shr_file_setlogunit(nunit)
Definition: mom_cap.F90:2324
mom_cap_mod::u_file_u
character(len= *), parameter u_file_u
Definition: mom_cap.F90:135
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
mom_ocean_model_nuopc::get_ocean_grid
subroutine, public get_ocean_grid(OS, Gridp)
Definition: mom_ocean_model_nuopc.F90:1068
mom_ocean_model_nuopc::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_nuopc.F90:431
mom_get_input::directories
Container for paths and parameter file names.
Definition: MOM_get_input.F90:20
mom_cap_mod::fldstoocn
type(fld_list_type), dimension(fldsmax) fldstoocn
Definition: mom_cap.F90:117
mom_cap_mod::write_diagnostics
logical write_diagnostics
Definition: mom_cap.F90:125
mom_cap_mod::scalar_field_idx_grid_nx
integer scalar_field_idx_grid_nx
Definition: mom_cap.F90:133
mom_domains::pass_var
Do a halo update on an array.
Definition: MOM_domains.F90:49
mom_cap_mod::geomtype
type(esmf_geomtype_flag) geomtype
Definition: mom_cap.F90:143
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_cap_mod::initializep0
subroutine initializep0(gcomp, importState, exportState, clock, rc)
First initialize subroutine called by NUOPC. The purpose is to set which version of the Initialize Ph...
Definition: mom_cap.F90:244
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_cap_mod::scalar_field_count
integer scalar_field_count
Definition: mom_cap.F90:132
mom_cap_mod::scalar_field_name
character(len=128) scalar_field_name
Definition: mom_cap.F90:131
mom_get_input
Reads the only Fortran name list needed to boot-strap the model.
Definition: MOM_get_input.F90:6
mom_cap_mod::ocean_model_finalize
subroutine ocean_model_finalize(gcomp, rc)
Called by NUOPC at the end of the run to clean up.
Definition: mom_cap.F90:2046
mom_cap_mod::debug
integer debug
Definition: mom_cap.F90:121
mom_cap_methods::mom_set_geomtype
subroutine, public mom_set_geomtype(geomtype_in)
Sets module variable geometry type.
Definition: mom_cap_methods.F90:50
mom_cap_mod::fldsfrocn_num
integer fldsfrocn_num
Definition: mom_cap.F90:118
mom_domains
Describes the decomposed MOM domain and has routines for communications across PEs.
Definition: MOM_domains.F90:2
mom_cap_time::alarminit
subroutine, public alarminit(clock, alarm, option, opt_n, opt_ymd, opt_tod, RefTime, alarmname, rc)
Setup an alarm in a clock. The ringtime sent to AlarmCreate MUST be the next alarm time....
Definition: mom_cap_time.F90:69
mom_cap_mod::ocean_internalstate_type
Internal state type with pointers to three types defined by MOM.
Definition: mom_cap.F90:96
mom_ocean_model_nuopc::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_nuopc.F90:133
mom_ocean_model_nuopc::ocean_model_end
subroutine, public ocean_model_end(Ocean_sfc, Ocean_state, Time, write_restart)
ocean_model_end terminates the model run, saving the ocean state in a restart and deallocating any da...
Definition: mom_ocean_model_nuopc.F90:725
mom_cap_mod::initializerealize
subroutine initializerealize(gcomp, importState, exportState, clock, rc)
Called by NUOPC to realize import and export fields. "Realizing" a field means that its grid has been...
Definition: mom_cap.F90:839
mom_cap_methods::mom_export
subroutine, public mom_export(ocean_public, ocean_grid, ocean_state, exportState, clock, rc)
Maps outgoing ocean data to ESMF State.
Definition: mom_cap_methods.F90:309
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_ocean_model_nuopc::ocean_model_init_sfc
subroutine, public ocean_model_init_sfc(OS, Ocean_sfc)
This subroutine extracts the surface properties from the ocean's internal state and stores them in th...
Definition: mom_ocean_model_nuopc.F90:961
mom_cap_mod::datainitialize
subroutine datainitialize(gcomp, rc)
TODO.
Definition: mom_cap.F90:1472
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_cap_mod::fld_list_type
Contains field information.
Definition: mom_cap.F90:109
mom_cap_mod::modelsetrunclock
subroutine modelsetrunclock(gcomp, rc)
Definition: mom_cap.F90:1879
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_cap_mod::grid_attach_area
logical grid_attach_area
Definition: mom_cap.F90:130
mom_cap_mod::state_setscalar
subroutine state_setscalar(value, scalar_id, State, mytask, scalar_name, scalar_count, rc)
Set scalar data from state for a particula name.
Definition: mom_cap.F90:2102
mom_cap_mod::import_slice
integer import_slice
Definition: mom_cap.F90:122
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_cap_mod::shr_file_getlogunit
subroutine shr_file_getlogunit(nunit)
Definition: mom_cap.F90:2330
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_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_cap_mod::ocean_internalstate_wrapper
Wrapper-derived type required to associate an internal state instance with the ESMF/NUOPC component.
Definition: mom_cap.F90:104
mom_ocean_model_nuopc::ocean_model_restart
subroutine, public ocean_model_restart(OS, timestamp, restartname)
This subroutine writes out the ocean model restart file.
Definition: mom_ocean_model_nuopc.F90:673
mom_cap_methods::mom_import
subroutine, public mom_import(ocean_public, ocean_grid, importState, ice_ocean_boundary, rc)
This function has a few purposes: (1) it imports surface fluxes using data from the mediator; and (2)...
Definition: mom_cap_methods.F90:61
mom_cap_mod::overwrite_timeslice
logical overwrite_timeslice
Definition: mom_cap.F90:126
setscalarfield
subroutine setscalarfield(field, rc)
Definition: mom_cap.F90:2251
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_ocean_model_nuopc::ocean_public_type
This type is used for communication with other components via the FMS coupler. The element names and ...
Definition: mom_ocean_model_nuopc.F90:86
mom_ocean_model_nuopc::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_nuopc.F90:226
mom_cap_mod::scalar_field_idx_grid_ny
integer scalar_field_idx_grid_ny
Definition: mom_cap.F90:134
mom_cap_mod::setservices
subroutine, public setservices(gcomp, rc)
NUOPC SetService method is the only public entry point. SetServices registers all of the user-provide...
Definition: mom_cap.F90:155
mom_cap_mod::fld_list_add
subroutine fld_list_add(num, fldlist, stdname, transferOffer, shortname)
Set up list of field information.
Definition: mom_cap.F90:2292
mom_ocean_model_nuopc::get_eps_omesh
real function, public get_eps_omesh(OS)
Returns eps_omesh read from param file.
Definition: mom_ocean_model_nuopc.F90:1078
mom_cap_mod::initializeadvertise
subroutine initializeadvertise(gcomp, importState, exportState, clock, rc)
Called by NUOPC to advertise import and export fields. "Advertise" simply means that the standard nam...
Definition: mom_cap.F90:432
mom_cap_mod::profile_memory
logical profile_memory
Definition: mom_cap.F90:129
mom_cap_methods
Contains import/export methods for both NEMS and CMEPS.
Definition: mom_cap_methods.F90:2
time_utils_mod
Set of time utilities for converting between FMS and ESMF time type.
Definition: time_utils.F90:2
time_utils_mod::esmf2fms_time
Converts time from FMS to ESMF format.
Definition: time_utils.F90:27
mom_cap_mod::tmpstr
character(len=256) tmpstr
Definition: mom_cap.F90:124
mom_cap_time
This was originally share code in CIME, but required CIME as a dependency to build the MOM cap....
Definition: mom_cap_time.F90:7
mom_cap_mod::fldsmax
integer, parameter fldsmax
Definition: mom_cap.F90:115
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:26
mom_cap_mod::mom_realizefields
subroutine mom_realizefields(state, nfields, field_defs, tag, grid, mesh, rc)
Realize the import and export fields using either a grid or a mesh.
Definition: mom_cap.F90:2139
mom_cap_mod::fldstoocn_num
integer fldstoocn_num
Definition: mom_cap.F90:116
mom_ocean_model_nuopc
Top-level module for the MOM6 ocean model in coupled mode.
Definition: mom_ocean_model_nuopc.F90:2