MOM6
MOM_state_initialization.F90
Go to the documentation of this file.
1 !> Initialize state variables, u, v, h, T and S.
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 use mom_debugging, only : hchksum, qchksum, uvchksum
7 use mom_coms, only : max_across_pes, min_across_pes, reproducing_sum
8 use mom_cpu_clock, only : cpu_clock_id, cpu_clock_begin, cpu_clock_end
9 use mom_cpu_clock, only : clock_routine, clock_loop
10 use mom_domains, only : pass_var, pass_vector, sum_across_pes, broadcast
11 use mom_domains, only : root_pe, to_all, scalar_pair, cgrid_ne, agrid
13 use mom_error_handler, only : mom_mesg, mom_error, fatal, warning, is_root_pe
16 use mom_file_parser, only : log_version
17 use mom_get_input, only : directories
20 use mom_io, only : close_file, fieldtype, file_exists
21 use mom_io, only : open_file, read_data, read_axis_data, single_file, multiple
22 use mom_io, only : slasher, vardesc, write_field
23 use mom_io, only : east_face, north_face
27 !use MOM_open_boundary, only : set_3D_OBC_data
33 use mom_ale_sponge, only : ale_sponge_cs
35 use mom_time_manager, only : time_type, set_time
81 
84 
90 use mom_tracer_initialization_from_z, only : horiz_interp_and_extrap_tracer
91 
92 implicit none ; private
93 
94 #include <MOM_memory.h>
95 
97 
98 character(len=40) :: mdl = "MOM_state_initialization" ! This module's name.
99 
100 contains
101 
102 ! -----------------------------------------------------------------------------
103 subroutine mom_initialize_state(u, v, h, tv, Time, G, GV, PF, dirs, &
104  restart_CS, ALE_CSp, tracer_Reg, sponge_CSp, &
105  ALE_sponge_CSp, OBC, Time_in)
106  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure.
107  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
108  real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), &
109  intent(out) :: u !< The zonal velocity that is being initialized,
110  !! in m s-1
111  real, dimension(SZI_(G),SZJB_(G),SZK_(G)), &
112  intent(out) :: v !< The meridional velocity that is being
113  !! initialized, in m s-1
114  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
115  intent(out) :: h !< Layer thicknesses, in H (usually m or
116  !! kg m-2)
117  type(thermo_var_ptrs), intent(inout) :: tv !< A structure pointing to various thermodynamic
118  !! variables
119  type(time_type), intent(inout) :: Time !< Time at the start of the run segment.
120  type(param_file_type), intent(in) :: PF !< A structure indicating the open file to parse
121  !! for model parameter values.
122  type(directories), intent(in) :: dirs !< A structure containing several relevant
123  !! directory paths.
124  type(mom_restart_cs), pointer :: restart_CS !< A pointer to the restart control
125  !! structure.
126  type(ale_cs), pointer :: ALE_CSp
127  type(tracer_registry_type), pointer :: tracer_Reg
128  type(sponge_cs), pointer :: sponge_CSp
129  type(ale_sponge_cs), pointer :: ALE_sponge_CSp
130  type(ocean_obc_type), pointer :: OBC
131  type(time_type), optional, intent(in) :: Time_in !< Time at the start of the run segment.
132  !! Time_in overrides any value set for Time.
133 ! Arguments: u - Zonal velocity, in m s-1.
134 ! (out) v - Meridional velocity, in m s-1.
135 ! (out) h - Layer thickness, in m.
136 ! (out) tv - A structure containing pointers to any available
137 ! thermodynamic fields, including potential temperature and
138 ! salinity or mixed layer density. Absent fields have NULL ptrs.
139 ! (out) Time - Time at the start of the run segment.
140 ! (inout) G - The ocean's grid structure.
141 ! (in) GV - The ocean's vertical grid structure.
142 ! (in) PF - A structure indicating the open file to parse for
143 ! model parameter values.
144 ! (in) dirs - A structure containing several relevant directory paths.
145 ! (inout) restart_CS - A pointer to the restart control structure.
146 ! (inout) CS - A structure of pointers to be exchanged with MOM.F90.
147 ! (in) Time_in - Time at the start of the run segment. Time_in overrides
148 ! any value set for Time.
149 
150  character(len=200) :: filename ! The name of an input file.
151  character(len=200) :: filename2 ! The name of an input files.
152  character(len=200) :: inputdir ! The directory where NetCDF input files are.
153  character(len=200) :: config
154  logical :: from_Z_file, useALE
155  logical :: new_sim
156  integer :: write_geom
157  logical :: use_temperature, use_sponge
158  logical :: use_EOS ! If true, density is calculated from T & S using an
159  ! equation of state.
160  logical :: depress_sfc ! If true, remove the mass that would be displaced
161  ! by a large surface pressure by squeezing the column.
162  logical :: trim_ic_for_p_surf ! If true, remove the mass that would be displaced
163  ! by a large surface pressure, such as with an ice sheet.
164  logical :: regrid_accelerate
165  integer :: regrid_iterations
166  logical :: Analytic_FV_PGF, obsol_test
167  logical :: convert
168  logical :: just_read ! If true, only read the parameters because this
169  ! is a run from a restart file; this option
170  ! allows the use of Fatal unused parameters.
171  type(eos_type), pointer :: eos => null()
172  logical :: debug ! indicates whether to write debugging output
173 ! This include declares and sets the variable "version".
174 #include "version_variable.h"
175  integer :: i, j, k, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz
176  integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
177 
178  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
179  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
180  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
181  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
182 
183  call calltree_enter("MOM_initialize_state(), MOM_state_initialization.F90")
184  call log_version(pf, mdl, version, "")
185  call get_param(pf, mdl, "DEBUG", debug, default=.false.)
186 
187  new_sim = .false.
188  if ((dirs%input_filename(1:1) == 'n') .and. &
189  (len_trim(dirs%input_filename) == 1)) new_sim = .true.
190 
191  just_read = .not.new_sim
192 
193  call get_param(pf, mdl, "INPUTDIR", inputdir, &
194  "The directory in which input files are found.", default=".")
195  inputdir = slasher(inputdir)
196 
197  use_temperature = ASSOCIATED(tv%T)
198  useale = associated(ale_csp)
199  use_eos = associated(tv%eqn_of_state)
200  if (use_eos) eos => tv%eqn_of_state
201 
202 !====================================================================
203 ! Initialize temporally evolving fields, either as initial
204 ! conditions or by reading them from a restart (or saves) file.
205 !====================================================================
206 
207  if (new_sim) then
208  call mom_mesg("Run initialized internally.", 3)
209 
210  if (present(time_in)) time = time_in
211  ! Otherwise leave Time at its input value.
212 
213  ! This initialization should not be needed. Certainly restricting it
214  ! to the computational domain helps detect possible uninitialized
215  ! data in halos which should be covered by the pass_var(h) later.
216  !do k = 1, nz; do j = js, je; do i = is, ie
217  ! h(i,j,k) = 0.
218  !enddo
219  endif
220 
221  ! The remaining initialization calls are done, regardless of whether the
222  ! fields are actually initialized here (if just_read=.false.) or whether it
223  ! is just to make sure that all valid parameters are read to enable the
224  ! detection of unused parameters.
225  call get_param(pf, mdl, "INIT_LAYERS_FROM_Z_FILE", from_z_file, &
226  "If true, intialize the layer thicknesses, temperatures, \n"//&
227  "and salnities from a Z-space file on a latitude- \n"//&
228  "longitude grid.", default=.false., do_not_log=just_read)
229 
230  if (from_z_file) then
231 ! Initialize thickness and T/S from z-coordinate data in a file.
232  if (.NOT.use_temperature) call mom_error(fatal,"MOM_initialize_state : "//&
233  "use_temperature must be true if INIT_LAYERS_FROM_Z_FILE is true")
234 
235  call mom_temp_salt_initialize_from_z(h, tv, g, gv, pf, just_read_params=just_read)
236 
237  else
238 ! Initialize thickness, h.
239  call get_param(pf, mdl, "THICKNESS_CONFIG", config, &
240  "A string that determines how the initial layer \n"//&
241  "thicknesses are specified for a new run: \n"//&
242  " \t file - read interface heights from the file specified \n"//&
243  " \t thickness_file - read thicknesses from the file specified \n"//&
244  " \t\t by (THICKNESS_FILE).\n"//&
245  " \t coord - determined by ALE coordinate.\n"//&
246  " \t uniform - uniform thickness layers evenly distributed \n"//&
247  " \t\t between the surface and MAXIMUM_DEPTH. \n"//&
248  " \t DOME - use a slope and channel configuration for the \n"//&
249  " \t\t DOME sill-overflow test case. \n"//&
250  " \t ISOMIP - use a configuration for the \n"//&
251  " \t\t ISOMIP test case. \n"//&
252  " \t benchmark - use the benchmark test case thicknesses. \n"//&
253  " \t search - search a density profile for the interface \n"//&
254  " \t\t densities. This is not yet implemented. \n"//&
255  " \t circle_obcs - the circle_obcs test case is used. \n"//&
256  " \t DOME2D - 2D version of DOME initialization. \n"//&
257  " \t adjustment2d - TBD AJA. \n"//&
258  " \t sloshing - TBD AJA. \n"//&
259  " \t seamount - TBD AJA. \n"//&
260  " \t soliton - Equatorial Rossby soliton. \n"//&
261  " \t rossby_front - a mixed layer front in thermal wind balance.\n"//&
262  " \t USER - call a user modified routine.", &
263  fail_if_missing=new_sim, do_not_log=just_read)
264  select case (trim(config))
265  case ("file"); call initialize_thickness_from_file(h, g, gv, pf, .false., just_read_params=just_read)
266  case ("thickness_file"); call initialize_thickness_from_file(h, g, gv, pf, .true., just_read_params=just_read)
267  case ("coord")
268  if (new_sim .and. useale) then
269  call ale_initthicknesstocoord( ale_csp, g, gv, h )
270  elseif (new_sim) then
271  call mom_error(fatal, "MOM_initialize_state: USE_REGRIDDING must be True "//&
272  "for THICKNESS_CONFIG of 'coord'")
273  endif
274  case ("uniform"); call initialize_thickness_uniform(h, g, gv, pf, &
275  just_read_params=just_read)
276  case ("DOME"); call dome_initialize_thickness(h, g, gv, pf, &
277  just_read_params=just_read)
278  case ("ISOMIP"); call isomip_initialize_thickness(h, g, gv, pf, tv, &
279  just_read_params=just_read)
280  case ("benchmark"); call benchmark_initialize_thickness(h, g, gv, pf, &
281  tv%eqn_of_state, tv%P_Ref, just_read_params=just_read)
282  case ("search"); call initialize_thickness_search
283  case ("circle_obcs"); call circle_obcs_initialize_thickness(h, g, gv, pf, &
284  just_read_params=just_read)
285  case ("lock_exchange"); call lock_exchange_initialize_thickness(h, g, gv, &
286  pf, just_read_params=just_read)
287  case ("external_gwave"); call external_gwave_initialize_thickness(h, g, &
288  pf, just_read_params=just_read)
289  case ("DOME2D"); call dome2d_initialize_thickness(h, g, gv, pf, &
290  just_read_params=just_read)
291  case ("adjustment2d"); call adjustment_initialize_thickness(h, g, gv, &
292  pf, just_read_params=just_read)
293  case ("sloshing"); call sloshing_initialize_thickness(h, g, gv, pf, &
294  just_read_params=just_read)
295  case ("seamount"); call seamount_initialize_thickness(h, g, gv, pf, &
296  just_read_params=just_read)
297  case ("soliton"); call soliton_initialize_thickness(h, g)
298  case ("phillips"); call phillips_initialize_thickness(h, g, gv, pf, &
299  just_read_params=just_read)
300  case ("rossby_front"); call rossby_front_initialize_thickness(h, g, gv, &
301  pf, just_read_params=just_read)
302  case ("USER"); call user_initialize_thickness(h, g, pf, tv%T, &
303  just_read_params=just_read)
304  case default ; call mom_error(fatal, "MOM_initialize_state: "//&
305  "Unrecognized layer thickness configuration "//trim(config))
306  end select
307 
308 ! Initialize temperature and salinity (T and S).
309  if ( use_temperature ) then
310  call get_param(pf, mdl, "TS_CONFIG", config, &
311  "A string that determines how the initial tempertures \n"//&
312  "and salinities are specified for a new run: \n"//&
313  " \t file - read velocities from the file specified \n"//&
314  " \t\t by (TS_FILE). \n"//&
315  " \t fit - find the temperatures that are consistent with \n"//&
316  " \t\t the layer densities and salinity S_REF. \n"//&
317  " \t TS_profile - use temperature and salinity profiles \n"//&
318  " \t\t (read from TS_FILE) to set layer densities. \n"//&
319  " \t benchmark - use the benchmark test case T & S. \n"//&
320  " \t linear - linear in logical layer space. \n"//&
321  " \t DOME2D - 2D DOME initialization. \n"//&
322  " \t ISOMIP - ISOMIP initialization. \n"//&
323  " \t adjustment2d - TBD AJA. \n"//&
324  " \t sloshing - TBD AJA. \n"//&
325  " \t seamount - TBD AJA. \n"//&
326  " \t rossby_front - a mixed layer front in thermal wind balance.\n"//&
327  " \t SCM_ideal_hurr - used in the SCM idealized hurricane test.\n"//&
328  " \t SCM_CVmix_tests - used in the SCM CVmix tests.\n"//&
329  " \t USER - call a user modified routine.", &
330  fail_if_missing=new_sim, do_not_log=just_read)
331 ! " \t baroclinic_zone - an analytic baroclinic zone. \n"//&
332  select case (trim(config))
333  case ("fit"); call initialize_temp_salt_fit(tv%T, tv%S, g, gv, pf, &
334  eos, tv%P_Ref, just_read_params=just_read)
335  case ("file"); call initialize_temp_salt_from_file(tv%T, tv%S, g, &
336  pf, just_read_params=just_read)
337  case ("benchmark"); call benchmark_init_temperature_salinity(tv%T, tv%S, &
338  g, gv, pf, eos, tv%P_Ref, just_read_params=just_read)
339  case ("TS_profile") ; call initialize_temp_salt_from_profile(tv%T, tv%S, &
340  g, pf, just_read_params=just_read)
341  case ("linear"); call initialize_temp_salt_linear(tv%T, tv%S, g, pf, &
342  just_read_params=just_read)
343  case ("DOME2D"); call dome2d_initialize_temperature_salinity ( tv%T, &
344  tv%S, h, g, pf, eos, just_read_params=just_read)
345  case ("ISOMIP"); call isomip_initialize_temperature_salinity ( tv%T, &
346  tv%S, h, g, gv, pf, eos, just_read_params=just_read)
347  case ("adjustment2d"); call adjustment_initialize_temperature_salinity ( tv%T, &
348  tv%S, h, g, pf, eos, just_read_params=just_read)
349  case ("baroclinic_zone"); call baroclinic_zone_init_temperature_salinity( tv%T, &
350  tv%S, h, g, pf, just_read_params=just_read)
351  case ("sloshing"); call sloshing_initialize_temperature_salinity(tv%T, &
352  tv%S, h, g, pf, eos, just_read_params=just_read)
353  case ("seamount"); call seamount_initialize_temperature_salinity(tv%T, &
354  tv%S, h, g, gv, pf, eos, just_read_params=just_read)
355  case ("rossby_front"); call rossby_front_initialize_temperature_salinity ( tv%T, &
356  tv%S, h, g, pf, eos, just_read_params=just_read)
357  case ("SCM_ideal_hurr"); call scm_idealized_hurricane_ts_init ( tv%T, &
358  tv%S, h, g, gv, pf, just_read_params=just_read)
359  case ("SCM_CVmix_tests"); call scm_cvmix_tests_ts_init (tv%T, &
360  tv%S, h, g, gv, pf, just_read_params=just_read)
361  case ("dense"); call dense_water_initialize_ts(g, gv, pf, eos, tv%T, tv%S, &
362  h, just_read_params=just_read)
363  case ("USER"); call user_init_temperature_salinity(tv%T, tv%S, g, pf, eos, &
364  just_read_params=just_read)
365  case default ; call mom_error(fatal, "MOM_initialize_state: "//&
366  "Unrecognized Temp & salt configuration "//trim(config))
367  end select
368  endif
369  endif ! not from_Z_file.
370 
371  ! The thicknesses in halo points might be needed to initialize the velocities.
372  if (new_sim) call pass_var(h, g%Domain)
373 
374 ! Initialize velocity components, u and v
375  call get_param(pf, mdl, "VELOCITY_CONFIG", config, &
376  "A string that determines how the initial velocities \n"//&
377  "are specified for a new run: \n"//&
378  " \t file - read velocities from the file specified \n"//&
379  " \t\t by (VELOCITY_FILE). \n"//&
380  " \t zero - the fluid is initially at rest. \n"//&
381  " \t uniform - the flow is uniform (determined by\n"//&
382  " \t\t parameters INITIAL_U_CONST and INITIAL_V_CONST).\n"//&
383  " \t rossby_front - a mixed layer front in thermal wind balance.\n"//&
384  " \t soliton - Equatorial Rossby soliton.\n"//&
385  " \t USER - call a user modified routine.", default="zero", &
386  do_not_log=just_read)
387  select case (trim(config))
388  case ("file"); call initialize_velocity_from_file(u, v, g, pf, &
389  just_read_params=just_read)
390  case ("zero"); call initialize_velocity_zero(u, v, g, pf, &
391  just_read_params=just_read)
392  case ("uniform"); call initialize_velocity_uniform(u, v, g, pf, &
393  just_read_params=just_read)
394  case ("circular"); call initialize_velocity_circular(u, v, g, pf, &
395  just_read_params=just_read)
396  case ("phillips"); call phillips_initialize_velocity(u, v, g, gv, pf, &
397  just_read_params=just_read)
398  case ("rossby_front"); call rossby_front_initialize_velocity(u, v, h, &
399  g, gv, pf, just_read_params=just_read)
400  case ("soliton"); call soliton_initialize_velocity(u, v, h, g)
401  case ("USER"); call user_initialize_velocity(u, v, g, pf, &
402  just_read_params=just_read)
403  case default ; call mom_error(fatal, "MOM_initialize_state: "//&
404  "Unrecognized velocity configuration "//trim(config))
405  end select
406 
407  if (new_sim) call pass_vector(u, v, g%Domain)
408  if (debug .and. new_sim) then
409  call uvchksum("MOM_initialize_state [uv]", u, v, g%HI, haloshift=1)
410  endif
411 
412 ! Optionally convert the thicknesses from m to kg m-2. This is particularly
413 ! useful in a non-Boussinesq model.
414  call get_param(pf, mdl, "CONVERT_THICKNESS_UNITS", convert, &
415  "If true, convert the thickness initial conditions from \n"//&
416  "units of m to kg m-2 or vice versa, depending on whether \n"//&
417  "BOUSSINESQ is defined. This does not apply if a restart \n"//&
418  "file is read.", default=.false., do_not_log=just_read)
419  if (new_sim) then
420  if (convert .and. .not. gv%Boussinesq) then
421  ! Convert h from m to kg m-2 then to thickness units (H)
422  call convert_thickness(h, g, gv, tv)
423  elseif (gv%Boussinesq) then
424  ! Convert h from m to thickness units (H)
425  do k = 1, nz; do j = js, je; do i = is, ie
426  h(i,j,k) = h(i,j,k)*gv%m_to_H
427  enddo ; enddo ; enddo
428  else
429  do k = 1, nz; do j = js, je; do i = is, ie
430  h(i,j,k) = h(i,j,k)*gv%kg_m2_to_H
431  enddo ; enddo ; enddo
432  endif
433  endif
434 
435 ! Remove the mass that would be displaced by an ice shelf or inverse barometer.
436  call get_param(pf, mdl, "DEPRESS_INITIAL_SURFACE", depress_sfc, &
437  "If true, depress the initial surface to avoid huge \n"//&
438  "tsunamis when a large surface pressure is applied.", &
439  default=.false., do_not_log=just_read)
440  call get_param(pf, mdl, "TRIM_IC_FOR_P_SURF", trim_ic_for_p_surf, &
441  "If true, cuts way the top of the column for initial conditions\n"//&
442  "at the depth where the hydrostatic presure matches the imposed\n"//&
443  "surface pressure which is read from file.", default=.false., &
444  do_not_log=just_read)
445  if (depress_sfc .and. trim_ic_for_p_surf) call mom_error(fatal, "MOM_initialize_state: "//&
446  "DEPRESS_INITIAL_SURFACE and TRIM_IC_FOR_P_SURF are exclusive and cannot both be True")
447  if (depress_sfc) call depress_surface(h, g, gv, pf, tv, just_read_params=just_read)
448  if (trim_ic_for_p_surf) call trim_for_ice(pf, g, gv, ale_csp, tv, h, just_read_params=just_read)
449 
450  ! Perhaps we want to run the regridding coordinate generator for multiple
451  ! iterations here so the initial grid is consistent with the coordinate
452  if (useale) then
453  call get_param(pf, mdl, "REGRID_ACCELERATE_INIT", regrid_accelerate, &
454  "If true, runs REGRID_ACCELERATE_ITERATIONS iterations of the regridding\n"//&
455  "algorithm to push the initial grid to be consistent with the initial\n"//&
456  "condition. Useful only for state-based and iterative coordinates.", &
457  default=.false., do_not_log=just_read)
458  if (regrid_accelerate) then
459  call get_param(pf, mdl, "REGRID_ACCELERATE_ITERATIONS", regrid_iterations, &
460  "The number of regridding iterations to perform to generate\n"//&
461  "an initial grid that is consistent with the initial conditions.", &
462  default=1, do_not_log=just_read)
463 
464  if (new_sim) &
465  call ale_regrid_accelerated(ale_csp, g, gv, h, tv, regrid_iterations, h, u, v)
466  endif
467  endif
468  ! This is the end of the block of code that might have initialized fields
469  ! internally at the start of a new run.
470 
471  if (.not.new_sim) then ! This block restores the state from a restart file.
472  ! This line calls a subroutine that reads the initial conditions !
473  ! from a previously generated file. !
474  call restore_state(dirs%input_filename, dirs%restart_input_dir, time, &
475  g, restart_cs)
476  if (present(time_in)) time = time_in
477  endif
478 
479  if ( use_temperature ) then
480  call pass_var(tv%T, g%Domain, complete=.false.)
481  call pass_var(tv%S, g%Domain, complete=.false.)
482  endif
483  call pass_var(h, g%Domain)
484 
485  if (debug) then
486  call hchksum(h, "MOM_initialize_state: h ", g%HI, haloshift=1, scale=gv%H_to_m)
487  if ( use_temperature ) call hchksum(tv%T, "MOM_initialize_state: T ", g%HI, haloshift=1)
488  if ( use_temperature ) call hchksum(tv%S, "MOM_initialize_state: S ", g%HI, haloshift=1)
489  endif
490 
491  call get_param(pf, mdl, "SPONGE", use_sponge, &
492  "If true, sponges may be applied anywhere in the domain. \n"//&
493  "The exact location and properties of those sponges are \n"//&
494  "specified via SPONGE_CONFIG.", default=.false.)
495  if ( use_sponge ) then
496  call get_param(pf, mdl, "SPONGE_CONFIG", config, &
497  "A string that sets how the sponges are configured: \n"//&
498  " \t file - read sponge properties from the file \n"//&
499  " \t\t specified by (SPONGE_FILE).\n"//&
500  " \t ISOMIP - apply ale sponge in the ISOMIP case \n"//&
501  " \t DOME - use a slope and channel configuration for the \n"//&
502  " \t\t DOME sill-overflow test case. \n"//&
503  " \t BFB - Sponge at the southern boundary of the domain\n"//&
504  " \t\t for buoyancy-forced basin case.\n"//&
505  " \t USER - call a user modified routine.", default="file")
506  select case (trim(config))
507  case ("DOME"); call dome_initialize_sponges(g, gv, tv, pf, sponge_csp)
508  case ("DOME2D"); call dome2d_initialize_sponges(g, gv, tv, pf, useale, &
509  sponge_csp, ale_sponge_csp)
510  case ("ISOMIP"); call isomip_initialize_sponges(g, gv, tv, pf, useale, &
511  sponge_csp, ale_sponge_csp)
512  case ("USER"); call user_initialize_sponges(g, use_temperature, tv, &
513  pf, sponge_csp, h)
514  case ("BFB"); call bfb_initialize_sponges_southonly(g, use_temperature, tv, &
515  pf, sponge_csp, h)
516  case ("phillips"); call phillips_initialize_sponges(g, use_temperature, tv, &
517  pf, sponge_csp, h)
518  case ("dense"); call dense_water_initialize_sponges(g, gv, tv, pf, useale, &
519  sponge_csp, ale_sponge_csp)
520  case ("file"); call initialize_sponges_file(g, gv, use_temperature, tv, &
521  pf, sponge_csp)
522  case default ; call mom_error(fatal, "MOM_initialize_state: "//&
523  "Unrecognized sponge configuration "//trim(config))
524  end select
525  endif
526 
527  ! Reads OBC parameters not pertaining to the location of the boundaries
528  call open_boundary_init(g, pf, obc)
529 
530  ! This controls user code for setting open boundary data
531  if (associated(obc)) then
532  call get_param(pf, mdl, "OBC_USER_CONFIG", config, &
533  "A string that sets how the user code is invoked to set open\n"//&
534  " boundary data: \n"//&
535  " DOME - specified inflow on northern boundary\n"//&
536  " tidal_bay - Flather with tidal forcing on eastern boundary\n"//&
537  " supercritical - now only needed here for the allocations\n"//&
538  " Kelvin - barotropic Kelvin wave forcing on the western boundary\n"//&
539  " shelfwave - Flather with shelf wave forcing on western boundary\n"//&
540  " USER - user specified", default="none")
541  if (trim(config) == "DOME") then
542  call dome_set_obc_data(obc, tv, g, gv, pf, tracer_reg)
543  elseif (lowercase(trim(config)) == "supercritical") then
544  call supercritical_set_obc_data(obc, g, pf)
545  elseif (trim(config) == "tidal_bay") then
546  obc%update_OBC = .true.
547  elseif (trim(config) == "Kelvin") then
548  obc%update_OBC = .true.
549  elseif (trim(config) == "shelfwave") then
550  obc%update_OBC = .true.
551  elseif (trim(config) == "USER") then
552  call user_set_obc_data(obc, tv, g, pf, tracer_reg)
553  elseif (.not. trim(config) == "none") then
554  call mom_error(fatal, "The open boundary conditions specified by "//&
555  "OBC_USER_CONFIG = "//trim(config)//" have not been fully implemented.")
556  endif
557  if (open_boundary_query(obc, apply_open_obc=.true.)) then
558  call set_tracer_data(obc, tv, h, g, pf, tracer_reg)
559  endif
560  endif
561 ! if (open_boundary_query(OBC, apply_nudged_OBC=.true.)) then
562 ! call set_3D_OBC_data(OBC, tv, h, G, PF, tracer_Reg)
563 ! endif
564  ! Still need a way to specify the boundary values
565  if (debug.and.associated(obc)) then
566  call hchksum(g%mask2dT, 'MOM_initialize_state: mask2dT ', g%HI)
567  call uvchksum('MOM_initialize_state: mask2dC[uv]', g%mask2dCu, &
568  g%mask2dCv, g%HI)
569  call qchksum(g%mask2dBu, 'MOM_initialize_state: mask2dBu ', g%HI)
570  endif
571 
572  call calltree_leave('MOM_initialize_state()')
573 
574 end subroutine mom_initialize_state
575 ! -----------------------------------------------------------------------------
576 
577 ! -----------------------------------------------------------------------------
578 !> This subroutine reads the layer thicknesses or interface heights from a file.
579 subroutine initialize_thickness_from_file(h, G, GV, param_file, file_has_thickness, just_read_params)
580  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
581  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure
582  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
583  intent(out) :: h !< The thickness that is being initialized, in m.
584  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file
585  !! to parse for model parameter values.
586  logical, intent(in) :: file_has_thickness !< If true, this file contains layer
587  !! thicknesses; otherwise it contains
588  !! interface heights.
589  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
590  !! only read parameters without changing h.
591 
592 ! Arguments: h - The thickness that is being initialized.
593 ! (in) G - The ocean's grid structure.
594 ! (in) GV - The ocean's vertical grid structure.
595 ! (in) param_file - A structure indicating the open file to parse for
596 ! model parameter values.
597 ! (in) file_has_thickness - If true, this file contains thicknesses;
598 ! otherwise it contains interface heights.
599 
600 ! This subroutine reads the layer thicknesses from file.
601  real :: eta(szi_(g),szj_(g),szk_(g)+1)
602  integer :: inconsistent = 0
603  real :: dilate ! The amount by which each layer is dilated to agree
604  ! with the bottom depth and free surface height, nondim.
605  logical :: correct_thickness
606  logical :: just_read ! If true, just read parameters but set nothing. character(len=20) :: verticalCoordinate
607  character(len=40) :: mdl = "initialize_thickness_from_file" ! This subroutine's name.
608  character(len=200) :: filename, thickness_file, inputdir, mesg ! Strings for file/path
609  integer :: i, j, k, is, ie, js, je, nz
610 
611  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
612 
613  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
614 
615  if (.not.just_read) &
616  call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
617 
618  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".", do_not_log=just_read)
619  inputdir = slasher(inputdir)
620  call get_param(param_file, mdl, "THICKNESS_FILE", thickness_file, &
621  "The name of the thickness file.", &
622  fail_if_missing=.not.just_read, do_not_log=just_read)
623 
624  filename = trim(inputdir)//trim(thickness_file)
625  if (.not.just_read) call log_param(param_file, mdl, "INPUTDIR/THICKNESS_FILE", filename)
626 
627  if ((.not.just_read) .and. (.not.file_exists(filename, g%Domain))) call mom_error(fatal, &
628  " initialize_thickness_from_file: Unable to open "//trim(filename))
629 
630  if (file_has_thickness) then
631  if (just_read) return ! All run-time parameters have been read, so return.
632  call read_data(filename,"h",h(:,:,:),domain=g%Domain%mpp_domain)
633  else
634  call get_param(param_file, mdl, "ADJUST_THICKNESS", correct_thickness, &
635  "If true, all mass below the bottom removed if the \n"//&
636  "topography is shallower than the thickness input file \n"//&
637  "would indicate.", default=.false., do_not_log=just_read)
638  if (just_read) return ! All run-time parameters have been read, so return.
639 
640  call read_data(filename,"eta",eta(:,:,:),domain=g%Domain%mpp_domain)
641 
642  if (correct_thickness) then
643  call adjustetatofitbathymetry(g, gv, eta, h)
644  else
645  do k=nz,1,-1 ; do j=js,je ; do i=is,ie
646  if (eta(i,j,k) < (eta(i,j,k+1) + gv%Angstrom_z)) then
647  eta(i,j,k) = eta(i,j,k+1) + gv%Angstrom_z
648  h(i,j,k) = gv%Angstrom_z
649  else
650  h(i,j,k) = eta(i,j,k) - eta(i,j,k+1)
651  endif
652  enddo ; enddo ; enddo
653 
654  do j=js,je ; do i=is,ie
655  if (abs(eta(i,j,nz+1) + g%bathyT(i,j)) > 1.0) &
656  inconsistent = inconsistent + 1
657  enddo ; enddo
658  call sum_across_pes(inconsistent)
659 
660  if ((inconsistent > 0) .and. (is_root_pe())) then
661  write(mesg,'("Thickness initial conditions are inconsistent ",'// &
662  '"with topography in ",I8," places.")') inconsistent
663  call mom_error(warning, mesg)
664  endif
665  endif
666 
667  endif
668  call calltree_leave(trim(mdl)//'()')
669 end subroutine initialize_thickness_from_file
670 ! -----------------------------------------------------------------------------
671 
672 ! -----------------------------------------------------------------------------
673 !> Adjust interface heights to fit the bathymetry and diagnose layer thickness.
674 !! If the bottom most interface is below the topography then the bottom-most
675 !! layers are contracted to GV%Angstrom_z.
676 !! If the bottom most interface is above the topography then the entire column
677 !! is dilated (expanded) to fill the void.
678 !! @remark{There is a (hard-wired) "tolerance" parameter such that the
679 !! criteria for adjustment must equal or exceed 10cm.}
680 !! @param[in] G Grid type
681 !! @param[in,out] eta Interface heights
682 !! @param[out] h Layer thicknesses
683 subroutine adjustetatofitbathymetry(G, GV, eta, h)
684  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
685  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure
686  real, dimension(SZI_(G),SZJ_(G), SZK_(G)+1), intent(inout) :: eta
687  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(inout) :: h !< Layer thicknesses, in m
688  ! Local variables
689  integer :: i, j, k, is, ie, js, je, nz, contractions, dilations
690  real, parameter :: hTolerance = 0.1 !< Tolerance to exceed adjustment criteria (m)
691  real :: hTmp, eTmp, dilate
692  character(len=100) :: mesg
693 
694  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
695 
696  contractions = 0
697  do j=js,je ; do i=is,ie
698  if (-eta(i,j,nz+1) > g%bathyT(i,j) + htolerance) then
699  eta(i,j,nz+1) = -g%bathyT(i,j)
700  contractions = contractions + 1
701  endif
702  enddo ; enddo
703  call sum_across_pes(contractions)
704  if ((contractions > 0) .and. (is_root_pe())) then
705  write(mesg,'("Thickness initial conditions were contracted ",'// &
706  '"to fit topography in ",I8," places.")') contractions
707  call mom_error(warning, 'adjustEtaToFitBathymetry: '//mesg)
708  endif
709 
710  do k=nz,1,-1 ; do j=js,je ; do i=is,ie
711  ! Collapse layers to thinnest possible if the thickness less than
712  ! the thinnest possible (or negative).
713  if (eta(i,j,k) < (eta(i,j,k+1) + gv%Angstrom_z)) then
714  eta(i,j,k) = eta(i,j,k+1) + gv%Angstrom_z
715  h(i,j,k) = gv%Angstrom_z
716  else
717  h(i,j,k) = eta(i,j,k) - eta(i,j,k+1)
718  endif
719  enddo ; enddo ; enddo
720 
721  dilations = 0
722  do j=js,je ; do i=is,ie
723  ! The whole column is dilated to accommodate deeper topography than
724  ! the bathymetry would indicate.
725  ! This should be... if ((G%mask2dt(i,j)*(eta(i,j,1)-eta(i,j,nz+1)) > 0.0) .and. &
726  if (-eta(i,j,nz+1) < g%bathyT(i,j) - htolerance) then
727  dilations = dilations + 1
728  if (eta(i,j,1) <= eta(i,j,nz+1)) then
729  do k=1,nz ; h(i,j,k) = (eta(i,j,1)+g%bathyT(i,j)) / real(nz) ; enddo
730  else
731  dilate = (eta(i,j,1)+g%bathyT(i,j)) / (eta(i,j,1)-eta(i,j,nz+1))
732  do k=1,nz ; h(i,j,k) = h(i,j,k) * dilate ; enddo
733  endif
734  do k=nz, 2, -1; eta(i,j,k) = eta(i,j,k+1) + h(i,j,k); enddo
735  endif
736  enddo ; enddo
737  call sum_across_pes(dilations)
738  if ((dilations > 0) .and. (is_root_pe())) then
739  write(mesg,'("Thickness initial conditions were dilated ",'// &
740  '"to fit topography in ",I8," places.")') dilations
741  call mom_error(warning, 'adjustEtaToFitBathymetry: '//mesg)
742  endif
743 
744 end subroutine adjustetatofitbathymetry
745 ! -----------------------------------------------------------------------------
746 
747 ! -----------------------------------------------------------------------------
748 subroutine initialize_thickness_uniform(h, G, GV, param_file, just_read_params)
749  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
750  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
751  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
752  intent(out) :: h !< The thickness that is being initialized, in m.
753  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file
754  !! to parse for model parameter values.
755  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
756  !! only read parameters without changing h.
757 
758 ! Arguments: h - The thickness that is being initialized.
759 ! (in) G - The ocean's grid structure.
760 ! (in) GV - The ocean's vertical grid structure.
761 ! (in) param_file - A structure indicating the open file to parse for
762 ! model parameter values.
763 
764 ! This subroutine initializes the layer thicknesses to be uniform.
765  character(len=40) :: mdl = "initialize_thickness_uniform" ! This subroutine's name.
766  real :: e0(szk_(g)+1) ! The resting interface heights, in m, usually !
767  ! negative because it is positive upward. !
768  real :: eta1D(szk_(g)+1)! Interface height relative to the sea surface !
769  ! positive upward, in m. !
770  logical :: just_read ! If true, just read parameters but set nothing. character(len=20) :: verticalCoordinate
771  integer :: i, j, k, is, ie, js, je, nz
772 
773  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
774 
775  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
776 
777  if (just_read) return ! This subroutine has no run-time parameters.
778 
779  call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
780 
781  if (g%max_depth<=0.) call mom_error(fatal,"initialize_thickness_uniform: "// &
782  "MAXIMUM_DEPTH has a non-sensical value! Was it set?")
783 
784  do k=1,nz
785  e0(k) = -g%max_depth * real(k-1) / real(nz)
786  enddo
787 
788  do j=js,je ; do i=is,ie
789 ! This sets the initial thickness (in m) of the layers. The !
790 ! thicknesses are set to insure that: 1. each layer is at least an !
791 ! Angstrom thick, and 2. the interfaces are where they should be !
792 ! based on the resting depths and interface height perturbations, !
793 ! as long at this doesn't interfere with 1. !
794  eta1d(nz+1) = -1.0*g%bathyT(i,j)
795  do k=nz,1,-1
796  eta1d(k) = e0(k)
797  if (eta1d(k) < (eta1d(k+1) + gv%Angstrom_z)) then
798  eta1d(k) = eta1d(k+1) + gv%Angstrom_z
799  h(i,j,k) = gv%Angstrom_z
800  else
801  h(i,j,k) = eta1d(k) - eta1d(k+1)
802  endif
803  enddo
804  enddo ; enddo
805 
806  call calltree_leave(trim(mdl)//'()')
807 end subroutine initialize_thickness_uniform
808 ! -----------------------------------------------------------------------------
809 
810 ! -----------------------------------------------------------------------------
812 ! search density space for location of layers
813  call mom_error(fatal," MOM_state_initialization.F90, initialize_thickness_search: NOT IMPLEMENTED")
814 end subroutine initialize_thickness_search
815 ! -----------------------------------------------------------------------------
816 
817 subroutine convert_thickness(h, G, GV, tv)
818  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
819  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure
820  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), &
821  intent(inout) :: h !< Layer thicknesses, being
822  !! converted from m to H (m or kg
823  !! m-2)
824  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various
825  !! thermodynamic variables
826 ! Arguments: h - The thickness that is being initialized.
827 ! (in) G - The ocean's grid structure.
828 ! (in) GV - The ocean's vertical grid structure.
829  real, dimension(SZI_(G),SZJ_(G)) :: &
830  p_top, p_bot
831  real :: dz_geo(szi_(g),szj_(g)) ! The change in geopotential height
832  ! across a layer, in m2 s-2.
833  real :: rho(szi_(g))
834  real :: I_gEarth
835  logical :: Boussinesq
836  integer :: i, j, k, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz
837  integer :: itt, max_itt
838 
839  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
840  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
841  max_itt = 10
842  boussinesq = gv%Boussinesq
843  i_gearth = 1.0 / gv%g_Earth
844 
845  if (boussinesq) then
846  call mom_error(fatal,"Not yet converting thickness with Boussinesq approx.")
847  else
848  if (associated(tv%eqn_of_state)) then
849  do j=jsq,jeq+1 ; do i=isq,ieq+1
850  p_bot(i,j) = 0.0 ; p_top(i,j) = 0.0
851  enddo ; enddo
852  do k=1,nz
853  do j=js,je
854  do i=is,ie ; p_top(i,j) = p_bot(i,j) ; enddo
855  call calculate_density(tv%T(:,j,k), tv%S(:,j,k), p_top(:,j), rho, &
856  is, ie-is+1, tv%eqn_of_state)
857  do i=is,ie
858  p_bot(i,j) = p_top(i,j) + gv%g_Earth * h(i,j,k) * rho(i)
859  enddo
860  enddo
861 
862  do itt=1,max_itt
863  call int_specific_vol_dp(tv%T(:,:,k), tv%S(:,:,k), p_top, p_bot, &
864  0.0, g%HI, tv%eqn_of_state, dz_geo)
865  if (itt < max_itt) then ; do j=js,je
866  call calculate_density(tv%T(:,j,k), tv%S(:,j,k), p_bot(:,j), rho, &
867  is, ie-is+1, tv%eqn_of_state)
868  ! Use Newton's method to correct the bottom value.
869  ! The hydrostatic equation is linear to such a
870  ! high degree that no bounds-checking is needed.
871  do i=is,ie
872  p_bot(i,j) = p_bot(i,j) + rho(i) * (gv%g_Earth*h(i,j,k) - dz_geo(i,j))
873  enddo
874  enddo ; endif
875  enddo
876 
877  do j=js,je ; do i=is,ie
878  h(i,j,k) = (p_bot(i,j) - p_top(i,j)) * gv%kg_m2_to_H * i_gearth
879  enddo ; enddo
880  enddo
881  else
882  do k=1,nz ; do j=js,je ; do i=is,ie
883  h(i,j,k) = h(i,j,k) * gv%Rlay(k) * gv%kg_m2_to_H
884  enddo ; enddo ; enddo
885  endif
886  endif
887 
888 end subroutine convert_thickness
889 
890 subroutine depress_surface(h, G, GV, param_file, tv, just_read_params)
891  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
892  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure
893  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), &
894  intent(inout) :: h !< Layer thicknesses, in H (usually m or kg m-2)
895  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
896  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various thermodynamic variables
897  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
898  !! only read parameters without changing h.
899 ! Arguments: h - The thickness that is being initialized.
900 ! (in) G - The ocean's grid structure.
901 ! (in) GV - The ocean's vertical grid structure.
902 ! (in) param_file - A structure indicating the open file to parse for
903 ! model parameter values.
904 
905  real, dimension(SZI_(G),SZJ_(G)) :: &
906  eta_sfc ! The free surface height that the model should use, in m.
907  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1) :: &
908  eta ! The free surface height that the model should use, in m.
909  real :: dilate ! A ratio by which layers are dilated, nondim.
910  real :: scale_factor ! A scaling factor for the eta_sfc values that are read
911  ! in, which can be used to change units, for example.
912  character(len=40) :: mdl = "depress_surface" ! This subroutine's name.
913  character(len=200) :: inputdir, eta_srf_file ! Strings for file/path
914  character(len=200) :: filename, eta_srf_var ! Strings for file/path
915  logical :: just_read ! If true, just read parameters but set nothing.
916  integer :: i, j, k, is, ie, js, je, nz
917  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
918 
919  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
920 
921  ! Read the surface height (or pressure) from a file.
922 
923  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
924  inputdir = slasher(inputdir)
925  call get_param(param_file, mdl, "SURFACE_HEIGHT_IC_FILE", eta_srf_file,&
926  "The initial condition file for the surface height.", &
927  fail_if_missing=.not.just_read, do_not_log=just_read)
928  call get_param(param_file, mdl, "SURFACE_HEIGHT_IC_VAR", eta_srf_var, &
929  "The initial condition variable for the surface height.",&
930  default="SSH", do_not_log=just_read)
931  filename = trim(inputdir)//trim(eta_srf_file)
932  if (.not.just_read) &
933  call log_param(param_file, mdl, "INPUTDIR/SURFACE_HEIGHT_IC_FILE", filename)
934 
935  call get_param(param_file, mdl, "SURFACE_HEIGHT_IC_SCALE", scale_factor, &
936  "A scaling factor to convert SURFACE_HEIGHT_IC_VAR into \n"//&
937  "units of m", units="variable", default=1.0, do_not_log=just_read)
938 
939  if (just_read) return ! All run-time parameters have been read, so return.
940 
941  call read_data(filename,eta_srf_var,eta_sfc,domain=g%Domain%mpp_domain)
942 
943  if (scale_factor /= 1.0) then ; do j=js,je ; do i=is,ie
944  eta_sfc(i,j) = eta_sfc(i,j) * scale_factor
945  enddo ; enddo ; endif
946 
947  ! Convert thicknesses to interface heights.
948  call find_eta(h, tv, gv%g_Earth, g, gv, eta)
949 
950  do j=js,je ; do i=is,ie ; if (g%mask2dT(i,j) > 0.0) then
951 ! if (eta_sfc(i,j) < eta(i,j,nz+1)) then
952  ! Issue a warning?
953 ! endif
954  if (eta_sfc(i,j) > eta(i,j,1)) then
955  ! Dilate the water column to agree, but only up to 10-fold.
956  if (eta_sfc(i,j) - eta(i,j,nz+1) > 10.0*(eta(i,j,1) - eta(i,j,nz+1))) then
957  dilate = 10.0
958  call mom_error(warning, "Free surface height dilation attempted "//&
959  "to exceed 10-fold.", all_print=.true.)
960  else
961  dilate = (eta_sfc(i,j) - eta(i,j,nz+1)) / (eta(i,j,1) - eta(i,j,nz+1))
962  endif
963  do k=1,nz ; h(i,j,k) = h(i,j,k) * dilate ; enddo
964  elseif (eta(i,j,1) > eta_sfc(i,j)) then
965  ! Remove any mass that is above the target free surface.
966  do k=1,nz
967  if (eta(i,j,k) <= eta_sfc(i,j)) exit
968  if (eta(i,j,k+1) >= eta_sfc(i,j)) then
969  h(i,j,k) = gv%Angstrom
970  else
971  h(i,j,k) = max(gv%Angstrom, h(i,j,k) * &
972  (eta_sfc(i,j) - eta(i,j,k+1)) / (eta(i,j,k) - eta(i,j,k+1)) )
973  endif
974  enddo
975  endif
976  endif ; enddo ; enddo
977 
978 end subroutine depress_surface
979 
980 !> Adjust the layer thicknesses by cutting away the top of each model column at the depth
981 !! where the hydrostatic pressure matches an imposed surface pressure read from file.
982 subroutine trim_for_ice(PF, G, GV, ALE_CSp, tv, h, just_read_params)
983  type(param_file_type), intent(in) :: PF !< Parameter file structure
984  type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
985  type(verticalgrid_type), intent(in) :: GV !< Vertical grid structure
986  type(ale_cs), pointer :: ALE_CSp !< ALE control structure
987  type(thermo_var_ptrs), intent(inout) :: tv !< Thermodynamics structure
988  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
989  intent(inout) :: h !< Layer thickness (H units, m or Pa)
990  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
991  !! only read parameters without changing h.
992 
993  ! Local variables
994  character(len=200) :: mdl = "trim_for_ice"
995  real, dimension(SZI_(G),SZJ_(G)) :: p_surf ! Imposed pressure on ocean at surface (Pa)
996  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: S_t, S_b, T_t, T_b ! Top and bottom edge values for reconstructions
997  ! of salinity and temperature within each layer.
998  character(len=200) :: inputdir, filename, p_surf_file, p_surf_var ! Strings for file/path
999  real :: scale_factor, min_thickness
1000  integer :: i, j, k
1001  logical :: just_read ! If true, just read parameters but set nothing.
1002  logical :: use_remapping
1003  type(remapping_cs), pointer :: remap_CS => null()
1004 
1005  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1006 
1007  call get_param(pf, mdl, "SURFACE_PRESSURE_FILE", p_surf_file, &
1008  "The initial condition file for the surface height.", &
1009  fail_if_missing=.not.just_read, do_not_log=just_read)
1010  call get_param(pf, mdl, "SURFACE_PRESSURE_VAR", p_surf_var, &
1011  "The initial condition variable for the surface height.", &
1012  units="kg m-2", default="", do_not_log=just_read)
1013  call get_param(pf, mdl, "INPUTDIR", inputdir, default=".", do_not_log=.true.)
1014  filename = trim(slasher(inputdir))//trim(p_surf_file)
1015  if (.not.just_read) call log_param(pf, mdl, "!INPUTDIR/SURFACE_HEIGHT_IC_FILE", filename)
1016 
1017  call get_param(pf, mdl, "SURFACE_PRESSURE_SCALE", scale_factor, &
1018  "A scaling factor to convert SURFACE_PRESSURE_VAR from\n"//&
1019  "file SURFACE_PRESSURE_FILE into a surface pressure.", &
1020  units="file dependent", default=1., do_not_log=just_read)
1021  call get_param(pf, mdl, "MIN_THICKNESS", min_thickness, 'Minimum layer thickness', &
1022  units='m', default=1.e-3, do_not_log=just_read)
1023  call get_param(pf, mdl, "TRIMMING_USES_REMAPPING", use_remapping, &
1024  'When trimming the column, also remap T and S.', &
1025  default=.false., do_not_log=just_read)
1026 
1027  if (just_read) return ! All run-time parameters have been read, so return.
1028 
1029  call read_data(filename, p_surf_var, p_surf, domain=g%Domain%mpp_domain)
1030  if (scale_factor /= 1.) p_surf(:,:) = scale_factor * p_surf(:,:)
1031 
1032  if (use_remapping) then
1033  allocate(remap_cs)
1034  call initialize_remapping(remap_cs, 'PLM', boundary_extrapolation=.true.)
1035  endif
1036 
1037  ! Find edge values of T and S used in reconstructions
1038  if ( associated(ale_csp) ) then ! This should only be associated if we are in ALE mode
1039 ! if ( PRScheme == PRESSURE_RECONSTRUCTION_PLM ) then
1040  call pressure_gradient_plm(ale_csp, s_t, s_b, t_t, t_b, g, gv, tv, h)
1041 ! elseif ( PRScheme == PRESSURE_RECONSTRUCTION_PPM ) then
1042 ! call pressure_gradient_ppm(ALE_CSp, S_t, S_b, T_t, T_b, G, GV, tv, h)
1043 ! endif
1044  else
1045 ! call MOM_error(FATAL, "trim_for_ice: Does not work without ALE mode")
1046  do k=1,g%ke ; do j=g%jsc,g%jec ; do i=g%isc,g%iec
1047  t_t(i,j,k) = tv%T(i,j,k) ; t_b(i,j,k) = tv%T(i,j,k)
1048  s_t(i,j,k) = tv%S(i,j,k) ; s_b(i,j,k) = tv%S(i,j,k)
1049  enddo ; enddo ; enddo
1050  endif
1051 
1052  do j=g%jsc,g%jec ; do i=g%isc,g%iec
1053  call cut_off_column_top(gv%ke, tv, gv%Rho0, gv%g_Earth, g%bathyT(i,j), min_thickness, &
1054  tv%T(i,j,:), t_t(i,j,:), t_b(i,j,:), tv%S(i,j,:), s_t(i,j,:), s_b(i,j,:), &
1055  p_surf(i,j), h(i,j,:), remap_cs)
1056  enddo ; enddo
1057 
1058 end subroutine trim_for_ice
1059 
1060 !> Adjust the layer thicknesses by cutting away the top at the depth where the hydrostatic
1061 !! pressure matches p_surf
1062 subroutine cut_off_column_top(nk, tv, Rho0, G_earth, depth, min_thickness, &
1063  T, T_t, T_b, S, S_t, S_b, p_surf, h, remap_CS)
1064  integer, intent(in) :: nk !< Number of layers
1065  type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamics structure
1066  real, intent(in) :: Rho0 !< Reference density (kg/m3)
1067  real, intent(in) :: G_earth !< Gravitational acceleration (m/s2)
1068  real, intent(in) :: depth !< Depth of ocean column (m)
1069  real, intent(in) :: min_thickness !< Smallest thickness allowed (m)
1070  real, dimension(nk), intent(inout) :: T !< Layer mean temperature
1071  real, dimension(nk), intent(in) :: T_t !< Temperature at top of layer
1072  real, dimension(nk), intent(in) :: T_b !< Temperature at bottom of layer
1073  real, dimension(nk), intent(inout) :: S !< Layer mean salinity
1074  real, dimension(nk), intent(in) :: S_t !< Salinity at top of layer
1075  real, dimension(nk), intent(in) :: S_b !< Salinity at bottom of layer
1076  real, intent(in) :: p_surf !< Imposed pressure on ocean at surface (Pa)
1077  real, dimension(nk), intent(inout) :: h !< Layer thickness (H units, m or Pa)
1078  type(remapping_cs), pointer :: remap_CS ! Remapping structure for remapping T and S, if associated
1079  ! Local variables
1080  real, dimension(nk+1) :: e ! Top and bottom edge values for reconstructions
1081  real, dimension(nk) :: h0, S0, T0, h1, S1, T1
1082  real :: P_t, P_b, z_out, e_top
1083  integer :: k
1084 
1085  ! Calculate original interface positions
1086  e(nk+1) = -depth
1087  do k=nk,1,-1
1088  e(k) = e(k+1) + h(k)
1089  h0(k) = h(nk+1-k) ! Keep a copy to use in remapping
1090  enddo
1091 
1092  p_t = 0.
1093  e_top = e(1)
1094  do k=1,nk
1095  call find_depth_of_pressure_in_cell(t_t(k), t_b(k), s_t(k), s_b(k), e(k), e(k+1), &
1096  p_t, p_surf, rho0, g_earth, tv%eqn_of_state, p_b, z_out)
1097  if (z_out>=e(k)) then
1098  ! Imposed pressure was less that pressure at top of cell
1099  exit
1100  elseif (z_out<=e(k+1)) then
1101  ! Imposed pressure was greater than pressure at bottom of cell
1102  e_top = e(k+1)
1103  else
1104  ! Imposed pressure was fell between pressures at top and bottom of cell
1105  e_top = z_out
1106  exit
1107  endif
1108  p_t = p_b
1109  enddo
1110  if (e_top<e(1)) then
1111  ! Clip layers from the top down, if at all
1112  do k=1,nk
1113  if (e(k)>e_top) then
1114  ! Original e(K) is too high
1115  e(k) = e_top
1116  e_top = e_top - min_thickness ! Next interface must be at least this deep
1117  endif
1118  ! This layer needs trimming
1119  h(k) = max( min_thickness, e(k) - e(k+1) )
1120  if (e(k)<e_top) exit ! No need to go further
1121  enddo
1122  endif
1123 
1124  ! Now we need to remap but remapping assumes the surface is at the
1125  ! same place in the two columns so we turn the column upside down.
1126  if (associated(remap_cs)) then
1127  do k=1,nk
1128  s0(k) = s(nk+1-k)
1129  t0(k) = t(nk+1-k)
1130  h1(k) = h(nk+1-k)
1131  enddo
1132  call remapping_core_h(remap_cs, nk, h0, t0, nk, h1, t1)
1133  call remapping_core_h(remap_cs, nk, h0, s0, nk, h1, s1)
1134  do k=1,nk
1135  s(k) = s1(nk+1-k)
1136  t(k) = t1(nk+1-k)
1137  enddo
1138  endif
1139 
1140 end subroutine cut_off_column_top
1141 
1142 ! -----------------------------------------------------------------------------
1143 subroutine initialize_velocity_from_file(u, v, G, param_file, just_read_params)
1144  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1145  real, dimension(SZIB_(G),SZJ_(G), SZK_(G)), intent(out) :: u !< The zonal velocity that is being initialized, in m s-1
1146  real, dimension(SZI_(G),SZJB_(G), SZK_(G)), intent(out) :: v !< The meridional velocity that is being initialized, in m s-1
1147  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file to
1148  !! parse for modelparameter values.
1149  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1150  !! only read parameters without changing h.
1151 ! Arguments: u - The zonal velocity that is being initialized.
1152 ! (out) v - The meridional velocity that is being initialized.
1153 ! (in) G - The ocean's grid structure.
1154 ! (in) param_file - parameter file type
1155 
1156 ! This subroutine reads the initial velocity components from file
1157  character(len=40) :: mdl = "initialize_velocity_from_file" ! This subroutine's name.
1158  character(len=200) :: filename,velocity_file,inputdir ! Strings for file/path
1159  logical :: just_read ! If true, just read parameters but set nothing.
1160 
1161  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1162 
1163  if (.not.just_read) call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
1164 
1165  call get_param(param_file, mdl, "VELOCITY_FILE", velocity_file, &
1166  "The name of the velocity initial condition file.", &
1167  fail_if_missing=.not.just_read, do_not_log=just_read)
1168  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
1169  inputdir = slasher(inputdir)
1170 
1171  if (just_read) return ! All run-time parameters have been read, so return.
1172 
1173  filename = trim(inputdir)//trim(velocity_file)
1174  call log_param(param_file, mdl, "INPUTDIR/VELOCITY_FILE", filename)
1175 
1176  if (.not.file_exists(filename, g%Domain)) call mom_error(fatal, &
1177  " initialize_velocity_from_file: Unable to open "//trim(filename))
1178 
1179  ! Read the velocities from a netcdf file.
1180  call read_data(filename,"u",u(:,:,:),domain=g%Domain%mpp_domain,position=east_face)
1181  call read_data(filename,"v",v(:,:,:),domain=g%Domain%mpp_domain,position=north_face)
1182 
1183  call calltree_leave(trim(mdl)//'()')
1184 end subroutine initialize_velocity_from_file
1185 ! -----------------------------------------------------------------------------
1186 
1187 ! -----------------------------------------------------------------------------
1188 subroutine initialize_velocity_zero(u, v, G, param_file, just_read_params)
1189  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1190  real, dimension(SZIB_(G),SZJ_(G), SZK_(G)), intent(out) :: u !< The zonal velocity that is being initialized, in m s-1
1191  real, dimension(SZI_(G),SZJB_(G), SZK_(G)), intent(out) :: v !< The meridional velocity that is being initialized, in m s-1
1192  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file to
1193  !! parse for modelparameter values.
1194  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1195  !! only read parameters without changing h.
1196 ! Arguments: u - The zonal velocity that is being initialized.
1197 ! (out) v - The meridional velocity that is being initialized.
1198 ! (in) G - The ocean's grid structure.
1199 ! (in) param_file - parameter file type
1200 
1201 ! This subroutine sets the initial velocity components to zero
1202  character(len=200) :: mdl = "initialize_velocity_zero" ! This subroutine's name.
1203  logical :: just_read ! If true, just read parameters but set nothing.
1204  integer :: i, j, k, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz
1205  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
1206  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
1207 
1208  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1209 
1210  if (.not.just_read) call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
1211 
1212  if (just_read) return ! All run-time parameters have been read, so return.
1213 
1214  do k=1,nz ; do j=js,je ; do i=isq,ieq
1215  u(i,j,k) = 0.0
1216  enddo ; enddo ; enddo
1217  do k=1,nz ; do j=jsq,jeq ; do i=is,ie
1218  v(i,j,k) = 0.0
1219  enddo ; enddo ; enddo
1220 
1221  call calltree_leave(trim(mdl)//'()')
1222 end subroutine initialize_velocity_zero
1223 ! -----------------------------------------------------------------------------
1224 
1225 ! -----------------------------------------------------------------------------
1226 subroutine initialize_velocity_uniform(u, v, G, param_file, just_read_params)
1227  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1228  real, dimension(SZIB_(G),SZJ_(G), SZK_(G)), intent(out) :: u !< The zonal velocity that is being initialized, in m s-1
1229  real, dimension(SZI_(G),SZJB_(G), SZK_(G)), intent(out) :: v !< The meridional velocity that is being initialized, in m s-1
1230  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file to
1231  !! parse for modelparameter values.
1232  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1233  !! only read parameters without changing h.
1234 ! Arguments: u - The zonal velocity that is being initialized.
1235 ! (out) v - The meridional velocity that is being initialized.
1236 ! (in) G - The ocean's grid structure.
1237 ! (in) param_file - parameter file type
1238 
1239 ! This subroutine sets the initial velocity components to uniform
1240  integer :: i, j, k, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz
1241  real :: initial_u_const, initial_v_const
1242  logical :: just_read ! If true, just read parameters but set nothing.
1243  character(len=200) :: mdl = "initialize_velocity_uniform" ! This subroutine's name.
1244  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
1245  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
1246 
1247  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1248 
1249  call get_param(param_file, mdl, "INITIAL_U_CONST", initial_u_const, &
1250  "A initial uniform value for the zonal flow.", &
1251  units="m s-1", fail_if_missing=.not.just_read, do_not_log=just_read)
1252  call get_param(param_file, mdl, "INITIAL_V_CONST", initial_v_const, &
1253  "A initial uniform value for the meridional flow.", &
1254  units="m s-1", fail_if_missing=.not.just_read, do_not_log=just_read)
1255 
1256  if (just_read) return ! All run-time parameters have been read, so return.
1257 
1258  do k=1,nz ; do j=js,je ; do i=isq,ieq
1259  u(i,j,k) = initial_u_const
1260  enddo ; enddo ; enddo
1261  do k=1,nz ; do j=jsq,jeq ; do i=is,ie
1262  v(i,j,k) = initial_v_const
1263  enddo ; enddo ; enddo
1264 
1265 end subroutine initialize_velocity_uniform
1266 ! -----------------------------------------------------------------------------
1267 
1268 ! -----------------------------------------------------------------------------
1269 subroutine initialize_velocity_circular(u, v, G, param_file, just_read_params)
1270  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1271  real, dimension(SZIB_(G),SZJ_(G), SZK_(G)), intent(out) :: u !< The zonal velocity that is being initialized, in m s-1
1272  real, dimension(SZI_(G),SZJB_(G), SZK_(G)), intent(out) :: v !< The meridional velocity that is being initialized, in m s-1
1273  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file to
1274  !! parse for modelparameter values.
1275  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1276  !! only read parameters without changing h.
1277 ! Arguments: u - The zonal velocity that is being initialized.
1278 ! (out) v - The meridional velocity that is being initialized.
1279 ! (in) G - The ocean's grid structure.
1280 ! (in) param_file - parameter file type
1281 
1282 ! This subroutine sets the initial velocity components to be circular with
1283 ! no flow at edges of domain and center.
1284  character(len=200) :: mdl = "initialize_velocity_circular"
1285  real :: circular_max_u
1286  real :: dpi, psi1, psi2
1287  logical :: just_read ! If true, just read parameters but set nothing.
1288  integer :: i, j, k, is, ie, js, je, Isq, Ieq, Jsq, Jeq, nz
1289  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
1290  isq = g%IscB ; ieq = g%IecB ; jsq = g%JscB ; jeq = g%JecB
1291 
1292  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1293 
1294  call get_param(param_file, mdl, "CIRCULAR_MAX_U", circular_max_u, &
1295  "The amplitude of zonal flow from which to scale the\n"// &
1296  "circular stream function (m/s).", &
1297  units="m s-1", default=0., do_not_log=just_read)
1298 
1299  if (just_read) return ! All run-time parameters have been read, so return.
1300 
1301  dpi=acos(0.0)*2.0 ! pi
1302 
1303  do k=1,nz ; do j=js,je ; do i=isq,ieq
1304  psi1 = my_psi(i,j)
1305  psi2 = my_psi(i,j-1)
1306  u(i,j,k) = (psi1-psi2)/g%dy_Cu(i,j)! *(circular_max_u*G%len_lon/(2.0*dpi))
1307  enddo ; enddo ; enddo
1308  do k=1,nz ; do j=jsq,jeq ; do i=is,ie
1309  psi1 = my_psi(i,j)
1310  psi2 = my_psi(i-1,j)
1311  v(i,j,k) = (psi2-psi1)/g%dx_Cv(i,j)! *(circular_max_u*G%len_lon/(2.0*dpi))
1312  enddo ; enddo ; enddo
1313 
1314  contains
1315 
1316  real function my_psi(ig,jg) ! in-line function
1317  integer :: ig, jg
1318  real :: x, y, r
1319  x = 2.0*(g%geoLonBu(ig,jg)-g%west_lon)/g%len_lon-1.0 ! -1<x<1
1320  y = 2.0*(g%geoLatBu(ig,jg)-g%south_lat)/g%len_lat-1.0 ! -1<y<1
1321  r = sqrt( x**2 + y**2 ) ! Circulat stream fn nis fn of radius only
1322  r = min(1.0,r) ! Flatten stream function in corners of box
1323  my_psi = 0.5*(1.0 - cos(dpi*r))
1324  my_psi = my_psi * (circular_max_u*g%len_lon*1e3/dpi) ! len_lon is in km
1325  end function my_psi
1326 
1327 end subroutine initialize_velocity_circular
1328 ! -----------------------------------------------------------------------------
1329 
1330 ! -----------------------------------------------------------------------------
1331 subroutine initialize_temp_salt_from_file(T, S, G, param_file, just_read_params)
1332  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1333  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: T !< The potential temperature that is being initialized.
1334  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: S !< The salinity that is being initialized.
1335  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
1336  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1337  !! only read parameters without changing h.
1338 ! This function puts the initial layer temperatures and salinities !
1339 ! into T(:,:,:) and S(:,:,:). !
1340 
1341 ! Arguments: T - The potential temperature that is being initialized.
1342 ! (out) S - The salinity that is being initialized.
1343 ! (in) from_file - .true. if the variables that are set here are to
1344 ! be read from a file; .false. to be set internally.
1345 ! (in) filename - The name of the file to read.
1346 ! (in) G - The ocean's grid structure.
1347 ! (in) param_file - A structure indicating the open file to parse for
1348 ! model parameter values.
1349  logical :: just_read ! If true, just read parameters but set nothing.
1350  character(len=200) :: filename, salt_filename ! Full paths to input files
1351  character(len=200) :: ts_file, salt_file, inputdir ! Strings for file/path
1352  character(len=40) :: mdl = "initialize_temp_salt_from_file"
1353  character(len=64) :: temp_var, salt_var ! Temperature and salinity names in files
1354 
1355  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1356 
1357  if (.not.just_read) call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
1358 
1359  call get_param(param_file, mdl, "TS_FILE", ts_file, &
1360  "The initial condition file for temperature.", &
1361  fail_if_missing=.not.just_read, do_not_log=just_read)
1362  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
1363  inputdir = slasher(inputdir)
1364 
1365  filename = trim(inputdir)//trim(ts_file)
1366  if (.not.just_read) call log_param(param_file, mdl, "INPUTDIR/TS_FILE", filename)
1367  call get_param(param_file, mdl, "TEMP_IC_VAR", temp_var, &
1368  "The initial condition variable for potential temperature.", &
1369  default="PTEMP", do_not_log=just_read)
1370  call get_param(param_file, mdl, "SALT_IC_VAR", salt_var, &
1371  "The initial condition variable for salinity.", &
1372  default="SALT", do_not_log=just_read)
1373  call get_param(param_file, mdl, "SALT_FILE", salt_file, &
1374  "The initial condition file for salinity.", &
1375  default=trim(ts_file), do_not_log=just_read)
1376 
1377  if (just_read) return ! All run-time parameters have been read, so return.
1378 
1379  if (.not.file_exists(filename, g%Domain)) call mom_error(fatal, &
1380  " initialize_temp_salt_from_file: Unable to open "//trim(filename))
1381 
1382 ! Read the temperatures and salinities from netcdf files. !
1383  call read_data(filename, temp_var, t(:,:,:), domain=g%Domain%mpp_domain)
1384 
1385  salt_filename = trim(inputdir)//trim(salt_file)
1386  if (.not.file_exists(salt_filename, g%Domain)) call mom_error(fatal, &
1387  " initialize_temp_salt_from_file: Unable to open "//trim(salt_filename))
1388 
1389  call read_data(salt_filename, salt_var, s(:,:,:), domain=g%Domain%mpp_domain)
1390 
1391  call calltree_leave(trim(mdl)//'()')
1392 end subroutine initialize_temp_salt_from_file
1393 ! -----------------------------------------------------------------------------
1394 
1395 ! -----------------------------------------------------------------------------
1396 subroutine initialize_temp_salt_from_profile(T, S, G, param_file, just_read_params)
1397  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1398  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: T, S
1399  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
1400  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1401  !! only read parameters without changing h.
1402 ! This function puts the initial layer temperatures and salinities !
1403 ! into T(:,:,:) and S(:,:,:). !
1404 
1405 ! Arguments: T - The potential temperature that is being initialized.
1406 ! (out) S - The salinity that is being initialized.
1407 ! (in) from_file - .true. if the variables that are set here are to
1408 ! be read from a file; .false. to be set internally.
1409 ! (in) filename - The name of the file to read.
1410 ! (in) G - The ocean's grid structure.
1411 ! (in) param_file - A structure indicating the open file to parse for
1412 ! model parameter values.
1413  real, dimension(SZK_(G)) :: T0, S0
1414  integer :: i, j, k
1415  logical :: just_read ! If true, just read parameters but set nothing.
1416  character(len=200) :: filename, ts_file, inputdir ! Strings for file/path
1417  character(len=40) :: mdl = "initialize_temp_salt_from_profile"
1418 
1419  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1420 
1421  if (.not.just_read) call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
1422 
1423  call get_param(param_file, mdl, "TS_FILE", ts_file, &
1424  "The file with the reference profiles for temperature \n"//&
1425  "and salinity.", fail_if_missing=.not.just_read, do_not_log=just_read)
1426 
1427  if (just_read) return ! All run-time parameters have been read, so return.
1428 
1429  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
1430  inputdir = slasher(inputdir)
1431  filename = trim(inputdir)//trim(ts_file)
1432  call log_param(param_file, mdl, "INPUTDIR/TS_FILE", filename)
1433  if (.not.file_exists(filename)) call mom_error(fatal, &
1434  " initialize_temp_salt_from_profile: Unable to open "//trim(filename))
1435 
1436 ! Read the temperatures and salinities from a netcdf file. !
1437  call read_data(filename,"PTEMP",t0(:),domain=g%Domain%mpp_domain)
1438  call read_data(filename,"SALT", s0(:),domain=g%Domain%mpp_domain)
1439 
1440  do k=1,g%ke ; do j=g%jsc,g%jec ; do i=g%isc,g%iec
1441  t(i,j,k) = t0(k) ; s(i,j,k) = s0(k)
1442  enddo ; enddo ; enddo
1443 
1444  call calltree_leave(trim(mdl)//'()')
1445 end subroutine initialize_temp_salt_from_profile
1446 ! -----------------------------------------------------------------------------
1447 
1448 
1449 ! -----------------------------------------------------------------------------
1450 subroutine initialize_temp_salt_fit(T, S, G, GV, param_file, eqn_of_state, P_Ref, just_read_params)
1451  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1452  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
1453  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), &
1454  intent(out) :: T !< The potential temperature that is being
1455  !! initialized.
1456  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), &
1457  intent(out) :: S !< The salinity that is being initialized.
1458  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time
1459  !! parameters.
1460  type(eos_type), pointer :: eqn_of_state !< Integer that selects the equatio of state.
1461  real, intent(in) :: P_Ref !< The coordinate-density reference pressure
1462  !! in Pa.
1463  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1464  !! only read parameters without changing h.
1465 ! This function puts the initial layer temperatures and salinities !
1466 ! into T(:,:,:) and S(:,:,:). !
1467 
1468 ! Arguments: T - The potential temperature that is being initialized.
1469 ! (out) S - The salinity that is being initialized.
1470 ! (in) G - The ocean's grid structure.
1471 ! (in) GV - The ocean's vertical grid structure.
1472 ! (in) param_file - A structure indicating the open file to parse for
1473 ! model parameter values.
1474 ! (in) eqn_of_state - integer that selects the equatio of state
1475 ! (in) P_Ref - The coordinate-density reference pressure in Pa.
1476  real :: T0(szk_(g)), S0(szk_(g))
1477  real :: T_Ref ! Reference Temperature
1478  real :: S_Ref ! Reference Salinity
1479  real :: pres(szk_(g)) ! An array of the reference pressure in Pa.
1480  real :: drho_dT(szk_(g)) ! Derivative of density with temperature in kg m-3 K-1. !
1481  real :: drho_dS(szk_(g)) ! Derivative of density with salinity in kg m-3 PSU-1. !
1482  real :: rho_guess(szk_(g)) ! Potential density at T0 & S0 in kg m-3.
1483  logical :: fit_salin ! If true, accept the prescribed temperature and fit the salinity.
1484  logical :: just_read ! If true, just read parameters but set nothing.
1485  character(len=40) :: mdl = "initialize_temp_salt_fit" ! This subroutine's name.
1486  integer :: i, j, k, itt, nz
1487  nz = g%ke
1488 
1489  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1490 
1491  if (.not.just_read) call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
1492 
1493  call get_param(param_file, mdl, "T_REF", t_ref, &
1494  "A reference temperature used in initialization.", &
1495  units="degC", fail_if_missing=.not.just_read, do_not_log=just_read)
1496  call get_param(param_file, mdl, "S_REF", s_ref, &
1497  "A reference salinity used in initialization.", units="PSU", &
1498  default=35.0, do_not_log=just_read)
1499  call get_param(param_file, mdl, "FIT_SALINITY", fit_salin, &
1500  "If true, accept the prescribed temperature and fit the \n"//&
1501  "salinity; otherwise take salinity and fit temperature.", &
1502  default=.false., do_not_log=just_read)
1503 
1504  if (just_read) return ! All run-time parameters have been read, so return.
1505 
1506  do k=1,nz
1507  pres(k) = p_ref ; s0(k) = s_ref
1508  t0(k) = t_ref
1509  enddo
1510 
1511  call calculate_density(t0(1),s0(1),pres(1),rho_guess(1),eqn_of_state)
1512  call calculate_density_derivs(t0,s0,pres,drho_dt,drho_ds,1,1,eqn_of_state)
1513 
1514  if (fit_salin) then
1515 ! A first guess of the layers' temperatures.
1516  do k=nz,1,-1
1517  s0(k) = max(0.0, s0(1) + (gv%Rlay(k) - rho_guess(1)) / drho_ds(1))
1518  enddo
1519 ! Refine the guesses for each layer.
1520  do itt=1,6
1521  call calculate_density(t0,s0,pres,rho_guess,1,nz,eqn_of_state)
1522  call calculate_density_derivs(t0,s0,pres,drho_dt,drho_ds,1,nz,eqn_of_state)
1523  do k=1,nz
1524  s0(k) = max(0.0, s0(k) + (gv%Rlay(k) - rho_guess(k)) / drho_ds(k))
1525  enddo
1526  enddo
1527  else
1528 ! A first guess of the layers' temperatures.
1529  do k=nz,1,-1
1530  t0(k) = t0(1) + (gv%Rlay(k) - rho_guess(1)) / drho_dt(1)
1531  enddo
1532  do itt=1,6
1533  call calculate_density(t0,s0,pres,rho_guess,1,nz,eqn_of_state)
1534  call calculate_density_derivs(t0,s0,pres,drho_dt,drho_ds,1,nz,eqn_of_state)
1535  do k=1,nz
1536  t0(k) = t0(k) + (gv%Rlay(k) - rho_guess(k)) / drho_dt(k)
1537  enddo
1538  enddo
1539  endif
1540 
1541  do k=1,nz ; do j=g%jsd,g%jed ; do i=g%isd,g%ied
1542  t(i,j,k) = t0(k) ; s(i,j,k) = s0(k)
1543  enddo ; enddo ; enddo
1544 
1545  call calltree_leave(trim(mdl)//'()')
1546 end subroutine initialize_temp_salt_fit
1547 ! -----------------------------------------------------------------------------
1548 
1549 ! -----------------------------------------------------------------------------
1550 subroutine initialize_temp_salt_linear(T, S, G, param_file, just_read_params)
1551  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1552  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: T, S
1553  type(param_file_type), intent(in) :: param_file !< A structure to parse for
1554  !! run-time parameters
1555  logical, optional, intent(in) :: just_read_params !< If present and true,
1556  !! this call will only read
1557  !! parameters without
1558  !! changing h.
1559 
1560  ! This subroutine initializes linear profiles for T and S according to
1561  ! reference surface layer salinity and temperature and a specified range.
1562  ! Note that the linear distribution is set up with respect to the layer
1563  ! number, not the physical position).
1564  integer :: k;
1565  real :: delta_S, delta_T
1566  real :: S_top, T_top ! Reference salinity and temerature within surface layer
1567  real :: S_range, T_range ! Range of salinities and temperatures over the vertical
1568  real :: delta
1569  logical :: just_read ! If true, just read parameters but set nothing.
1570  character(len=40) :: mdl = "initialize_temp_salt_linear" ! This subroutine's name.
1571 
1572  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1573 
1574  if (.not.just_read) call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
1575  call get_param(param_file, mdl, "T_TOP", t_top, &
1576  "Initial temperature of the top surface.", &
1577  units="degC", fail_if_missing=.not.just_read, do_not_log=just_read)
1578  call get_param(param_file, mdl, "T_RANGE", t_range, &
1579  "Initial temperature difference (top-bottom).", &
1580  units="degC", fail_if_missing=.not.just_read, do_not_log=just_read)
1581  call get_param(param_file, mdl, "S_TOP", s_top, &
1582  "Initial salinity of the top surface.", &
1583  units="PSU", fail_if_missing=.not.just_read, do_not_log=just_read)
1584  call get_param(param_file, mdl, "S_RANGE", s_range, &
1585  "Initial salinity difference (top-bottom).", &
1586  units="PSU", fail_if_missing=.not.just_read, do_not_log=just_read)
1587 
1588  if (just_read) return ! All run-time parameters have been read, so return.
1589 
1590 ! ! Prescribe salinity
1591 ! delta_S = S_range / ( G%ke - 1.0 );
1592 ! S(:,:,1) = S_top;
1593 ! do k = 2,G%ke
1594 ! S(:,:,k) = S(:,:,k-1) + delta_S;
1595 ! end do
1596  do k = 1,g%ke
1597  s(:,:,k) = s_top - s_range*((real(k)-0.5)/real(G%ke))
1598  t(:,:,k) = t_top - t_range*((real(k)-0.5)/real(G%ke))
1599  end do
1600 
1601 ! ! Prescribe temperature
1602 ! delta_T = T_range / ( G%ke - 1.0 );
1603 ! T(:,:,1) = T_top;
1604 ! do k = 2,G%ke
1605 ! T(:,:,k) = T(:,:,k-1) + delta_T;
1606 ! end do
1607 ! delta = 1;
1608 ! T(:,:,G%ke/2 - (delta-1):G%ke/2 + delta) = 1.0;
1609 
1610  call calltree_leave(trim(mdl)//'()')
1611 end subroutine initialize_temp_salt_linear
1612 ! -----------------------------------------------------------------------------
1613 
1614 ! -----------------------------------------------------------------------------
1615 !> This subroutine sets the inverse restoration time (Idamp), and
1616 !! the values towards which the interface heights and an arbitrary
1617 !! number of tracers should be restored within each sponge. The
1618 !!interface height is always subject to damping, and must always be
1619 !! the first registered field.
1620 subroutine initialize_sponges_file(G, GV, use_temperature, tv, param_file, CSp)
1621  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1622  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
1623  logical, intent(in) :: use_temperature
1624  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to various thermodynamic
1625  !! variables.
1626  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters.
1627  type(sponge_cs), pointer :: CSp !! A pointer that is set to point to the control
1628  !! structure for this module.
1629 ! This subroutine sets the inverse restoration time (Idamp), and !
1630 ! the values towards which the interface heights and an arbitrary !
1631 ! number of tracers should be restored within each sponge. The !
1632 ! interface height is always subject to damping, and must always be !
1633 ! the first registered field. !
1634 
1635 ! Arguments: from_file - .true. if the variables that are used here are to
1636 ! be read from a file; .false. to be set internally.
1637 ! (in) filename - The name of the file to read for all fields
1638 ! except the inverse damping rate.
1639 ! (in) damp_file - The name of the file from which to read the
1640 ! inverse damping rate.
1641 ! (in) G - The ocean's grid structure.
1642 ! (in) GV - The ocean's vertical grid structure.
1643 ! (in) use_temperature - If true, T & S are state variables.
1644 ! (in) tv - A structure containing pointers to any available
1645 ! thermodynamic fields, including potential temperature and
1646 ! salinity or mixed layer density. Absent fields have NULL ptrs.
1647 ! (in) param_file - A structure indicating the open file to parse for
1648 ! model parameter values.
1649 ! (in/out) CSp - A pointer that is set to point to the control structure
1650 ! for this module
1651 
1652  real :: eta(szi_(g),szj_(g),szk_(g)+1) ! The target interface heights, in m.
1653  real, dimension (SZI_(G),SZJ_(G),SZK_(G)) :: &
1654  tmp, tmp2 ! A temporary array for tracers.
1655  real, dimension (SZI_(G),SZJ_(G)) :: &
1656  tmp_2d ! A temporary array for tracers.
1657 
1658  real :: Idamp(szi_(g),szj_(g)) ! The inverse damping rate, in s-1.
1659  real :: pres(szi_(g)) ! An array of the reference pressure, in Pa.
1660 
1661  integer :: i, j, k, is, ie, js, je, nz
1662  character(len=40) :: potemp_var, salin_var, Idamp_var, eta_var
1663  character(len=40) :: mdl = "initialize_sponges_file"
1664  character(len=200) :: damping_file, state_file ! Strings for filenames
1665  character(len=200) :: filename, inputdir ! Strings for file/path and path.
1666  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
1667 
1668  pres(:) = 0.0 ; eta(:,:,:) = 0.0 ; tmp(:,:,:) = 0.0 ; idamp(:,:) = 0.0
1669 
1670  call get_param(param_file, mdl, "INPUTDIR", inputdir, default=".")
1671  inputdir = slasher(inputdir)
1672  call get_param(param_file, mdl, "SPONGE_DAMPING_FILE", damping_file, &
1673  "The name of the file with the sponge damping rates.", &
1674  fail_if_missing=.true.)
1675  call get_param(param_file, mdl, "SPONGE_STATE_FILE", state_file, &
1676  "The name of the file with the state to damp toward.", &
1677  default=damping_file)
1678 
1679  call get_param(param_file, mdl, "SPONGE_PTEMP_VAR", potemp_var, &
1680  "The name of the potential temperature variable in \n"//&
1681  "SPONGE_STATE_FILE.", default="PTEMP")
1682  call get_param(param_file, mdl, "SPONGE_SALT_VAR", salin_var, &
1683  "The name of the salinity variable in \n"//&
1684  "SPONGE_STATE_FILE.", default="SALT")
1685  call get_param(param_file, mdl, "SPONGE_ETA_VAR", eta_var, &
1686  "The name of the interface height variable in \n"//&
1687  "SPONGE_STATE_FILE.", default="ETA")
1688  call get_param(param_file, mdl, "SPONGE_IDAMP_VAR", idamp_var, &
1689  "The name of the inverse damping rate variable in \n"//&
1690  "SPONGE_DAMPING_FILE.", default="IDAMP")
1691 
1692  filename = trim(inputdir)//trim(damping_file)
1693  call log_param(param_file, mdl, "INPUTDIR/SPONGE_DAMPING_FILE", filename)
1694  if (.not.file_exists(filename, g%Domain)) &
1695  call mom_error(fatal, " initialize_sponges: Unable to open "//trim(filename))
1696 
1697 
1698  call read_data(filename,"Idamp",idamp(:,:), domain=g%Domain%mpp_domain)
1699 
1700 ! Now register all of the fields which are damped in the sponge. !
1701 ! By default, momentum is advected vertically within the sponge, but !
1702 ! momentum is typically not damped within the sponge. !
1703 
1704  filename = trim(inputdir)//trim(state_file)
1705  call log_param(param_file, mdl, "INPUTDIR/SPONGE_STATE_FILE", filename)
1706  if (.not.file_exists(filename, g%Domain)) &
1707  call mom_error(fatal, " initialize_sponges: Unable to open "//trim(filename))
1708 
1709 
1710 ! The first call to set_up_sponge_field is for the interface height.!
1711  call read_data(filename, eta_var, eta(:,:,:), domain=g%Domain%mpp_domain)
1712 
1713  do j=js,je ; do i=is,ie
1714  eta(i,j,nz+1) = -g%bathyT(i,j)
1715  enddo ; enddo
1716  do k=nz,1,-1 ; do j=js,je ; do i=is,ie
1717  if (eta(i,j,k) < (eta(i,j,k+1) + gv%Angstrom_z)) &
1718  eta(i,j,k) = eta(i,j,k+1) + gv%Angstrom_z
1719  enddo ; enddo ; enddo
1720 ! Set the inverse damping rates so that the model will know where to !
1721 ! apply the sponges, along with the interface heights. !
1722  call initialize_sponge(idamp, eta, g, param_file, csp)
1723 
1724 ! Now register all of the tracer fields which are damped in the !
1725 ! sponge. By default, momentum is advected vertically within the !
1726 ! sponge, but momentum is typically not damped within the sponge. !
1727 
1728  if ( gv%nkml>0 ) then
1729 ! This call to set_up_sponge_ML_density registers the target values of the
1730 ! mixed layer density, which is used in determining which layers can be
1731 ! inflated without causing static instabilities.
1732  do i=is-1,ie ; pres(i) = tv%P_Ref ; enddo
1733 
1734  call read_data(filename, potemp_var, tmp(:,:,:), domain=g%Domain%mpp_domain)
1735  call read_data(filename, salin_var, tmp2(:,:,:), domain=g%Domain%mpp_domain)
1736 
1737  do j=js,je
1738  call calculate_density(tmp(:,j,1), tmp2(:,j,1), pres, tmp_2d(:,j), &
1739  is, ie-is+1, tv%eqn_of_state)
1740  enddo
1741 
1742  call set_up_sponge_ml_density(tmp_2d, g, csp)
1743  endif
1744 
1745 ! The remaining calls to set_up_sponge_field can be in any order. !
1746  if ( use_temperature ) then
1747  call read_data(filename, potemp_var, tmp(:,:,:), domain=g%Domain%mpp_domain)
1748  call set_up_sponge_field(tmp, tv%T, g, nz, csp)
1749  call read_data(filename, salin_var, tmp(:,:,:), domain=g%Domain%mpp_domain)
1750  call set_up_sponge_field(tmp, tv%S, g, nz, csp)
1751  endif
1752 
1753 
1754 end subroutine initialize_sponges_file
1755 ! -----------------------------------------------------------------------------
1756 
1757 ! -----------------------------------------------------------------------------
1758 subroutine set_velocity_depth_max(G)
1759  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
1760  ! This subroutine sets the 4 bottom depths at velocity points to be the
1761  ! maximum of the adjacent depths.
1762  integer :: i, j
1763 
1764  do i=g%isd,g%ied-1 ; do j=g%jsd,g%jed
1765  g%Dblock_u(i,j) = g%mask2dCu(i,j) * max(g%bathyT(i,j), g%bathyT(i+1,j))
1766  g%Dopen_u(i,j) = g%Dblock_u(i,j)
1767  enddo ; enddo
1768  do i=g%isd,g%ied ; do j=g%jsd,g%jed-1
1769  g%Dblock_v(i,j) = g%mask2dCv(i,j) * max(g%bathyT(i,j), g%bathyT(i,j+1))
1770  g%Dopen_v(i,j) = g%Dblock_v(i,j)
1771  enddo ; enddo
1772 end subroutine set_velocity_depth_max
1773 ! -----------------------------------------------------------------------------
1774 
1775 ! -----------------------------------------------------------------------------
1776 subroutine compute_global_grid_integrals(G)
1777  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
1778  ! Subroutine to pre-compute global integrals of grid quantities for
1779  ! later use in reporting diagnostics
1780  real, dimension(G%isc:G%iec, G%jsc:G%jec) :: tmpForSumming
1781  integer :: i,j
1782 
1783  tmpforsumming(:,:) = 0.
1784  g%areaT_global = 0.0 ; g%IareaT_global = 0.0
1785  do j=g%jsc,g%jec ; do i=g%isc,g%iec
1786  tmpforsumming(i,j) = g%areaT(i,j) * g%mask2dT(i,j)
1787  enddo ; enddo
1788  g%areaT_global = reproducing_sum(tmpforsumming)
1789  g%IareaT_global = 1. / g%areaT_global
1790 end subroutine compute_global_grid_integrals
1791 
1792 ! -----------------------------------------------------------------------------
1793 subroutine set_velocity_depth_min(G)
1794  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
1795  ! This subroutine sets the 4 bottom depths at velocity points to be the
1796  ! minimum of the adjacent depths.
1797  integer :: i, j
1798 
1799  do i=g%isd,g%ied-1 ; do j=g%jsd,g%jed
1800  g%Dblock_u(i,j) = g%mask2dCu(i,j) * min(g%bathyT(i,j), g%bathyT(i+1,j))
1801  g%Dopen_u(i,j) = g%Dblock_u(i,j)
1802  enddo ; enddo
1803  do i=g%isd,g%ied ; do j=g%jsd,g%jed-1
1804  g%Dblock_v(i,j) = g%mask2dCv(i,j) * min(g%bathyT(i,j), g%bathyT(i,j+1))
1805  g%Dopen_v(i,j) = g%Dblock_v(i,j)
1806  enddo ; enddo
1807 end subroutine set_velocity_depth_min
1808 ! -----------------------------------------------------------------------------
1809 
1810 ! -----------------------------------------------------------------------------
1811 !> This subroutine determines the isopycnal or other coordinate interfaces and
1812 !! layer potential temperatures and salinities directly from a z-space file on
1813 !! a latitude-longitude grid.
1814 subroutine mom_temp_salt_initialize_from_z(h, tv, G, GV, PF, just_read_params)
1815 ! This subroutine was written by M. Harrison, with input from R. Hallberg & A. Adcroft.
1816 !
1817 ! Arguments:
1818 ! (out) h - Layer thickness, in m.
1819 ! (out) tv - A structure containing pointers to any available
1820 ! thermodynamic fields, including potential temperature and
1821 ! salinity or mixed layer density. Absent fields have NULL ptrs.
1822 ! (inout) G - The ocean's grid structure.
1823 ! (in) GV - The ocean's vertical grid structure.
1824 ! (in) PF - A structure indicating the open file to parse for
1825 ! model parameter values.
1826 
1827  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
1828  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
1829  intent(out) :: h !< Layer thicknesses being initialized, in m
1830  type(thermo_var_ptrs), intent(inout) :: tv !< A structure pointing to various thermodynamic
1831  !! variables including temperature and salinity
1832  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure
1833  type(param_file_type), intent(in) :: PF !< A structure indicating the open file
1834  !! to parse for model parameter values.
1835  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
1836  !! only read parameters without changing h.
1837 
1838  character(len=200) :: filename ! The name of an input file containing temperature
1839  ! and salinity in z-space; also used for ice shelf area.
1840  character(len=200) :: shelf_file ! The name of an input file used for ice shelf area.
1841  character(len=200) :: inputdir ! The directory where NetCDF input filesare.
1842  character(len=200) :: mesg, area_varname, ice_shelf_file
1843 
1844  type(eos_type), pointer :: eos => null()
1845 
1846 ! This include declares and sets the variable "version".
1847 #include "version_variable.h"
1848  character(len=40) :: mdl = "MOM_initialize_layers_from_Z" ! This module's name.
1849 
1850  integer :: is, ie, js, je, nz ! compute domain indices
1851  integer :: isc,iec,jsc,jec ! global compute domain indices
1852  integer :: isg, ieg, jsg, jeg ! global extent
1853  integer :: isd, ied, jsd, jed ! data domain indices
1854 
1855  integer :: i, j, k, ks, np, ni, nj
1856  integer :: idbg, jdbg
1857  integer :: nkml, nkbl ! number of mixed and buffer layers
1858 
1859  integer :: kd, inconsistent
1860  real :: PI_180 ! for conversion from degrees to radians
1861 
1862  real, dimension(:,:), pointer :: shelf_area
1863  real :: min_depth
1864  real :: dilate
1865  real :: missing_value_temp, missing_value_salt
1866  logical :: correct_thickness
1867  character(len=40) :: potemp_var, salin_var
1868  character(len=8) :: laynum
1869 
1870  integer, parameter :: niter=10 ! number of iterations for t/s adjustment to layer density
1871  logical :: just_read ! If true, just read parameters but set nothing.
1872  logical :: adjust_temperature = .true. ! fit t/s to target densities
1873  real, parameter :: missing_value = -1.e20
1874  real, parameter :: temp_land_fill = 0.0, salt_land_fill = 35.0
1875  logical :: reentrant_x, tripolar_n,dbg
1876  logical :: debug = .false. ! manually set this to true for verbose output
1877 
1878  !data arrays
1879  real, dimension(:), allocatable :: z_edges_in, z_in, Rb
1880  real, dimension(:,:,:), allocatable, target :: temp_z, salt_z, mask_z
1881  real, dimension(:,:,:), allocatable :: rho_z
1882  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1) :: zi
1883  real, dimension(SZI_(G),SZJ_(G)) :: nlevs
1884  real, dimension(SZI_(G)) :: press
1885 
1886 
1887  ! Local variables for ALE remapping
1888  real, dimension(:), allocatable :: hTarget
1889  real, dimension(:,:), allocatable :: area_shelf_h
1890  real, dimension(:,:), allocatable, target :: frac_shelf_h
1891  real, dimension(:,:,:), allocatable :: tmpT1dIn, tmpS1dIn, h1, tmp_mask_in
1892  real :: zTopOfCell, zBottomOfCell
1893  type(regridding_cs) :: regridCS ! Regridding parameters and work arrays
1894  type(remapping_cs) :: remapCS ! Remapping parameters and work arrays
1895 
1896  logical :: homogenize, useALEremapping, remap_full_column, remap_general, remap_old_alg
1897  logical :: use_ice_shelf
1898  character(len=10) :: remappingScheme
1899  real :: tempAvg, saltAvg
1900  integer :: nPoints, ans
1901  integer :: id_clock_routine, id_clock_read, id_clock_interp, id_clock_fill, id_clock_ALE
1902 
1903  id_clock_routine = cpu_clock_id('(Initialize from Z)', grain=clock_routine)
1904  id_clock_ale = cpu_clock_id('(Initialize from Z) ALE', grain=clock_loop)
1905 
1906  call cpu_clock_begin(id_clock_routine)
1907 
1908  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
1909  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
1910  isg = g%isg ; ieg = g%ieg ; jsg = g%jsg ; jeg = g%jeg
1911 
1912  pi_180=atan(1.0)/45.
1913 
1914  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
1915 
1916  if (.not.just_read) call calltree_enter(trim(mdl)//"(), MOM_state_initialization.F90")
1917  if (.not.just_read) call log_version(pf, mdl, version, "")
1918 
1919  inputdir = "." ; call get_param(pf, mdl, "INPUTDIR", inputdir)
1920  inputdir = slasher(inputdir)
1921 
1922  eos => tv%eqn_of_state
1923 
1924 ! call mpp_get_compute_domain(G%domain%mpp_domain,isc,iec,jsc,jec)
1925 
1926  reentrant_x = .false. ; call get_param(pf, mdl, "REENTRANT_X", reentrant_x,default=.true.)
1927  tripolar_n = .false. ; call get_param(pf, mdl, "TRIPOLAR_N", tripolar_n, default=.false.)
1928  call get_param(pf, mdl, "MINIMUM_DEPTH", min_depth, default=0.0)
1929 
1930  call get_param(pf, mdl, "NKML",nkml,default=0)
1931  call get_param(pf, mdl, "NKBL",nkbl,default=0)
1932 
1933  call get_param(pf, mdl, "TEMP_SALT_Z_INIT_FILE",filename, &
1934  "The name of the z-space input file used to initialize \n"//&
1935  "the layer thicknesses, temperatures and salinities.", &
1936  default="temp_salt_z.nc", do_not_log=just_read)
1937  filename = trim(inputdir)//trim(filename)
1938  call get_param(pf, mdl, "Z_INIT_FILE_PTEMP_VAR", potemp_var, &
1939  "The name of the potential temperature variable in \n"//&
1940  "TEMP_SALT_Z_INIT_FILE.", default="ptemp", do_not_log=just_read)
1941  call get_param(pf, mdl, "Z_INIT_FILE_SALT_VAR", salin_var, &
1942  "The name of the salinity variable in \n"//&
1943  "TEMP_SALT_Z_INIT_FILE.", default="salt", do_not_log=just_read)
1944  call get_param(pf, mdl, "Z_INIT_HOMOGENIZE", homogenize, &
1945  "If True, then horizontally homogenize the interpolated \n"//&
1946  "initial conditions.", default=.false., do_not_log=just_read)
1947  call get_param(pf, mdl, "Z_INIT_ALE_REMAPPING", usealeremapping, &
1948  "If True, then remap straight to model coordinate from file.",&
1949  default=.false., do_not_log=just_read)
1950  call get_param(pf, mdl, "Z_INIT_REMAPPING_SCHEME", remappingscheme, &
1951  "The remapping scheme to use if using Z_INIT_ALE_REMAPPING\n"//&
1952  "is True.", default="PPM_IH4", do_not_log=just_read)
1953  call get_param(pf, mdl, "Z_INIT_REMAP_GENERAL", remap_general, &
1954  "If false, only initializes to z* coordinates.\n"//&
1955  "If true, allows initialization directly to general coordinates.",&
1956  default=.false., do_not_log=just_read)
1957  call get_param(pf, mdl, "Z_INIT_REMAP_FULL_COLUMN", remap_full_column, &
1958  "If false, only reconstructs profiles for valid data points.\n"//&
1959  "If true, inserts vanished layers below the valid data.",&
1960  default=remap_general, do_not_log=just_read)
1961  call get_param(pf, mdl, "Z_INIT_REMAP_OLD_ALG", remap_old_alg, &
1962  "If false, uses the preferred remapping algorithm for initialization.\n"//&
1963  "If true, use an older, less robust algorithm for remapping.",&
1964  default=.true., do_not_log=just_read)
1965  call get_param(pf, mdl, "ICE_SHELF", use_ice_shelf, default=.false.)
1966  if (use_ice_shelf) then
1967  call get_param(pf, mdl, "ICE_THICKNESS_FILE", ice_shelf_file, &
1968  "The file from which the ice bathymetry and area are read.", &
1969  fail_if_missing=.not.just_read, do_not_log=just_read)
1970  shelf_file = trim(inputdir)//trim(ice_shelf_file)
1971  if (.not.just_read) call log_param(pf, mdl, "INPUTDIR/THICKNESS_FILE", shelf_file)
1972  call get_param(pf, mdl, "ICE_AREA_VARNAME", area_varname, &
1973  "The name of the area variable in ICE_THICKNESS_FILE.", &
1974  fail_if_missing=.not.just_read, do_not_log=just_read)
1975  endif
1976  if (.not.usealeremapping) then
1977  call get_param(pf, mdl, "ADJUST_THICKNESS", correct_thickness, &
1978  "If true, all mass below the bottom removed if the \n"//&
1979  "topography is shallower than the thickness input file \n"//&
1980  "would indicate.", default=.false., do_not_log=just_read)
1981 
1982  call get_param(pf, mdl, "FIT_TO_TARGET_DENSITY_IC", adjust_temperature, &
1983  "If true, all the interior layers are adjusted to \n"//&
1984  "their target densities using mostly temperature \n"//&
1985  "This approach can be problematic, particularly in the \n"//&
1986  "high latitudes.", default=.true., do_not_log=just_read)
1987  endif
1988  if (just_read) then
1989  call cpu_clock_end(id_clock_routine)
1990  return ! All run-time parameters have been read, so return.
1991  endif
1992 
1993 ! Read input grid coordinates for temperature and salinity field
1994 ! in z-coordinate dataset. The file is REQUIRED to contain the
1995 ! following:
1996 !
1997 ! dimension variables:
1998 ! lon (degrees_E), lat (degrees_N), depth(meters)
1999 ! variables:
2000 ! ptemp(lon,lat,depth) : degC, potential temperature
2001 ! salt (lon,lat,depth) : PSU, salinity
2002 !
2003 ! The first record will be read if there are multiple time levels.
2004 ! The observation grid MUST tile the model grid. If the model grid extends
2005 ! to the North/South Pole past the limits of the input data, they are extrapolated using the average
2006 ! value at the northernmost/southernmost latitude.
2007 
2008  call horiz_interp_and_extrap_tracer(filename, potemp_var,1.0,1, &
2009  g, temp_z, mask_z, z_in, z_edges_in, missing_value_temp, reentrant_x, tripolar_n, homogenize)
2010 
2011  call horiz_interp_and_extrap_tracer(filename, salin_var,1.0,1, &
2012  g, salt_z, mask_z, z_in, z_edges_in, missing_value_salt, reentrant_x, tripolar_n, homogenize)
2013 
2014  kd = size(z_in,1)
2015 
2016  allocate(rho_z(isd:ied,jsd:jed,kd))
2017  allocate(area_shelf_h(isd:ied,jsd:jed))
2018  allocate(frac_shelf_h(isd:ied,jsd:jed))
2019 
2020  press(:)=tv%p_ref
2021 
2022  !Convert T&S to Absolute Salinity and Conservative Temperature if using TEOS10 or NEMO
2023  call convert_temp_salt_for_teos10(temp_z,salt_z, press, g, kd, mask_z, eos)
2024 
2025  do k=1,kd
2026  do j=js,je
2027  call calculate_density(temp_z(:,j,k),salt_z(:,j,k), press, rho_z(:,j,k), is, ie, eos)
2028  enddo
2029  enddo ! kd
2030 
2031  call pass_var(temp_z,g%Domain)
2032  call pass_var(salt_z,g%Domain)
2033  call pass_var(mask_z,g%Domain)
2034  call pass_var(rho_z,g%Domain)
2035 
2036  ! This is needed for building an ALE grid under ice shelves
2037  if (use_ice_shelf) then
2038  if (.not.file_exists(shelf_file, g%Domain)) call mom_error(fatal, &
2039  "MOM_temp_salt_initialize_from_Z: Unable to open shelf file "//trim(shelf_file))
2040 
2041  call read_data(shelf_file,trim(area_varname),area_shelf_h,domain=g%Domain%mpp_domain)
2042 
2043  ! initialize frac_shelf_h with zeros (open water everywhere)
2044  frac_shelf_h(:,:) = 0.0
2045  ! compute fractional ice shelf coverage of h
2046  do j=jsd,jed ; do i=isd,ied
2047  if (g%areaT(i,j) > 0.0) &
2048  frac_shelf_h(i,j) = area_shelf_h(i,j) / g%areaT(i,j)
2049  enddo ; enddo
2050  ! pass to the pointer
2051  shelf_area => frac_shelf_h
2052 
2053  endif
2054 
2055 ! Done with horizontal interpolation.
2056 ! Now remap to model coordinates
2057  if (usealeremapping) then
2058  call cpu_clock_begin(id_clock_ale)
2059  ! The regridding tools (grid generation) are coded to work on model arrays of the same
2060  ! vertical shape. We need to re-write the regridding if the model has fewer layers
2061  ! than the data. -AJA
2062  if (kd>nz) call mom_error(fatal,"MOM_initialize_state, MOM_temp_salt_initialize_from_Z(): "//&
2063  "Data has more levels than the model - this has not been coded yet!")
2064  ! Build the source grid and copy data onto model-shaped arrays with vanished layers
2065  allocate( tmp_mask_in(isd:ied,jsd:jed,nz) ) ; tmp_mask_in(:,:,:) = 0.
2066  allocate( h1(isd:ied,jsd:jed,nz) ) ; h1(:,:,:) = 0.
2067  allocate( tmpt1din(isd:ied,jsd:jed,nz) ) ; tmpt1din(:,:,:) = 0.
2068  allocate( tmps1din(isd:ied,jsd:jed,nz) ) ; tmps1din(:,:,:) = 0.
2069  do j = js, je ; do i = is, ie
2070  if (g%mask2dT(i,j)>0.) then
2071  ztopofcell = 0. ; zbottomofcell = 0. ; npoints = 0
2072  tmp_mask_in(i,j,1:kd) = mask_z(i,j,:)
2073  do k = 1, nz
2074  if (tmp_mask_in(i,j,k)>0. .and. k<=kd) then
2075  zbottomofcell = -min( z_edges_in(k+1), g%bathyT(i,j) )
2076  tmpt1din(i,j,k) = temp_z(i,j,k)
2077  tmps1din(i,j,k) = salt_z(i,j,k)
2078  elseif (k>1) then
2079  zbottomofcell = -g%bathyT(i,j)
2080  tmpt1din(i,j,k) = tmpt1din(i,j,k-1)
2081  tmps1din(i,j,k) = tmps1din(i,j,k-1)
2082  else ! This next block should only ever be reached over land
2083  tmpt1din(i,j,k) = -99.9
2084  tmps1din(i,j,k) = -99.9
2085  endif
2086  h1(i,j,k) = ztopofcell - zbottomofcell
2087  if (h1(i,j,k)>0.) npoints = npoints + 1
2088  ztopofcell = zbottomofcell ! Bottom becomes top for next value of k
2089  enddo
2090  h1(i,j,kd) = h1(i,j,kd) + ( ztopofcell + g%bathyT(i,j) ) ! In case data is deeper than model
2091  endif ! mask2dT
2092  enddo ; enddo
2093  deallocate( tmp_mask_in )
2094  call pass_var(h1, g%Domain)
2095  call pass_var(tmpt1din, g%Domain)
2096  call pass_var(tmps1din, g%Domain)
2097 
2098  ! Build the target grid (and set the model thickness to it)
2099  ! This call can be more general but is hard-coded for z* coordinates... ????
2100  call ale_initregridding( gv, g%max_depth, pf, mdl, regridcs ) ! sets regridCS
2101 
2102  if (.not. remap_general) then
2103  ! This is the old way of initializing to z* coordinates only
2104  allocate( htarget(nz) )
2105  htarget = getcoordinateresolution( regridcs )
2106  do j = js, je ; do i = is, ie
2107  h(i,j,:) = 0.
2108  if (g%mask2dT(i,j)>0.) then
2109  ! Build the target grid combining hTarget and topography
2110  ztopofcell = 0. ; zbottomofcell = 0.
2111  do k = 1, nz
2112  zbottomofcell = max( ztopofcell - htarget(k), -g%bathyT(i,j) )
2113  h(i,j,k) = ztopofcell - zbottomofcell
2114  ztopofcell = zbottomofcell ! Bottom becomes top for next value of k
2115  enddo
2116  else
2117  h(i,j,:) = 0.
2118  endif ! mask2dT
2119  enddo ; enddo
2120  call pass_var(h, g%Domain)
2121  deallocate( htarget )
2122  endif
2123 
2124  ! Now remap from source grid to target grid
2125  call initialize_remapping( remapcs, remappingscheme, boundary_extrapolation=.false. ) ! Reconstruction parameters
2126  if (remap_general) then
2127  call set_regrid_params( regridcs, min_thickness=0. )
2128  h(:,:,:) = h1(:,:,:) ; tv%T(:,:,:) = tmpt1din(:,:,:) ; tv%S(:,:,:) = tmps1din(:,:,:)
2129  do j = js, je ; do i = is, ie
2130  if (g%mask2dT(i,j)==0.) then ! Ensure there are no nonsense values on land
2131  h(i,j,:) = 0. ; tv%T(i,j,:) = 0. ; tv%S(i,j,:) = 0.
2132  endif
2133  enddo ; enddo
2134  call pass_var(h, g%Domain) ! Regridding might eventually use spatial information and
2135  call pass_var(tv%T, g%Domain) ! thus needs to be up to date in the halo regions even though
2136  call pass_var(tv%S, g%Domain) ! ALE_build_grid() only updates h on the computational domain.
2137 
2138  if (use_ice_shelf) then
2139  call ale_build_grid( g, gv, regridcs, remapcs, h, tv, .true., shelf_area)
2140  else
2141  call ale_build_grid( g, gv, regridcs, remapcs, h, tv, .true. )
2142  endif
2143  endif
2144  call ale_remap_scalar( remapcs, g, gv, nz, h1, tmpt1din, h, tv%T, all_cells=remap_full_column, old_remap=remap_old_alg )
2145  call ale_remap_scalar( remapcs, g, gv, nz, h1, tmps1din, h, tv%S, all_cells=remap_full_column, old_remap=remap_old_alg )
2146  deallocate( h1 )
2147  deallocate( tmpt1din )
2148  deallocate( tmps1din )
2149 
2150  call cpu_clock_end(id_clock_ale)
2151 
2152  else ! remap to isopycnal layer space
2153 
2154 ! next find interface positions using local arrays
2155 ! nlevs contains the number of valid data points in each column
2156  nlevs = sum(mask_z,dim=3)
2157 
2158 ! Rb contains the layer interface densities
2159  allocate(rb(nz+1))
2160  do k=2,nz ; rb(k)=0.5*(gv%Rlay(k-1)+gv%Rlay(k)) ; enddo
2161  rb(1) = 0.0 ; rb(nz+1) = 2.0*gv%Rlay(nz) - gv%Rlay(nz-1)
2162 
2163  zi(is:ie,js:je,:) = find_interfaces(rho_z(is:ie,js:je,:), z_in, rb, g%bathyT(is:ie,js:je), &
2164  nlevs(is:ie,js:je), nkml, nkbl, min_depth)
2165 
2166  if (correct_thickness) then
2167  call adjustetatofitbathymetry(g, gv, zi, h)
2168  else
2169  do k=nz,1,-1 ; do j=js,je ; do i=is,ie
2170  if (zi(i,j,k) < (zi(i,j,k+1) + gv%Angstrom_z)) then
2171  zi(i,j,k) = zi(i,j,k+1) + gv%Angstrom_z
2172  h(i,j,k) = gv%Angstrom_z
2173  else
2174  h(i,j,k) = zi(i,j,k) - zi(i,j,k+1)
2175  endif
2176  enddo ; enddo ; enddo
2177  inconsistent=0
2178  do j=js,je ; do i=is,ie
2179  if (abs(zi(i,j,nz+1) + g%bathyT(i,j)) > 1.0) &
2180  inconsistent = inconsistent + 1
2181  enddo ; enddo
2182  call sum_across_pes(inconsistent)
2183 
2184  if ((inconsistent > 0) .and. (is_root_pe())) then
2185  write(mesg,'("Thickness initial conditions are inconsistent ",'// &
2186  '"with topography in ",I5," places.")') inconsistent
2187  call mom_error(warning, mesg)
2188  endif
2189  endif
2190 
2191  tv%T(is:ie,js:je,:) = tracer_z_init(temp_z(is:ie,js:je,:),-1.0*z_edges_in,zi(is:ie,js:je,:), &
2192  nkml,nkbl,missing_value,g%mask2dT(is:ie,js:je),nz, &
2193  nlevs(is:ie,js:je),dbg,idbg,jdbg)
2194  tv%S(is:ie,js:je,:) = tracer_z_init(salt_z(is:ie,js:je,:),-1.0*z_edges_in,zi(is:ie,js:je,:), &
2195  nkml,nkbl,missing_value,g%mask2dT(is:ie,js:je),nz, &
2196  nlevs(is:ie,js:je))
2197 
2198  do k=1,nz
2199  npoints = 0 ; tempavg = 0. ; saltavg = 0.
2200  do j=js,je ; do i=is,ie ; if (g%mask2dT(i,j) >= 1.0) then
2201  npoints = npoints + 1
2202  tempavg = tempavg + tv%T(i,j,k)
2203  saltavg =saltavg + tv%S(i,j,k)
2204  endif ; enddo ; enddo
2205 
2206  ! Horizontally homogenize data to produce perfectly "flat" initial conditions
2207  if (homogenize) then
2208  call sum_across_pes(npoints)
2209  call sum_across_pes(tempavg)
2210  call sum_across_pes(saltavg)
2211  if (npoints>0) then
2212  tempavg = tempavg/real(npoints)
2213  saltavg = saltavg/real(npoints)
2214  endif
2215  tv%T(:,:,k) = tempavg
2216  tv%S(:,:,k) = saltavg
2217  endif
2218  enddo
2219 
2220  endif ! useALEremapping
2221 
2222 ! Fill land values
2223  do k=1,nz ; do j=js,je ; do i=is,ie
2224  if (tv%T(i,j,k) == missing_value) then
2225  tv%T(i,j,k)=temp_land_fill
2226  tv%S(i,j,k)=salt_land_fill
2227  endif
2228  enddo ; enddo ; enddo
2229 
2230 ! Finally adjust to target density
2231  ks=max(0,nkml)+max(0,nkbl)+1
2232 
2233  if (adjust_temperature .and. .not. usealeremapping) then
2234  call determine_temperature(tv%T(is:ie,js:je,:), tv%S(is:ie,js:je,:), &
2235  gv%Rlay(1:nz), tv%p_ref, niter, missing_value, h(is:ie,js:je,:), ks, eos)
2236 
2237  endif
2238 
2239  deallocate(z_in,z_edges_in,temp_z,salt_z,mask_z)
2240 
2241  call pass_var(h, g%Domain)
2242  call pass_var(tv%T, g%Domain)
2243  call pass_var(tv%S, g%Domain)
2244 
2245  call calltree_leave(trim(mdl)//'()')
2246  call cpu_clock_end(id_clock_routine)
2247 
2248 end subroutine mom_temp_salt_initialize_from_z
2249 
2250 !> Run simple unit tests
2251 subroutine mom_state_init_tests(G, GV, tv)
2252  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure.
2253  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
2254  type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamics structure.
2255  ! Local variables
2256  integer, parameter :: nk=5
2257  real, dimension(nk) :: T, T_t, T_b, S, S_t, S_b, rho, h, z
2258  real, dimension(nk+1) :: e
2259  integer :: k
2260  real :: P_tot, P_t, P_b, z_out
2261  type(remapping_cs), pointer :: remap_CS => null()
2262 
2263  do k = 1, nk
2264  h(k) = 100.
2265  enddo
2266  e(1) = 0.
2267  do k = 1, nk
2268  e(k+1) = e(k) - h(k)
2269  enddo
2270  p_tot = 0.
2271  do k = 1, nk
2272  z(k) = 0.5 * ( e(k) + e(k+1) )
2273  t_t(k) = 20.+(0./500.)*e(k)
2274  t(k) = 20.+(0./500.)*z(k)
2275  t_b(k) = 20.+(0./500.)*e(k+1)
2276  s_t(k) = 35.-(0./500.)*e(k)
2277  s(k) = 35.+(0./500.)*z(k)
2278  s_b(k) = 35.-(0./500.)*e(k+1)
2279  call calculate_density(0.5*(t_t(k)+t_b(k)), 0.5*(s_t(k)+s_b(k)), -gv%Rho0*gv%g_Earth*z(k), rho(k), tv%eqn_of_state)
2280  p_tot = p_tot + gv%g_Earth * rho(k) * h(k)
2281  enddo
2282 
2283  p_t = 0.
2284  do k = 1, nk
2285  call find_depth_of_pressure_in_cell(t_t(k), t_b(k), s_t(k), s_b(k), e(k), e(k+1), &
2286  p_t, 0.5*p_tot, gv%Rho0, gv%g_Earth, tv%eqn_of_state, p_b, z_out)
2287  write(0,*) k,p_t,p_b,0.5*p_tot,e(k),e(k+1),z_out
2288  p_t = p_b
2289  enddo
2290  write(0,*) p_b,p_tot
2291 
2292  write(0,*) ''
2293  write(0,*) ' ==================================================================== '
2294  write(0,*) ''
2295  write(0,*) h
2296  call cut_off_column_top(nk, tv, gv%Rho0, gv%g_Earth, -e(nk+1), gv%Angstrom, &
2297  t, t_t, t_b, s, s_t, s_b, 0.5*p_tot, h, remap_cs)
2298  write(0,*) h
2299 
2300 end subroutine mom_state_init_tests
2301 
2302 end module mom_state_initialization
The module configures the model for the "external_gwave" experiment. external_gwave = External Gravit...
subroutine, public read_axis_data(filename, axis_name, var)
Definition: MOM_io.F90:424
subroutine, public user_initialize_sponges(G, use_temperature, tv, param_file, CSp, h)
Set up the sponges.
subroutine adjustetatofitbathymetry(G, GV, eta, h)
Adjust interface heights to fit the bathymetry and diagnose layer thickness. If the bottom most inter...
subroutine, public soliton_initialize_thickness(h, G)
Initialization of thicknesses in Equatorial Rossby soliton test.
real function, dimension(size(tr_in, 1), size(tr_in, 2), nlay), public tracer_z_init(tr_in, z_edges, e, nkml, nkbl, land_fill, wet, nlay, nlevs, debug, i_debug, j_debug)
subroutine mom_state_init_tests(G, GV, tv)
Run simple unit tests.
subroutine, public circle_obcs_initialize_thickness(h, G, GV, param_file, just_read_params)
This subroutine initializes layer thicknesses for the circle_obcs experiment.
subroutine initialize_temp_salt_from_file(T, S, G, param_file, just_read_params)
subroutine depress_surface(h, G, GV, param_file, tv, just_read_params)
This module contains the main regridding routines. Regridding comprises two steps: (1) Interpolation ...
Definition: MOM_ALE.F90:7
logical function, public ispointincell(G, i, j, x, y)
Returns true if the coordinates (x,y) are within the h-cell (i,j)
Definition: MOM_grid.F90:406
subroutine, public benchmark_init_temperature_salinity(T, S, G, GV, param_file, eqn_of_state, P_Ref, just_read_params)
This function puts the initial layer temperatures and salinities into T(:,:,:) and S(:...
subroutine initialize_temp_salt_fit(T, S, G, GV, param_file, eqn_of_state, P_Ref, just_read_params)
subroutine, public isomip_initialize_temperature_salinity(T, S, h, G, GV, param_file, eqn_of_state, just_read_params)
Initial values for temperature and salinity.
subroutine, public isomip_initialize_thickness(h, G, GV, param_file, tv, just_read_params)
Initialization of thicknesses.
subroutine, public scm_cvmix_tests_ts_init(T, S, h, G, GV, param_file, just_read_params)
Initializes temperature and salinity for the SCM CVmix test example.
subroutine, public int_specific_vol_dp(T, S, p_t, p_b, alpha_ref, HI, EOS, dza, intp_dza, intx_dza, inty_dza, halo_size)
Calls the appropriate subroutine to alculate analytical and nearly-analytical integrals in pressure a...
Definition: MOM_EOS.F90:333
subroutine, public initialize_masks(G, PF)
initialize_masks initializes the grid masks and any metrics that come with masks already applied...
subroutine, public ale_build_grid(G, GV, regridCS, remapCS, h, tv, debug, frac_shelf_h)
Generates new grid.
Definition: MOM_ALE.F90:648
subroutine initialize_velocity_zero(u, v, G, param_file, just_read_params)
integer, parameter, public to_all
The module calculates interface heights, including free surface height.
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
subroutine, public user_init_temperature_salinity(T, S, G, param_file, eqn_of_state, just_read_params)
This function puts the initial layer temperatures and salinities into T(:,:,:) and S(:...
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:45
subroutine initialize_thickness_uniform(h, G, GV, param_file, just_read_params)
Provides the ocean grid type.
Definition: MOM_grid.F90:2
real function, dimension(cs%nk), public getcoordinateresolution(CS)
subroutine trim_for_ice(PF, G, GV, ALE_CSp, tv, h, just_read_params)
Adjust the layer thicknesses by cutting away the top of each model column at the depth where the hydr...
Generates vertical grids as part of the ALE algorithm.
Provides column-wise vertical remapping functions.
subroutine, public mom_initialize_state(u, v, h, tv, Time, G, GV, PF, dirs, restart_CS, ALE_CSp, tracer_Reg, sponge_CSp, ALE_sponge_CSp, OBC, Time_in)
subroutine, public ale_initthicknesstocoord(CS, G, GV, h)
Set h to coordinate values for fixed coordinate systems.
Definition: MOM_ALE.F90:1307
By Robert Hallberg, April 1994 - June 2002 *This subroutine initializes the fields for the simulation...
subroutine initialize_temp_salt_from_profile(T, S, G, param_file, just_read_params)
subroutine, public calltree_leave(mesg)
Writes a message about leaving a subroutine if call tree reporting is active.
The module configures the model for the geostrophic adjustment test case.
The module configures the ISOMIP test case.
subroutine convert_thickness(h, G, GV, tv)
real function my_psi(ig, jg)
This module contains I/O framework code.
Definition: MOM_io.F90:2
subroutine, public ale_regrid_accelerated(CS, G, GV, h_orig, tv, n, h_new, u, v)
For a state-based coordinate, accelerate the process of regridding by repeatedly applying the grid ca...
Definition: MOM_ALE.F90:691
subroutine initialize_velocity_uniform(u, v, G, param_file, just_read_params)
subroutine, public find_depth_of_pressure_in_cell(T_t, T_b, S_t, S_b, z_t, z_b, P_t, P_tgt, rho_ref, G_e, EOS, P_b, z_out)
Find the depth at which the reconstructed pressure matches P_tgt.
Definition: MOM_EOS.F90:1235
logical function, public open_boundary_query(OBC, apply_open_OBC, apply_specified_OBC, apply_Flather_OBC, apply_nudged_OBC, needs_ext_seg_data)
Initial conditions for the 2D Rossby front test.
subroutine, public set_up_ale_sponge_field(sp_val, G, f_ptr, CS)
This subroutine stores the reference profile at h points for the variable.
This module contains the routines used to apply sponge layers when using the ALE mode. Applying sponges requires the following: (1) initialize_ALE_sponge (2) set_up_ALE_sponge_field (tracers) and set_up_ALE_sponge_vel_field (vel) (3) apply_ALE_sponge (4) init_ALE_sponge_diags (not being used for now) (5) ALE_sponge_end (not being used for now)
subroutine, public adjustment_initialize_temperature_salinity(T, S, h, G, param_file, eqn_of_state, just_read_params)
Initialization of temperature and salinity.
SPONGE control structure.
By Robert Hallberg, April 1994 - June 2002 *This subroutine initializes the fields for the simulation...
subroutine, public setverticalgridaxes(Rlay, GV)
This sets the coordinate data for the "layer mode" of the isopycnal model.
Initial conditions for the Equatorial Rossby soliton test (Boyd).
subroutine, public phillips_initialize_sponges(G, use_temperature, tv, param_file, CSp, h)
Sets up the the inverse restoration time (Idamp), and.
subroutine, public dome_initialize_thickness(h, G, GV, param_file, just_read_params)
This subroutine initializes layer thicknesses for the DOME experiment.
Container for remapping parameters.
integer, parameter, public obc_simple
subroutine, public phillips_initialize_velocity(u, v, G, GV, param_file, just_read_params)
Initialize velocity fields.
character(len=len(input_string)) function, public lowercase(input_string)
subroutine, public dome2d_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialize thicknesses according to coordinate mode.
subroutine cut_off_column_top(nk, tv, Rho0, G_earth, depth, min_thickness, T, T_t, T_b, S, S_t, S_b, p_surf, h, remap_CS)
Adjust the layer thicknesses by cutting away the top at the depth where the hydrostatic pressure matc...
subroutine, public phillips_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialize thickness field.
subroutine, public sloshing_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialization of thicknesses This routine is called when THICKNESS_CONFIG is set to &#39;sloshing&#39;...
subroutine, public convert_temp_salt_for_teos10(T, S, press, G, kd, mask_z, EOS)
Convert T&S to Absolute Salinity and Conservative Temperature if using TEOS10.
Definition: MOM_EOS.F90:2129
subroutine, public lock_exchange_initialize_thickness(h, G, GV, param_file, just_read_params)
This subroutine initializes layer thicknesses for the lock_exchange experiment.
subroutine, public calltree_waypoint(mesg, n)
Writes a message about reaching a milestone if call tree reporting is active.
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
subroutine, public rossby_front_initialize_velocity(u, v, h, G, GV, param_file, just_read_params)
Initialization of u and v in the Rossby front test.
subroutine, public calculate_density_derivs(T, S, pressure, drho_dT, drho_dS, start, npts, EOS)
Calls the appropriate subroutine to calculate density derivatives for 1-D array inputs.
Definition: MOM_EOS.F90:214
character(len=len(input_string)) function, public uppercase(input_string)
Initial conditions for an idealized baroclinic zone.
Regridding control structure.
subroutine, public initialize_sponge(Iresttime, int_height, G, param_file, CS, Iresttime_i_mean, int_height_i_mean)
Definition: MOM_sponge.F90:142
subroutine, public set_regrid_params(CS, boundary_extrapolation, min_thickness, old_grid_weight, interp_scheme, depth_of_time_filter_shallow, depth_of_time_filter_deep, compress_fraction, dz_min_surface, nz_fixed_surface, Rho_ML_avg_depth, nlay_ML_to_interior, fix_haloclines, halocline_filt_len, halocline_strat_tol, integrate_downward_for_e, adaptTimeRatio, adaptZoom, adaptZoomCoeff, adaptBuoyCoeff, adaptAlpha, adaptDoMin)
Can be used to set any of the parameters for MOM_regridding.
subroutine, public sloshing_initialize_temperature_salinity(T, S, h, G, param_file, eqn_of_state, just_read_params)
Initialization of temperature and salinity.
subroutine, public set_up_sponge_field(sp_val, f_ptr, G, nlay, CS, sp_val_i_mean)
Definition: MOM_sponge.F90:271
Type to carry basic tracer information.
subroutine, public scm_idealized_hurricane_ts_init(T, S, h, G, GV, param_file, just_read_params)
Initializes temperature and salinity for the SCM idealized hurricane example.
subroutine, public user_set_obc_data(OBC, tv, G, param_file, tr_Reg)
This subroutine sets the properties of flow at open boundary conditions.
subroutine, public seamount_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialization of thicknesses. This subroutine initializes the layer thicknesses to be uniform...
subroutine, public open_boundary_init(G, param_file, OBC)
Initialize open boundary control structure.
logical function, public is_root_pe()
subroutine, public dense_water_initialize_ts(G, GV, param_file, eqn_of_state, T, S, h, just_read_params)
Initialize the temperature and salinity for the dense water experiment.
subroutine, public set_grid_metrics(G, param_file)
set_grid_metrics is used to set the primary values in the model&#39;s horizontal grid. The bathymetry, land-sea mask and any restricted channel widths are not known yet, so these are set later.
subroutine, public dome2d_initialize_sponges(G, GV, tv, param_file, use_ALE, CSp, ACSp)
Set up sponges in 2d DOME configuration.
subroutine, public add_tracer_obc_values(name, Reg, OBC_inflow, OBC_in_u, OBC_in_v)
This subroutine adds open boundary condition concentrations for a tracer that has previously been reg...
subroutine, public rossby_front_initialize_temperature_salinity(T, S, h, G, param_file, eqn_of_state, just_read_params)
Initialization of temperature and salinity in the Rossby front test.
subroutine initialize_thickness_from_file(h, G, GV, param_file, file_has_thickness, just_read_params)
This subroutine reads the layer thicknesses or interface heights from a file.
The module configures the model for the "lock_exchange" experiment. lock_exchange = A 2-d density dri...
subroutine, public rossby_front_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialization of thicknesses in 2D Rossby front test.
subroutine, public soliton_initialize_velocity(u, v, h, G)
Initialization of u and v in the equatorial Rossby soliton test.
subroutine, public baroclinic_zone_init_temperature_salinity(T, S, h, G, param_file, just_read_params)
Initialization of temperature and salinity with the baroclinic zone initial conditions.
The module configures the model for the "circle_obcs" experiment. circle_obcs = Test of Open Boundary...
The module configures the model for the non-rotating sloshing test case.
subroutine, public dome_initialize_sponges(G, GV, tv, PF, CSp)
This subroutine sets the inverse restoration time (Idamp), and ! the values towards which the interfa...
subroutine initialize_velocity_circular(u, v, G, param_file, just_read_params)
subroutine, public initialize_ale_sponge(Iresttime, data_h, nz_data, G, param_file, CS)
This subroutine determines the number of points which are within.
subroutine, public mom_mesg(message, verb, all_print)
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
Type for describing a variable, typically a tracer.
Definition: MOM_io.F90:51
subroutine, public user_initialize_thickness(h, G, param_file, T, just_read_params)
initialize thicknesses.
subroutine, public isomip_initialize_sponges(G, GV, tv, PF, use_ALE, CSp, ACSp)
Sets up the the inverse restoration time (Idamp), and.
subroutine, public remapping_core_h(CS, n0, h0, u0, n1, h1, u1)
Remaps column of values u0 on grid h0 to grid h1 assuming the top edge is aligned.
subroutine, public ale_initregridding(GV, max_depth, param_file, mdl, regridCS)
Initializes regridding for the main ALE algorithm.
Definition: MOM_ALE.F90:1188
Initialize state variables, u, v, h, T and S.
subroutine, public supercritical_set_obc_data(OBC, G, param_file)
This subroutine sets the properties of flow at open boundary conditions.
subroutine mom_temp_salt_initialize_from_z(h, tv, G, GV, PF, just_read_params)
This subroutine determines the isopycnal or other coordinate interfaces and layer potential temperatu...
subroutine initialize_sponges_file(G, GV, use_temperature, tv, param_file, CSp)
This subroutine sets the inverse restoration time (Idamp), and the values towards which the interface...
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine, public external_gwave_initialize_thickness(h, G, param_file, just_read_params)
This subroutine initializes layer thicknesses for the external_gwave experiment.
real function, dimension(size(rho, 1), size(rho, 2), size(rb, 1)), public find_interfaces(rho, zin, Rb, depth, nlevs, nkml, nkbl, hml, debug)
Initial conditions and forcing for the single column model (SCM) CVmix test set.
Initialization routines for the dense water formation and overflow experiment.
integer, parameter, public obc_none
subroutine, public pressure_gradient_plm(CS, S_t, S_b, T_t, T_b, G, GV, tv, h)
Use plm reconstruction for pressure gradient (determine edge values) By using a PLM (limited piecewis...
Definition: MOM_ALE.F90:1030
Controls where open boundary conditions are applied.
subroutine, public dome2d_initialize_temperature_salinity(T, S, h, G, param_file, eqn_of_state, just_read_params)
Initialize temperature and salinity in the 2d DOME configuration.
subroutine, public benchmark_initialize_thickness(h, G, GV, param_file, eqn_of_state, P_ref, just_read_params)
This subroutine initializes layer thicknesses for the benchmark test case, by finding the depths of i...
subroutine, public initialize_remapping(CS, remapping_scheme, boundary_extrapolation, check_reconstruction, check_remapping, force_bounds_in_subcell)
Constructor for remapping control structure.
subroutine, public adjustment_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialization of thicknesses. This subroutine initializes the layer thicknesses to be uniform...
subroutine, public set_up_sponge_ml_density(sp_val, G, CS, sp_val_i_mean)
Definition: MOM_sponge.F90:339
subroutine, public dome_set_obc_data(OBC, tv, G, GV, param_file, tr_Reg)
This subroutine sets the properties of flow at open boundary conditions. This particular example is f...
ALE control structure.
Definition: MOM_ALE.F90:61
The module configures the model for the "DOME" experiment. DOME = Dynamics of Overflows and Mixing Ex...
subroutine, public set_tracer_data(OBC, tv, h, G, PF, tracer_Reg)
Sets the initial values of the tracer and h open boundary conditions. Also allocates and fills the se...
subroutine, public ale_remap_scalar(CS, G, GV, nk_src, h_src, s_src, h_dst, s_dst, all_cells, old_remap)
Remaps a single scalar between grids described by thicknesses h_src and h_dst. h_dst must be dimensio...
Definition: MOM_ALE.F90:970
subroutine, public dense_water_initialize_sponges(G, GV, tv, param_file, use_ALE, CSp, ACSp)
Initialize the restoring sponges for the dense water experiment.
subroutine initialize_velocity_from_file(u, v, G, param_file, just_read_params)
subroutine, public determine_temperature(temp, salt, R, p_ref, niter, land_fill, h, k_start, eos)
subroutine, public mom_error(level, message, all_print)
Initial conditions and forcing for the single column model (SCM) idealized hurricane example...
subroutine, public seamount_initialize_temperature_salinity(T, S, h, G, GV, param_file, eqn_of_state, just_read_params)
Initial values for temperature and salinity.
subroutine initialize_temp_salt_linear(T, S, G, param_file, just_read_params)
The module configures the model for the idealized seamount test case.
subroutine, public restore_state(filename, directory, day, G, CS)
subroutine, public bfb_initialize_sponges_southonly(G, use_temperature, tv, param_file, CSp, h)
subroutine, public user_initialize_velocity(u, v, G, param_file, just_read_params)
initialize velocities.
The module configures the model for the "supercritical" experiment. https://marine.rutgers.edu/po/index.php?model=test-problems&title=supercritical.
A control structure for the equation of state.
Definition: MOM_EOS.F90:55
subroutine, public calltree_enter(mesg, n)
Writes a message about entering a subroutine if call tree reporting is active.