MOM6
sloshing_initialization.F90
1 !> Initialization for the "sloshing" internal waves configuration.
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 use mom_domains, only : sum_across_pes
8 use mom_error_handler, only : mom_mesg, mom_error, fatal, is_root_pe
10 use mom_get_input, only : directories
11 use mom_grid, only : ocean_grid_type
12 use mom_sponge, only : set_up_sponge_field, initialize_sponge, sponge_cs
18 
19 implicit none ; private
20 
21 #include <MOM_memory.h>
22 
23 ! The following routines are visible to the outside world
24 public sloshing_initialize_topography
25 public sloshing_initialize_thickness
26 public sloshing_initialize_temperature_salinity
27 
28 contains
29 
30 !> Initialization of topography.
31 subroutine sloshing_initialize_topography( D, G, param_file, max_depth )
32  type(dyn_horgrid_type), intent(in) :: g !< The dynamic horizontal grid type
33  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
34  intent(out) :: d !< Ocean bottom depth in the units of depth_max
35  type(param_file_type), intent(in) :: param_file !< Parameter file structure
36  real, intent(in) :: max_depth !< Maximum ocean depth in arbitrary units
37 
38  ! Local variables
39  integer :: i, j
40 
41  do i=g%isc,g%iec ; do j=g%jsc,g%jec
42  d(i,j) = max_depth
43  enddo ; enddo
44 
45 end subroutine sloshing_initialize_topography
46 
47 
48 !> Initialization of thicknesses
49 !! This routine is called when THICKNESS_CONFIG is set to 'sloshing'
50 !!
51 !! This routine initializes layer positions to set off a sloshing motion in
52 !! the zonal direction in a rectangular basin. All layers have initially the
53 !! same thickness but all interfaces (except bottom and sea surface) are
54 !! displaced according to a half-period cosine, with maximum value on the
55 !! left and minimum value on the right. This sets off a regular sloshing motion.
56 subroutine sloshing_initialize_thickness ( h, G, GV, US, param_file, just_read_params)
57  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure.
58  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure.
59  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
60  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
61  intent(out) :: h !< The thickness that is being initialized [H ~> m or kg m-2].
62  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file
63  !! to parse for model parameter values.
64  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
65  !! only read parameters without changing h.
66 
67  real :: displ(szk_(g)+1) ! The interface displacement in depth units.
68  real :: z_unif(szk_(g)+1) ! Fractional uniform interface heights [nondim].
69  real :: z_inter(szk_(g)+1) ! Interface heights, in depth units.
70  real :: a0 ! The displacement amplitude in depth units.
71  real :: weight_z ! A (misused?) depth-space weighting, in inconsistent units.
72  real :: x1, y1, x2, y2 ! Dimensonless parameters.
73  real :: x, t ! Dimensionless depth coordinates?
74  logical :: use_ic_bug ! If true, set the initial conditions retaining an old bug.
75  logical :: just_read ! If true, just read parameters but set nothing.
76  ! This include declares and sets the variable "version".
77 # include "version_variable.h"
78  character(len=40) :: mdl = "sloshing_initialization" !< This module's name.
79 
80  integer :: i, j, k, is, ie, js, je, nx, nz
81 
82  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
83 
84  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
85  if (.not.just_read) call log_version(param_file, mdl, version, "")
86  call get_param(param_file, mdl, "SLOSHING_IC_AMPLITUDE", a0, &
87  "Initial amplitude of sloshing internal interface height "//&
88  "displacements it the sloshing test case.", &
89  units='m', default=75.0, scale=us%m_to_Z, do_not_log=just_read)
90  call get_param(param_file, mdl, "SLOSHING_IC_BUG", use_ic_bug, &
91  "If true, use code with a bug to set the sloshing initial conditions.", &
92  default=.true., do_not_log=just_read)
93 
94  if (just_read) return ! All run-time parameters have been read, so return.
95 
96  ! Define thicknesses
97  do j=g%jsc,g%jec ; do i=g%isc,g%iec
98 
99  ! Define uniform interfaces
100  do k = 0,nz
101  z_unif(k+1) = -real(k)/real(nz)
102  enddo
103 
104  ! 1. Define stratification
105  do k = 1,nz+1
106 
107  ! Thin pycnocline in the middle
108  !z_inter(k) = (2.0**(n-1)) * (z_unif(k) + 0.5)**n - 0.5
109 
110  ! Thin pycnocline in the middle (piecewise linear profile)
111  x1 = 0.30; y1 = 0.48; x2 = 0.70; y2 = 0.52
112 
113  x = -z_unif(k)
114 
115  if ( x <= x1 ) then
116  t = y1*x/x1
117  elseif ( (x > x1 ) .and. ( x < x2 )) then
118  t = y1 + (y2-y1) * (x-x1) / (x2-x1)
119  else
120  t = y2 + (1.0-y2) * (x-x2) / (1.0-x2)
121  endif
122 
123  t = - z_unif(k)
124 
125  z_inter(k) = -t * g%max_depth
126 
127  enddo
128 
129  ! 2. Define displacement
130  ! a0 is set via get_param; by default a0 is a 75m Displacement amplitude in depth units.
131  do k = 1,nz+1
132 
133  weight_z = - 4.0 * ( z_unif(k) + 0.5 )**2 + 1.0
134 
135  x = g%geoLonT(i,j) / g%len_lon
136  if (use_ic_bug) then
137  displ(k) = a0 * cos(acos(-1.0)*x) + weight_z * us%m_to_Z
138  else
139  displ(k) = a0 * cos(acos(-1.0)*x) * weight_z
140  endif
141 
142  if ( k == 1 ) then
143  displ(k) = 0.0
144  endif
145 
146  if ( k == nz+1 ) then
147  displ(k) = 0.0
148  endif
149 
150  z_inter(k) = z_inter(k) + displ(k)
151 
152  enddo
153 
154  ! 3. The last interface must coincide with the seabed
155  z_inter(nz+1) = -g%bathyT(i,j)
156  ! Modify interface heights to make sure all thicknesses are strictly positive
157  do k = nz,1,-1
158  if ( z_inter(k) < (z_inter(k+1) + gv%Angstrom_Z) ) then
159  z_inter(k) = z_inter(k+1) + gv%Angstrom_Z
160  endif
161  enddo
162 
163  ! 4. Define layers
164  do k = 1,nz
165  h(i,j,k) = gv%Z_to_H * (z_inter(k) - z_inter(k+1))
166  enddo
167 
168  enddo ; enddo
169 
170 end subroutine sloshing_initialize_thickness
171 
172 
173 !> Initialization of temperature and salinity
174 !!
175 !! This subroutine initializes linear profiles for T and S according to
176 !! reference surface layer salinity and temperature and a specified range.
177 !! Note that the linear distribution is set up with respect to the layer
178 !! number, not the physical position).
179 subroutine sloshing_initialize_temperature_salinity ( T, S, h, G, GV, param_file, &
180  eqn_of_state, just_read_params)
181  type(ocean_grid_type), intent(in) :: g !< Ocean grid structure.
182  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure.
183  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: t !< Potential temperature [degC].
184  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: s !< Salinity [ppt].
185  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(in) :: h !< Layer thickness [H ~> m or kg m-2].
186  type(param_file_type), intent(in) :: param_file !< A structure indicating the
187  !! open file to parse for model
188  !! parameter values.
189  type(eos_type), pointer :: eqn_of_state !< Equation of state structure.
190  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
191  !! only read parameters without changing h.
192 
193  integer :: i, j, k, is, ie, js, je, nz
194  real :: delta_s, delta_t
195  real :: s_ref, t_ref; ! Reference salinity and temerature within
196  ! surface layer
197  real :: s_range, t_range; ! Range of salinities and temperatures over the
198  ! vertical
199  integer :: kdelta
200  real :: deltah
201  real :: xi0, xi1
202  logical :: just_read ! If true, just read parameters but set nothing.
203  character(len=40) :: mdl = "initialize_temp_salt_linear" ! This subroutine's
204  ! name.
205 
206  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
207 
208  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
209 
210  call get_param(param_file, mdl,"S_REF",s_ref,'Reference value for salinity', &
211  units='1e-3', fail_if_missing=.not.just_read, do_not_log=just_read)
212  call get_param(param_file, mdl,"T_REF",t_ref,'Refernce value for temperature', &
213  units='C', fail_if_missing=.not.just_read, do_not_log=just_read)
214 
215  ! The default is to assume an increase by 2 for the salinity and a uniform
216  ! temperature
217  call get_param(param_file, mdl,"S_RANGE",s_range,'Initial salinity range.', &
218  units='1e-3', default=2.0, do_not_log=just_read)
219  call get_param(param_file, mdl,"T_RANGE",t_range,'Initial temperature range', &
220  units='C', default=0.0, do_not_log=just_read)
221 
222  if (just_read) return ! All run-time parameters have been read, so return.
223 
224  ! Prescribe salinity
225  !delta_S = S_range / ( G%ke - 1.0 )
226 
227  !S(:,:,1) = S_ref
228  !do k = 2,G%ke
229  ! S(:,:,k) = S(:,:,k-1) + delta_S
230  !enddo
231 
232  deltah = g%max_depth / nz
233  do j=js,je ; do i=is,ie
234  xi0 = 0.0
235  do k = 1,nz
236  xi1 = xi0 + deltah / g%max_depth ! = xi0 + 1.0 / real(nz)
237  s(i,j,k) = 34.0 + 0.5 * s_range * (xi0 + xi1)
238  xi0 = xi1
239  enddo
240  enddo ; enddo
241 
242  ! Prescribe temperature
243  delta_t = t_range / ( g%ke - 1.0 )
244 
245  t(:,:,1) = t_ref
246  do k = 2,g%ke
247  t(:,:,k) = t(:,:,k-1) + delta_t
248  enddo
249  kdelta = 2
250  t(:,:,g%ke/2 - (kdelta-1):g%ke/2 + kdelta) = 1.0
251 
252 end subroutine sloshing_initialize_temperature_salinity
253 
254 !> \namespace sloshing_initialization
255 !!
256 !! The module configures the model for the non-rotating sloshing test case.
257 end module sloshing_initialization
mom_verticalgrid
Provides a transparent vertical ocean grid type and supporting routines.
Definition: MOM_verticalGrid.F90:2
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
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_get_input::directories
Container for paths and parameter file names.
Definition: MOM_get_input.F90:20
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_eos
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
mom_tracer_registry
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
Definition: MOM_tracer_registry.F90:5
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_get_input
Reads the only Fortran name list needed to boot-strap the model.
Definition: MOM_get_input.F90:6
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
mom_verticalgrid::verticalgrid_type
Describes the vertical ocean grid, including unit conversion factors.
Definition: MOM_verticalGrid.F90:24
mom_domains
Describes the decomposed MOM domain and has routines for communications across PEs.
Definition: MOM_domains.F90:2
mom_variables
Provides transparent structures with groups of MOM6 variables and supporting routines.
Definition: MOM_variables.F90:2
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
sloshing_initialization
Initialization for the "sloshing" internal waves configuration.
Definition: sloshing_initialization.F90:2
mom_eos::calculate_density_derivs
Calculate the derivatives of density with temperature and salinity from T, S, and P.
Definition: MOM_EOS.F90:70
mom_tracer_registry::tracer_registry_type
Type to carry basic tracer information.
Definition: MOM_tracer_registry.F90:122
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
mom_eos::calculate_density
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:60