MOM6
dense_water_initialization.F90
1 !> Initialization routines for the dense water formation
2 !! and overflow experiment.
4 
5 ! This file is part of MOM6. See LICENSE.md for the license.
6 
9 use mom_eos, only : eos_type
10 use mom_error_handler, only : mom_error, fatal
12 use mom_grid, only : ocean_grid_type
13 use mom_sponge, only : sponge_cs
17 
18 implicit none ; private
19 
20 #include <MOM_memory.h>
21 
22 public dense_water_initialize_topography
23 public dense_water_initialize_ts
24 public dense_water_initialize_sponges
25 
26 character(len=40) :: mdl = "dense_water_initialization" !< Module name
27 
28 real, parameter :: default_sill = 0.2 !< Default depth of the sill [nondim]
29 real, parameter :: default_shelf = 0.4 !< Default depth of the shelf [nondim]
30 real, parameter :: default_mld = 0.25 !< Default depth of the mixed layer [nondim]
31 
32 contains
33 
34 !> Initialize the topography field for the dense water experiment
35 subroutine dense_water_initialize_topography(D, G, param_file, max_depth)
36  type(dyn_horgrid_type), intent(in) :: g !< The dynamic horizontal grid type
37  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
38  intent(out) :: d !< Ocean bottom depth in the units of depth_max
39  type(param_file_type), intent(in) :: param_file !< Parameter file structure
40  real, intent(in) :: max_depth !< Maximum ocean depth in arbitrary units
41 
42  ! Local variables
43  real, dimension(5) :: domain_params ! nondimensional widths of all domain sections
44  real :: sill_frac, shelf_frac
45  integer :: i, j
46  real :: x
47 
48  call get_param(param_file, mdl, "DENSE_WATER_DOMAIN_PARAMS", domain_params, &
49  "Fractional widths of all the domain sections for the dense water experiment.\n"//&
50  "As a 5-element vector:\n"//&
51  " - open ocean, the section at maximum depth\n"//&
52  " - downslope, the downward overflow slope\n"//&
53  " - sill separating downslope from upslope\n"//&
54  " - upslope, the upward slope accumulating dense water\n"//&
55  " - the shelf in the dense formation region.", &
56  units="nondim", fail_if_missing=.true.)
57  call get_param(param_file, mdl, "DENSE_WATER_SILL_DEPTH", sill_frac, &
58  "Depth of the sill separating downslope from upslope, as fraction of basin depth.", &
59  units="nondim", default=default_sill)
60  call get_param(param_file, mdl, "DENSE_WATER_SHELF_DEPTH", shelf_frac, &
61  "Depth of the shelf region accumulating dense water for overflow, as fraction of basin depth.", &
62  units="nondim", default=default_shelf)
63 
64  do i = 2, 5
65  ! turn widths into positions
66  domain_params(i) = domain_params(i-1) + domain_params(i)
67  enddo
68 
69  do j = g%jsc,g%jec
70  do i = g%isc,g%iec
71  ! compute normalised zonal coordinate
72  x = (g%geoLonT(i,j) - g%west_lon) / g%len_lon
73 
74  if (x <= domain_params(1)) then
75  ! open ocean region
76  d(i,j) = max_depth
77  elseif (x <= domain_params(2)) then
78  ! downslope region, linear
79  d(i,j) = max_depth - (1.0 - sill_frac) * max_depth * &
80  (x - domain_params(1)) / (domain_params(2) - domain_params(1))
81  elseif (x <= domain_params(3)) then
82  ! sill region
83  d(i,j) = sill_frac * max_depth
84  elseif (x <= domain_params(4)) then
85  ! upslope region
86  d(i,j) = sill_frac * max_depth + (shelf_frac - sill_frac) * max_depth * &
87  (x - domain_params(3)) / (domain_params(4) - domain_params(3))
88  else
89  ! shelf region
90  d(i,j) = shelf_frac * max_depth
91  endif
92  enddo
93  enddo
94 
95 end subroutine dense_water_initialize_topography
96 
97 !> Initialize the temperature and salinity for the dense water experiment
98 subroutine dense_water_initialize_ts(G, GV, param_file, eqn_of_state, T, S, h, just_read_params)
99  type(ocean_grid_type), intent(in) :: g !< Horizontal grid control structure
100  type(verticalgrid_type), intent(in) :: gv !< Vertical grid control structure
101  type(param_file_type), intent(in) :: param_file !< Parameter file structure
102  type(eos_type), pointer :: eqn_of_state !< EOS structure
103  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(out) :: t !< Output temperature [degC]
104  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(out) :: s !< Output salinity [ppt]
105  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
106  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
107  !! only read parameters without changing h.
108  ! Local variables
109  real :: mld, s_ref, s_range, t_ref
110  real :: zi, zmid
111  logical :: just_read ! If true, just read parameters but set nothing.
112  integer :: i, j, k, nz
113 
114  nz = gv%ke
115 
116  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
117 
118  call get_param(param_file, mdl, "DENSE_WATER_MLD", mld, &
119  "Depth of unstratified mixed layer as a fraction of the water column.", &
120  units="nondim", default=default_mld, do_not_log=just_read)
121 
122  call get_param(param_file, mdl, "S_REF", s_ref, do_not_log=.true.)
123  call get_param(param_file, mdl, "S_RANGE", s_range, do_not_log=.true.)
124  call get_param(param_file, mdl, "T_REF", t_ref, do_not_log=.true.)
125 
126  if (just_read) return ! All run-time parameters have been read, so return.
127 
128  ! uniform temperature everywhere
129  t(:,:,:) = t_ref
130 
131  do j = g%jsc,g%jec
132  do i = g%isc,g%iec
133  zi = 0.
134  do k = 1,nz
135  ! nondimensional middle of layer
136  zmid = zi + 0.5 * h(i,j,k) / (gv%Z_to_H * g%max_depth)
137 
138  if (zmid < mld) then
139  ! use reference salinity in the mixed layer
140  s(i,j,k) = s_ref
141  else
142  ! linear between bottom of mixed layer and bottom
143  s(i,j,k) = s_ref + s_range * (zmid - mld) / (1.0 - mld)
144  endif
145 
146  zi = zi + h(i,j,k) / (gv%Z_to_H * g%max_depth)
147  enddo
148  enddo
149  enddo
150 end subroutine dense_water_initialize_ts
151 
152 !> Initialize the restoring sponges for the dense water experiment
153 subroutine dense_water_initialize_sponges(G, GV, tv, param_file, use_ALE, CSp, ACSp)
154  type(ocean_grid_type), intent(in) :: g !< Horizontal grid control structure
155  type(verticalgrid_type), intent(in) :: gv !< Vertical grid control structure
156  type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic variables
157  type(param_file_type), intent(in) :: param_file !< Parameter file structure
158  logical, intent(in) :: use_ale !< ALE flag
159  type(sponge_cs), pointer :: csp !< Layered sponge control structure pointer
160  type(ale_sponge_cs), pointer :: acsp !< ALE sponge control structure pointer
161  ! Local variables
162  real :: west_sponge_time_scale, west_sponge_width
163  real :: east_sponge_time_scale, east_sponge_width
164 
165  real, dimension(SZI_(G),SZJ_(G)) :: idamp ! inverse damping timescale
166  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)) :: h, t, s ! sponge thicknesses, temp and salt
167  real, dimension(SZK_(GV)+1) :: e0, eta1d ! interface positions for ALE sponge
168 
169  integer :: i, j, k, nz
170  real :: x, zi, zmid, dist
171  real :: mld, s_ref, s_range, s_dense, t_ref, sill_height
172 
173  nz = gv%ke
174 
175  call get_param(param_file, mdl, "DENSE_WATER_WEST_SPONGE_TIME_SCALE", west_sponge_time_scale, &
176  "The time scale on the west (outflow) of the domain for restoring. If zero, the sponge is disabled.", &
177  units="s", default=0.)
178  call get_param(param_file, mdl, "DENSE_WATER_WEST_SPONGE_WIDTH", west_sponge_width, &
179  "The fraction of the domain in which the western (outflow) sponge is active.", &
180  units="nondim", default=0.1)
181  call get_param(param_file, mdl, "DENSE_WATER_EAST_SPONGE_TIME_SCALE", east_sponge_time_scale, &
182  "The time scale on the east (outflow) of the domain for restoring. If zero, the sponge is disabled.", &
183  units="s", default=0.)
184  call get_param(param_file, mdl, "DENSE_WATER_EAST_SPONGE_WIDTH", east_sponge_width, &
185  "The fraction of the domain in which the eastern (outflow) sponge is active.", &
186  units="nondim", default=0.1)
187 
188  call get_param(param_file, mdl, "DENSE_WATER_EAST_SPONGE_SALT", s_dense, &
189  "Salt anomaly of the dense water being formed in the overflow region.", &
190  units="1e-3", default=4.0)
191 
192  call get_param(param_file, mdl, "DENSE_WATER_MLD", mld, default=default_mld, do_not_log=.true.)
193  call get_param(param_file, mdl, "DENSE_WATER_SILL_HEIGHT", sill_height, default=default_sill, do_not_log=.true.)
194 
195  call get_param(param_file, mdl, "S_REF", s_ref, do_not_log=.true.)
196  call get_param(param_file, mdl, "S_RANGE", s_range, do_not_log=.true.)
197  call get_param(param_file, mdl, "T_REF", t_ref, do_not_log=.true.)
198 
199  ! no active sponges
200  if (west_sponge_time_scale <= 0. .and. east_sponge_time_scale <= 0.) return
201 
202  ! everywhere is initially unsponged
203  idamp(:,:) = 0.0
204 
205  do j = g%jsc, g%jec
206  do i = g%isc,g%iec
207  if (g%mask2dT(i,j) > 0.) then
208  ! nondimensional x position
209  x = (g%geoLonT(i,j) - g%west_lon) / g%len_lon
210 
211  if (west_sponge_time_scale > 0. .and. x < west_sponge_width) then
212  dist = 1. - x / west_sponge_width
213  ! scale restoring by depth into sponge
214  idamp(i,j) = 1. / west_sponge_time_scale * max(0., min(1., dist))
215  elseif (east_sponge_time_scale > 0. .and. x > (1. - east_sponge_width)) then
216  dist = 1. - (1. - x) / east_sponge_width
217  idamp(i,j) = 1. / east_sponge_time_scale * max(0., min(1., dist))
218  endif
219  endif
220  enddo
221  enddo
222 
223  if (use_ale) then
224  ! construct a uniform grid for the sponge
225  do k = 1,nz
226  e0(k) = -g%max_depth * (real(k - 1) / real(nz))
227  enddo
228  e0(nz+1) = -g%max_depth
229 
230  do j = g%jsc,g%jec
231  do i = g%isc,g%iec
232  eta1d(nz+1) = -g%bathyT(i,j)
233  do k = nz,1,-1
234  eta1d(k) = e0(k)
235 
236  if (eta1d(k) < (eta1d(k+1) + gv%Angstrom_Z)) then
237  ! is this layer vanished?
238  eta1d(k) = eta1d(k+1) + gv%Angstrom_Z
239  h(i,j,k) = gv%Angstrom_H
240  else
241  h(i,j,k) = gv%Z_to_H * (eta1d(k) - eta1d(k+1))
242  endif
243  enddo
244  enddo
245  enddo
246 
247  call initialize_ale_sponge(idamp, g, param_file, acsp, h, nz)
248 
249  ! construct temperature and salinity for the sponge
250  ! start with initial condition
251  t(:,:,:) = t_ref
252  s(:,:,:) = s_ref
253 
254  do j = g%jsc,g%jec
255  do i = g%isc,g%iec
256  zi = 0.
257  x = (g%geoLonT(i,j) - g%west_lon) / g%len_lon
258  do k = 1,nz
259  ! nondimensional middle of layer
260  zmid = zi + 0.5 * h(i,j,k) / (gv%Z_to_H * g%max_depth)
261 
262  if (x > (1. - east_sponge_width)) then
263  !if (zmid >= 0.9 * sill_height) &
264  s(i,j,k) = s_ref + s_dense
265  else
266  ! linear between bottom of mixed layer and bottom
267  if (zmid >= mld) &
268  s(i,j,k) = s_ref + s_range * (zmid - mld) / (1.0 - mld)
269  endif
270 
271  zi = zi + h(i,j,k) / (gv%Z_to_H * g%max_depth)
272  enddo
273  enddo
274  enddo
275 
276  if (associated(tv%T)) call set_up_ale_sponge_field(t, g, tv%T, acsp)
277  if (associated(tv%S)) call set_up_ale_sponge_field(s, g, tv%S, acsp)
278  else
279  call mom_error(fatal, "dense_water_initialize_sponges: trying to use non ALE sponge")
280  endif
281 end subroutine dense_water_initialize_sponges
282 
284 
285 !> \namespace dense_water_initialization
286 !!
287 !! This experiment consists of a shelf accumulating dense water, which spills
288 !! over an upward slope and a sill, before flowing down a slope into an open
289 !! ocean region. It's intended as a test of one of the motivating situations
290 !! for the adaptive coordinate.
291 !!
292 !! The nondimensional widths of the 5 regions are controlled by the
293 !! <code>DENSE_WATER_DOMAIN_PARAMS</code>, and the heights of the sill and shelf
294 !! as a fraction of the total domain depth are controlled by
295 !! <code>DENSE_WATER_SILL_HEIGHT</code> and <code>DENSE_WATER_SHELF_HEIGHT</code>.
296 !!
297 !! The density in the domain is governed by a linear equation of state, and
298 !! is set up with a mixed layer of non-dimensional depth <code>DENSE_WATER_MLD</code>
299 !! below which there is a linear stratification from <code>S_REF</code>, increasing
300 !! by <code>S_RANGE</code> to the bottom.
301 !!
302 !! To force the experiment, there are sponges on the inflow and outflow of the
303 !! domain. The inflow sponge has a salinity anomaly of
304 !! <code>DENSE_WATER_EAST_SPONGE_SALT</code> through the entire depth. The outflow
305 !! sponge simply restores to the initial condition. Both sponges have controllable
306 !! widths and restoring timescales.
mom_verticalgrid
Provides a transparent vertical ocean grid type and supporting routines.
Definition: MOM_verticalGrid.F90:2
mom_variables::thermo_var_ptrs
Pointers to an assortment of thermodynamic fields that may be available, including potential temperat...
Definition: MOM_variables.F90:82
mom_ale_sponge::initialize_ale_sponge
Ddetermine the number of points which are within sponges in this computational domain.
Definition: MOM_ALE_sponge.F90:49
mom_dyn_horgrid
Contains a shareable dynamic type for describing horizontal grids and metric data and utilty routines...
Definition: MOM_dyn_horgrid.F90:3
mom_ale_sponge::ale_sponge_cs
ALE sponge control structure.
Definition: MOM_ALE_sponge.F90:85
mom_eos
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_ale_sponge
This module contains the routines used to apply sponge layers when using the ALE mode.
Definition: MOM_ALE_sponge.F90:11
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
mom_eos::eos_type
A control structure for the equation of state.
Definition: MOM_EOS.F90:86
dense_water_initialization
Initialization routines for the dense water formation and overflow experiment.
Definition: dense_water_initialization.F90:3
mom_ale_sponge::set_up_ale_sponge_field
Store the reference profile at h points for a variable.
Definition: MOM_ALE_sponge.F90:34
mom_verticalgrid::verticalgrid_type
Describes the vertical ocean grid, including unit conversion factors.
Definition: MOM_verticalGrid.F90:24
mom_variables
Provides transparent structures with groups of MOM6 variables and supporting routines.
Definition: MOM_variables.F90:2
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_sponge
Implements sponge regions in isopycnal mode.
Definition: MOM_sponge.F90:2
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_sponge::sponge_cs
This control structure holds memory and parameters for the MOM_sponge module.
Definition: MOM_sponge.F90:40
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom_dyn_horgrid::dyn_horgrid_type
Describes the horizontal ocean grid with only dynamic memory arrays.
Definition: MOM_dyn_horgrid.F90:22
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25