MOM6
MOM_fixed_initialization.F90
Go to the documentation of this file.
1 !> Initializes fixed aspects of the model, such as horizontal grid metrics,
2 !! topography and Coriolis.
4 
5 ! This file is part of MOM6. See LICENSE.md for the license.
6 
7 use mom_debugging, only : hchksum, qchksum, uvchksum
8 use mom_domains, only : pass_var
10 use mom_error_handler, only : mom_mesg, mom_error, fatal, warning, is_root_pe
13 use mom_file_parser, only : log_version
14 use mom_io, only : slasher
20 ! use MOM_shared_initialization, only : MOM_shared_init_init
29 
43 
44 use netcdf
45 
46 implicit none ; private
47 
48 public mom_initialize_fixed, mom_initialize_rotation, mom_initialize_topography
49 
50 contains
51 
52 ! -----------------------------------------------------------------------------
53 !> MOM_initialize_fixed sets up time-invariant quantities related to MOM6's
54 !! horizontal grid, bathymetry, and the Coriolis parameter.
55 subroutine mom_initialize_fixed(G, US, OBC, PF, write_geom, output_dir)
56  type(dyn_horgrid_type), intent(inout) :: g !< The ocean's grid structure.
57  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
58  type(ocean_obc_type), pointer :: obc !< Open boundary structure.
59  type(param_file_type), intent(in) :: pf !< A structure indicating the open file
60  !! to parse for model parameter values.
61  logical, intent(in) :: write_geom !< If true, write grid geometry files.
62  character(len=*), intent(in) :: output_dir !< The directory into which to write files.
63 
64  ! Local
65  character(len=200) :: inputdir ! The directory where NetCDF input files are.
66  character(len=200) :: config
67  character(len=40) :: mdl = "MOM_fixed_initialization" ! This module's name.
68  logical :: debug
69 ! This include declares and sets the variable "version".
70 #include "version_variable.h"
71 
72  call calltree_enter("MOM_initialize_fixed(), MOM_fixed_initialization.F90")
73  call log_version(pf, mdl, version, "")
74  call get_param(pf, mdl, "DEBUG", debug, default=.false.)
75 
76  call get_param(pf, mdl, "INPUTDIR", inputdir, &
77  "The directory in which input files are found.", default=".")
78  inputdir = slasher(inputdir)
79 
80  ! Set up the parameters of the physical domain (i.e. the grid), G
81  call set_grid_metrics(g, pf, us)
82 
83  ! Set up the bottom depth, G%bathyT either analytically or from file
84  ! This also sets G%max_depth based on the input parameter MAXIMUM_DEPTH,
85  ! or, if absent, is diagnosed as G%max_depth = max( G%D(:,:) )
86  call mom_initialize_topography(g%bathyT, g%max_depth, g, pf, us)
87 ! call rescale_dyn_horgrid_bathymetry(G, US%Z_to_m)
88 
89  ! To initialize masks, the bathymetry in halo regions must be filled in
90  call pass_var(g%bathyT, g%Domain)
91 
92  ! Determine the position of any open boundaries
93  call open_boundary_config(g, us, pf, obc)
94 
95  ! Make bathymetry consistent with open boundaries
96  call open_boundary_impose_normal_slope(obc, g, g%bathyT)
97 
98  ! This call sets masks that prohibit flow over any point interpreted as land
99  call initialize_masks(g, pf, us)
100 
101  ! Make OBC mask consistent with land mask
102  call open_boundary_impose_land_mask(obc, g, g%areaCu, g%areaCv, us)
103 
104  if (debug) then
105  call hchksum(g%bathyT, 'MOM_initialize_fixed: depth ', g%HI, haloshift=1, scale=us%Z_to_m)
106  call hchksum(g%mask2dT, 'MOM_initialize_fixed: mask2dT ', g%HI)
107  call uvchksum('MOM_initialize_fixed: mask2dC[uv]', g%mask2dCu, &
108  g%mask2dCv, g%HI)
109  call qchksum(g%mask2dBu, 'MOM_initialize_fixed: mask2dBu ', g%HI)
110  endif
111 
112  ! Modulate geometric scales according to geography.
113  call get_param(pf, mdl, "CHANNEL_CONFIG", config, &
114  "A parameter that determines which set of channels are \n"//&
115  "restricted to specific widths. Options are:\n"//&
116  " \t none - All channels have the grid width.\n"//&
117  " \t global_1deg - Sets 16 specific channels appropriate \n"//&
118  " \t\t for a 1-degree model, as used in CM2G.\n"//&
119  " \t list - Read the channel locations and widths from a \n"//&
120  " \t\t text file, like MOM_channel_list in the MOM_SIS \n"//&
121  " \t\t test case.\n"//&
122  " \t file - Read open face widths everywhere from a \n"//&
123  " \t\t NetCDF file on the model grid.", &
124  default="none")
125  select case ( trim(config) )
126  case ("none")
127  case ("list") ; call reset_face_lengths_list(g, pf, us)
128  case ("file") ; call reset_face_lengths_file(g, pf, us)
129  case ("global_1deg") ; call reset_face_lengths_named(g, pf, trim(config), us)
130  case default ; call mom_error(fatal, "MOM_initialize_fixed: "// &
131  "Unrecognized channel configuration "//trim(config))
132  end select
133 
134  ! This call sets the topography at velocity points.
135  if (g%bathymetry_at_vel) then
136  call get_param(pf, mdl, "VELOCITY_DEPTH_CONFIG", config, &
137  "A string that determines how the topography is set at "//&
138  "velocity points. This may be 'min' or 'max'.", &
139  default="max")
140  select case ( trim(config) )
141  case ("max") ; call set_velocity_depth_max(g)
142  case ("min") ; call set_velocity_depth_min(g)
143  case default ; call mom_error(fatal, "MOM_initialize_fixed: "// &
144  "Unrecognized velocity depth configuration "//trim(config))
145  end select
146  endif
147 
148 ! Calculate the value of the Coriolis parameter at the latitude !
149 ! of the q grid points [s-1].
150  call mom_initialize_rotation(g%CoriolisBu, g, pf, us=us)
151 ! Calculate the components of grad f (beta)
152  call mom_calculate_grad_coriolis(g%dF_dx, g%dF_dy, g, us=us)
153  if (debug) then
154  call qchksum(g%CoriolisBu, "MOM_initialize_fixed: f ", g%HI, scale=us%s_to_T)
155  call hchksum(g%dF_dx, "MOM_initialize_fixed: dF_dx ", g%HI, scale=us%m_to_L*us%s_to_T)
156  call hchksum(g%dF_dy, "MOM_initialize_fixed: dF_dy ", g%HI, scale=us%m_to_L*us%s_to_T)
157  endif
158 
159  call initialize_grid_rotation_angle(g, pf)
160 
161 ! Compute global integrals of grid values for later use in scalar diagnostics !
162  call compute_global_grid_integrals(g, us=us)
163 
164 ! Write out all of the grid data used by this run.
165  if (write_geom) call write_ocean_geometry_file(g, pf, output_dir, us=us)
166 
167  call calltree_leave('MOM_initialize_fixed()')
168 
169 end subroutine mom_initialize_fixed
170 
171 !> MOM_initialize_topography makes the appropriate call to set up the bathymetry. At this
172 !! point the topography is in units of [m], but this can be changed later.
173 subroutine mom_initialize_topography(D, max_depth, G, PF, US)
174  type(dyn_horgrid_type), intent(in) :: g !< The dynamic horizontal grid type
175  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
176  intent(out) :: d !< Ocean bottom depth [m]
177  type(param_file_type), intent(in) :: pf !< Parameter file structure
178  real, intent(out) :: max_depth !< Maximum depth of model [m]
179  type(unit_scale_type), optional, intent(in) :: us !< A dimensional unit scaling type
180 
181  ! This subroutine makes the appropriate call to set up the bottom depth.
182  ! This is a separate subroutine so that it can be made public and shared with
183  ! the ice-sheet code or other components.
184 
185  ! Local variables
186  real :: m_to_z, z_to_m ! Dimensional rescaling factors
187  character(len=40) :: mdl = "MOM_initialize_topography" ! This subroutine's name.
188  character(len=200) :: config
189 
190  m_to_z = 1.0 ; if (present(us)) m_to_z = us%m_to_Z
191  z_to_m = 1.0 ; if (present(us)) z_to_m = us%Z_to_m
192 
193  call get_param(pf, mdl, "TOPO_CONFIG", config, &
194  "This specifies how bathymetry is specified: \n"//&
195  " \t file - read bathymetric information from the file \n"//&
196  " \t\t specified by (TOPO_FILE).\n"//&
197  " \t flat - flat bottom set to MAXIMUM_DEPTH. \n"//&
198  " \t bowl - an analytically specified bowl-shaped basin \n"//&
199  " \t\t ranging between MAXIMUM_DEPTH and MINIMUM_DEPTH. \n"//&
200  " \t spoon - a similar shape to 'bowl', but with an vertical \n"//&
201  " \t\t wall at the southern face. \n"//&
202  " \t halfpipe - a zonally uniform channel with a half-sine \n"//&
203  " \t\t profile in the meridional direction. \n"//&
204  " \t benchmark - use the benchmark test case topography. \n"//&
205  " \t Neverland - use the Neverland test case topography. \n"//&
206  " \t DOME - use a slope and channel configuration for the \n"//&
207  " \t\t DOME sill-overflow test case. \n"//&
208  " \t ISOMIP - use a slope and channel configuration for the \n"//&
209  " \t\t ISOMIP test case. \n"//&
210  " \t DOME2D - use a shelf and slope configuration for the \n"//&
211  " \t\t DOME2D gravity current/overflow test case. \n"//&
212  " \t Kelvin - flat but with rotated land mask.\n"//&
213  " \t seamount - Gaussian bump for spontaneous motion test case.\n"//&
214  " \t dumbbell - Sloshing channel with reservoirs on both ends.\n"//&
215  " \t shelfwave - exponential slope for shelfwave test case.\n"//&
216  " \t Phillips - ACC-like idealized topography used in the Phillips config.\n"//&
217  " \t dense - Denmark Strait-like dense water formation and overflow.\n"//&
218  " \t USER - call a user modified routine.", &
219  fail_if_missing=.true.)
220  max_depth = -1.e9*m_to_z ; call read_param(pf, "MAXIMUM_DEPTH", max_depth, scale=m_to_z)
221  select case ( trim(config) )
222  case ("file"); call initialize_topography_from_file(d, g, pf, us)
223  case ("flat"); call initialize_topography_named(d, g, pf, config, max_depth, us)
224  case ("spoon"); call initialize_topography_named(d, g, pf, config, max_depth, us)
225  case ("bowl"); call initialize_topography_named(d, g, pf, config, max_depth, us)
226  case ("halfpipe"); call initialize_topography_named(d, g, pf, config, max_depth, us)
227  case ("DOME"); call dome_initialize_topography(d, g, pf, max_depth, us)
228  case ("ISOMIP"); call isomip_initialize_topography(d, g, pf, max_depth, us)
229  case ("benchmark"); call benchmark_initialize_topography(d, g, pf, max_depth, us)
230  case ("Neverland"); call neverland_initialize_topography(d, g, pf, max_depth)
231  case ("DOME2D"); call dome2d_initialize_topography(d, g, pf, max_depth)
232  case ("Kelvin"); call kelvin_initialize_topography(d, g, pf, max_depth, us)
233  case ("sloshing"); call sloshing_initialize_topography(d, g, pf, max_depth)
234  case ("seamount"); call seamount_initialize_topography(d, g, pf, max_depth)
235  case ("dumbbell"); call dumbbell_initialize_topography(d, g, pf, max_depth)
236  case ("shelfwave"); call shelfwave_initialize_topography(d, g, pf, max_depth, us)
237  case ("Phillips"); call phillips_initialize_topography(d, g, pf, max_depth, us)
238  case ("dense"); call dense_water_initialize_topography(d, g, pf, max_depth)
239  case ("USER"); call user_initialize_topography(d, g, pf, max_depth, us)
240  case default ; call mom_error(fatal,"MOM_initialize_topography: "// &
241  "Unrecognized topography setup '"//trim(config)//"'")
242  end select
243  if (max_depth>0.) then
244  call log_param(pf, mdl, "MAXIMUM_DEPTH", max_depth*z_to_m, &
245  "The maximum depth of the ocean.", units="m")
246  else
247  max_depth = diagnosemaximumdepth(d,g)
248  call log_param(pf, mdl, "!MAXIMUM_DEPTH", max_depth*z_to_m, &
249  "The (diagnosed) maximum depth of the ocean.", units="m")
250  endif
251  if (trim(config) /= "DOME") then
252  call limit_topography(d, g, pf, max_depth, us)
253  endif
254 
255 end subroutine mom_initialize_topography
256 
257 end module mom_fixed_initialization
mom_shared_initialization
Code that initializes fixed aspects of the model grid, such as horizontal grid metrics,...
Definition: MOM_shared_initialization.F90:3
dome2d_initialization
Initialization of the 2D DOME experiment with density water initialized on a coastal shelf.
Definition: DOME2d_initialization.F90:2
mom_fixed_initialization::mom_initialize_fixed
subroutine, public mom_initialize_fixed(G, US, OBC, PF, write_geom, output_dir)
MOM_initialize_fixed sets up time-invariant quantities related to MOM6's horizontal grid,...
Definition: MOM_fixed_initialization.F90:56
mom_grid_initialize::set_grid_metrics
subroutine, public set_grid_metrics(G, param_file, US)
set_grid_metrics is used to set the primary values in the model's horizontal grid....
Definition: MOM_grid_initialize.F90:63
mom_open_boundary::open_boundary_impose_normal_slope
subroutine, public open_boundary_impose_normal_slope(OBC, G, depth)
Sets the slope of bathymetry normal to an open bounndary to zero.
Definition: MOM_open_boundary.F90:1594
mom_shared_initialization::reset_face_lengths_file
subroutine, public reset_face_lengths_file(G, param_file, US)
This subroutine sets the open face lengths at selected points to restrict passages to their observed ...
Definition: MOM_shared_initialization.F90:750
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
dome_initialization::dome_initialize_topography
subroutine, public dome_initialize_topography(D, G, param_file, max_depth, US)
This subroutine sets up the DOME topography.
Definition: DOME_initialization.F90:41
isomip_initialization::isomip_initialize_topography
subroutine, public isomip_initialize_topography(D, G, param_file, max_depth, US)
Initialization of topography for the ISOMIP configuration.
Definition: ISOMIP_initialization.F90:45
mom_dyn_horgrid
Contains a shareable dynamic type for describing horizontal grids and metric data and utilty routines...
Definition: MOM_dyn_horgrid.F90:3
kelvin_initialization
Configures the model for the Kelvin wave experiment.
Definition: Kelvin_initialization.F90:6
benchmark_initialization::benchmark_initialize_topography
subroutine, public benchmark_initialize_topography(D, G, param_file, max_depth, US)
This subroutine sets up the benchmark test case topography.
Definition: benchmark_initialization.F90:35
mom_error_handler::mom_mesg
subroutine, public mom_mesg(message, verb, all_print)
This provides a convenient interface for writing an informative comment.
Definition: MOM_error_handler.F90:53
mom_shared_initialization::read_face_length_list
subroutine, public read_face_length_list(iounit, filename, num_lines, lines)
This subroutine reads and counts the non-blank lines in the face length list file,...
Definition: MOM_shared_initialization.F90:1055
shelfwave_initialization
Configures the model for the idealized shelfwave test case.
Definition: shelfwave_initialization.F90:2
mom_domains::pass_var
Do a halo update on an array.
Definition: MOM_domains.F90:49
sloshing_initialization::sloshing_initialize_topography
subroutine, public sloshing_initialize_topography(D, G, param_file, max_depth)
Initialization of topography.
Definition: sloshing_initialization.F90:32
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_shared_initialization::set_rotation_beta_plane
subroutine, public set_rotation_beta_plane(f, G, param_file, US)
This subroutine sets up the Coriolis parameter for a beta-plane or f-plane.
Definition: MOM_shared_initialization.F90:497
mom_io
This module contains I/O framework code.
Definition: MOM_io.F90:2
mom_fixed_initialization::mom_initialize_topography
subroutine, public mom_initialize_topography(D, max_depth, G, PF, US)
MOM_initialize_topography makes the appropriate call to set up the bathymetry. At this point the topo...
Definition: MOM_fixed_initialization.F90:174
mom_shared_initialization::reset_face_lengths_named
subroutine, public reset_face_lengths_named(G, param_file, name, US)
This subroutine sets the open face lengths at selected points to restrict passages to their observed ...
Definition: MOM_shared_initialization.F90:622
mom_open_boundary::open_boundary_query
logical function, public open_boundary_query(OBC, apply_open_OBC, apply_specified_OBC, apply_Flather_OBC, apply_nudged_OBC, needs_ext_seg_data)
Definition: MOM_open_boundary.F90:1541
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
shelfwave_initialization::shelfwave_initialize_topography
subroutine, public shelfwave_initialize_topography(D, G, param_file, max_depth, US)
Initialization of topography.
Definition: shelfwave_initialization.F90:98
neverland_initialization
Initialization for the "Neverland" configuration.
Definition: Neverland_initialization.F90:2
mom_shared_initialization::set_velocity_depth_min
subroutine, public set_velocity_depth_min(G)
Set the bathymetry at velocity points to be the minimum of the depths at the neighoring tracer points...
Definition: MOM_shared_initialization.F90:1129
mom_shared_initialization::limit_topography
subroutine, public limit_topography(D, G, param_file, max_depth, US)
limit_topography ensures that min_depth < D(x,y) < max_depth
Definition: MOM_shared_initialization.F90:415
dumbbell_initialization
Configures the model for the idealized dumbbell test case.
Definition: dumbbell_initialization.F90:2
dense_water_initialization
Initialization routines for the dense water formation and overflow experiment.
Definition: dense_water_initialization.F90:3
mom_shared_initialization::initialize_topography_from_file
subroutine, public initialize_topography_from_file(D, G, param_file, US)
Read gridded depths from file.
Definition: MOM_shared_initialization.F90:141
mom_shared_initialization::set_velocity_depth_max
subroutine, public set_velocity_depth_max(G)
Set the bathymetry at velocity points to be the maximum of the depths at the neighoring tracer points...
Definition: MOM_shared_initialization.F90:1109
seamount_initialization::seamount_initialize_topography
subroutine, public seamount_initialize_topography(D, G, param_file, max_depth)
Initialization of topography.
Definition: seamount_initialization.F90:42
phillips_initialization::phillips_initialize_topography
subroutine, public phillips_initialize_topography(D, G, param_file, max_depth, US)
Initialize topography.
Definition: Phillips_initialization.F90:297
mom_shared_initialization::set_rotation_planetary
subroutine, public set_rotation_planetary(f, G, param_file, US)
This subroutine sets up the Coriolis parameter for a sphere.
Definition: MOM_shared_initialization.F90:464
mom_domains
Describes the decomposed MOM domain and has routines for communications across PEs.
Definition: MOM_domains.F90:2
neverland_initialization::neverland_initialize_topography
subroutine, public neverland_initialize_topography(D, G, param_file, max_depth)
This subroutine sets up the Neverland test case topography.
Definition: Neverland_initialization.F90:36
benchmark_initialization
Initialization for the "bench mark" configuration.
Definition: benchmark_initialization.F90:2
mom_shared_initialization::apply_topography_edits_from_file
subroutine, public apply_topography_edits_from_file(D, G, param_file, US)
Applies a list of topography overrides read from a netcdf file.
Definition: MOM_shared_initialization.F90:186
mom_shared_initialization::initialize_topography_named
subroutine, public initialize_topography_named(D, G, param_file, topog_config, max_depth, US)
initialize the bathymetry based on one of several named idealized configurations
Definition: MOM_shared_initialization.F90:302
mom_fixed_initialization
Initializes fixed aspects of the model, such as horizontal grid metrics, topography and Coriolis.
Definition: MOM_fixed_initialization.F90:3
mom_open_boundary
Controls where open boundary conditions are applied.
Definition: MOM_open_boundary.F90:2
dome_initialization
Configures the model for the "DOME" experiment. DOME = Dynamics of Overflows and Mixing Experiment.
Definition: DOME_initialization.F90:3
mom_shared_initialization::mom_initialize_rotation
subroutine, public mom_initialize_rotation(f, G, PF, US)
MOM_initialize_rotation makes the appropriate call to set up the Coriolis parameter.
Definition: MOM_shared_initialization.F90:58
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
sloshing_initialization
Initialization for the "sloshing" internal waves configuration.
Definition: sloshing_initialization.F90:2
mom_shared_initialization::mom_calculate_grad_coriolis
subroutine, public mom_calculate_grad_coriolis(dF_dx, dF_dy, G, US)
Calculates the components of grad f (Coriolis parameter)
Definition: MOM_shared_initialization.F90:91
mom_error_handler::calltree_leave
subroutine, public calltree_leave(mesg)
Writes a message about leaving a subroutine if call tree reporting is active.
Definition: MOM_error_handler.F90:151
user_initialization::user_initialize_topography
subroutine, public user_initialize_topography(D, G, param_file, max_depth, US)
Initialize topography.
Definition: user_initialization.F90:65
kelvin_initialization::kelvin_initialize_topography
subroutine, public kelvin_initialize_topography(D, G, param_file, max_depth, US)
This subroutine sets up the Kelvin topography and land mask.
Definition: Kelvin_initialization.F90:132
mom_open_boundary::ocean_obc_type
Open-boundary data.
Definition: MOM_open_boundary.F90:195
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
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_grid_initialize
Initializes horizontal grid.
Definition: MOM_grid_initialize.F90:2
dumbbell_initialization::dumbbell_initialize_topography
subroutine, public dumbbell_initialize_topography(D, G, param_file, max_depth)
Initialization of topography.
Definition: dumbbell_initialization.F90:43
mom_debugging
Provides checksumming functions for debugging.
Definition: MOM_debugging.F90:7
mom_shared_initialization::initialize_grid_rotation_angle
subroutine, public initialize_grid_rotation_angle(G, PF)
initialize_grid_rotation_angle initializes the arrays with the sine and cosine of the angle between l...
Definition: MOM_shared_initialization.F90:548
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_error_handler::calltree_waypoint
subroutine, public calltree_waypoint(mesg, n)
Writes a message about reaching a milestone if call tree reporting is active.
Definition: MOM_error_handler.F90:161
mom_dyn_horgrid::rescale_dyn_horgrid_bathymetry
subroutine, public rescale_dyn_horgrid_bathymetry(G, m_in_new_units)
rescale_dyn_horgrid_bathymetry permits a change in the internal units for the bathymetry on the grid,...
Definition: MOM_dyn_horgrid.F90:285
mom_grid_initialize::initialize_masks
subroutine, public initialize_masks(G, PF, US)
Initializes the grid masks and any metrics that come with masks already applied.
Definition: MOM_grid_initialize.F90:1235
mom_file_parser::log_param
An overloaded interface to log the values of various types of parameters.
Definition: MOM_file_parser.F90:96
dense_water_initialization::dense_water_initialize_topography
subroutine, public dense_water_initialize_topography(D, G, param_file, max_depth)
Initialize the topography field for the dense water experiment.
Definition: dense_water_initialization.F90:36
seamount_initialization
Configures the model for the idealized seamount test case.
Definition: seamount_initialization.F90:2
phillips_initialization
Initialization for the "Phillips" channel configuration.
Definition: Phillips_initialization.F90:2
mom_shared_initialization::reset_face_lengths_list
subroutine, public reset_face_lengths_list(G, param_file, US)
This subroutine sets the open face lengths at selected points to restrict passages to their observed ...
Definition: MOM_shared_initialization.F90:820
mom_shared_initialization::write_ocean_geometry_file
subroutine, public write_ocean_geometry_file(G, param_file, directory, geom_file, US)
Write out a file describing the topography, Coriolis parameter, grid locations and various other fixe...
Definition: MOM_shared_initialization.F90:1178
mom_open_boundary::open_boundary_config
subroutine, public open_boundary_config(G, US, param_file, OBC)
Enables OBC module and reads configuration parameters This routine is called from MOM_initialize_fixe...
Definition: MOM_open_boundary.F90:317
mom_shared_initialization::compute_global_grid_integrals
subroutine, public compute_global_grid_integrals(G, US)
Pre-compute global integrals of grid quantities (like masked ocean area) for later use in reporting d...
Definition: MOM_shared_initialization.F90:1149
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
dome2d_initialization::dome2d_initialize_topography
subroutine, public dome2d_initialize_topography(D, G, param_file, max_depth)
Initialize topography with a shelf and slope in a 2D domain.
Definition: DOME2d_initialization.F90:42
mom_error_handler::calltree_enter
subroutine, public calltree_enter(mesg, n)
Writes a message about entering a subroutine if call tree reporting is active.
Definition: MOM_error_handler.F90:130
mom_dyn_horgrid::dyn_horgrid_type
Describes the horizontal ocean grid with only dynamic memory arrays.
Definition: MOM_dyn_horgrid.F90:23
isomip_initialization
Configures the ISOMIP test case.
Definition: ISOMIP_initialization.F90:2
mom_shared_initialization::diagnosemaximumdepth
real function, public diagnosemaximumdepth(D, G)
Return the global maximum ocean bottom depth in the same units as the input depth.
Definition: MOM_shared_initialization.F90:125
mom_open_boundary::open_boundary_impose_land_mask
subroutine, public open_boundary_impose_land_mask(OBC, G, areaCu, areaCv, US)
Reconcile masks and open boundaries, deallocate OBC on PEs where it is not needed....
Definition: MOM_open_boundary.F90:1639
user_initialization
A template of a user to code up customized initial conditions.
Definition: user_initialization.F90:2
mom_file_parser::read_param
An overloaded interface to read various types of parameters.
Definition: MOM_file_parser.F90:90