MOM6
seamount_initialization.F90
Go to the documentation of this file.
2 !***********************************************************************
3 !* GNU General Public License *
4 !* This file is a part of MOM. *
5 !* *
6 !* MOM is free software; you can redistribute it and/or modify it and *
7 !* are expected to follow the terms of the GNU General Public License *
8 !* as published by the Free Software Foundation; either version 2 of *
9 !* the License, or (at your option) any later version. *
10 !* *
11 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
12 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
13 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
14 !* License for more details. *
15 !* *
16 !* For the full text of the GNU General Public License, *
17 !* write to: Free Software Foundation, Inc., *
18 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
19 !* or see: http://www.gnu.org/licenses/gpl.html *
20 !***********************************************************************
21 
22 use mom_domains, only : sum_across_pes
26 use mom_get_input, only : directories
27 use mom_grid, only : ocean_grid_type
28 use mom_io, only : close_file, fieldtype, file_exists
29 use mom_io, only : open_file, read_data, read_axis_data, single_file
30 use mom_io, only : write_field, slasher, vardesc
39 
40 implicit none ; private
41 
42 #include <MOM_memory.h>
43 
44 character(len=40) :: mdl = "seamount_initialization" ! This module's name.
45 
46 ! -----------------------------------------------------------------------------
47 ! The following routines are visible to the outside world
48 ! -----------------------------------------------------------------------------
52 
53 ! -----------------------------------------------------------------------------
54 ! This module contains the following routines
55 ! -----------------------------------------------------------------------------
56 contains
57 
58 !> Initialization of topography.
59 subroutine seamount_initialize_topography ( D, G, param_file, max_depth )
60  ! Arguments
61  type(dyn_horgrid_type), intent(in) :: G !< The dynamic horizontal grid type
62  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
63  intent(out) :: D !< Ocean bottom depth in m
64  type(param_file_type), intent(in) :: param_file !< Parameter file structure
65  real, intent(in) :: max_depth !< Maximum depth of model in m
66 
67  ! Local variables
68  integer :: i, j
69  real :: x, y, delta, Lx, rLx, Ly, rLy
70 
71  call get_param(param_file, mdl,"SEAMOUNT_DELTA",delta, &
72  "Non-dimensional height of seamount.", &
73  units="non-dim", default=0.5)
74  call get_param(param_file, mdl,"SEAMOUNT_X_LENGTH_SCALE",lx, &
75  "Length scale of seamount in x-direction.\n"//&
76  "Set to zero make topography uniform in the x-direction.", &
77  units="Same as x,y", default=20.)
78  call get_param(param_file, mdl,"SEAMOUNT_Y_LENGTH_SCALE",ly, &
79  "Length scale of seamount in y-direction.\n"//&
80  "Set to zero make topography uniform in the y-direction.", &
81  units="Same as x,y", default=0.)
82 
83  lx = lx / g%len_lon
84  ly = ly / g%len_lat
85  rlx = 0. ; if (lx>0.) rlx = 1. / lx
86  rly = 0. ; if (ly>0.) rly = 1. / ly
87  do i=g%isc,g%iec
88  do j=g%jsc,g%jec
89  ! Compute normalized zonal coordinates (x,y=0 at center of domain)
90  x = ( g%geoLonT(i,j) - g%west_lon ) / g%len_lon - 0.5
91  y = ( g%geoLatT(i,j) - g%south_lat ) / g%len_lat - 0.5
92  d(i,j) = g%max_depth * ( 1.0 - delta * exp(-(rlx*x)**2 -(rly*y)**2) )
93  enddo
94  enddo
95 
96 end subroutine seamount_initialize_topography
97 
98 !> Initialization of thicknesses.
99 !! This subroutine initializes the layer thicknesses to be uniform.
100 subroutine seamount_initialize_thickness ( h, G, GV, param_file, just_read_params)
101  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
102  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
103  real, dimension(SZI_(G),SZJ_(G),SZK_(GV)), &
104  intent(out) :: h !< The thickness that is being initialized, in m.
105  type(param_file_type), intent(in) :: param_file !< A structure indicating the open file
106  !! to parse for model parameter values.
107  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
108  !! only read parameters without changing h.
109 
110  real :: e0(szk_(g)+1) ! The resting interface heights, in m, usually !
111  ! negative because it is positive upward. !
112  real :: eta1D(szk_(g)+1)! Interface height relative to the sea surface !
113  ! positive upward, in m. !
114  integer :: i, j, k, is, ie, js, je, nz
115  real :: x
116  real :: delta_h
117  real :: min_thickness, S_surf, S_range, S_ref, S_light, S_dense
118  character(len=20) :: verticalCoordinate
119  logical :: just_read ! If true, just read parameters but set nothing. character(len=20) :: verticalCoordinate
120 
121  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
122 
123  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
124 
125  if (.not.just_read) &
126  call mom_mesg("MOM_initialization.F90, initialize_thickness_uniform: setting thickness")
127 
128  call get_param(param_file, mdl,"MIN_THICKNESS",min_thickness, &
129  'Minimum thickness for layer',&
130  units='m', default=1.0e-3, do_not_log=just_read)
131  call get_param(param_file, mdl,"REGRIDDING_COORDINATE_MODE",verticalcoordinate, &
132  default=default_coordinate_mode, do_not_log=just_read)
133 
134  ! WARNING: this routine specifies the interface heights so that the last layer
135  ! is vanished, even at maximum depth. In order to have a uniform
136  ! layer distribution, use this line of code within the loop:
137  ! e0(k) = -G%max_depth * real(k-1) / real(nz)
138  ! To obtain a thickness distribution where the last layer is
139  ! vanished and the other thicknesses uniformly distributed, use:
140  ! e0(k) = -G%max_depth * real(k-1) / real(nz-1)
141  !do k=1,nz+1
142  ! e0(k) = -G%max_depth * real(k-1) / real(nz)
143  !enddo
144 
145  select case ( coordinatemode(verticalcoordinate) )
146 
147  case ( regridding_layer, regridding_rho ) ! Initial thicknesses for isopycnal coordinates
148  call get_param(param_file, mdl,"INITIAL_SSS", s_surf, default=34., do_not_log=.true.)
149  call get_param(param_file, mdl,"INITIAL_S_RANGE", s_range, default=2., do_not_log=.true.)
150  call get_param(param_file, mdl, "S_REF", s_ref, default=35.0, do_not_log=.true.)
151  call get_param(param_file, mdl, "TS_RANGE_S_LIGHT", s_light, default = s_ref, do_not_log=.true.)
152  call get_param(param_file, mdl, "TS_RANGE_S_DENSE", s_dense, default = s_ref, do_not_log=.true.)
153  if (just_read) return ! All run-time parameters have been read, so return.
154 
155  do k=1,nz+1
156  ! Salinity of layer k is S_light + (k-1)/(nz-1) * (S_dense - S_light)
157  ! Salinity of interface K is S_light + (K-3/2)/(nz-1) * (S_dense - S_light)
158  ! Salinity at depth z should be S(z) = S_surf - S_range * z/max_depth
159  ! Equating: S_surf - S_range * z/max_depth = S_light + (K-3/2)/(nz-1) * (S_dense - S_light)
160  ! Equating: - S_range * z/max_depth = S_light - S_surf + (K-3/2)/(nz-1) * (S_dense - S_light)
161  ! Equating: z/max_depth = - ( S_light - S_surf + (K-3/2)/(nz-1) * (S_dense - S_light) ) / S_range
162  e0(k) = - g%max_depth * ( ( s_light - s_surf ) + ( s_dense - s_light ) * ( (real(k)-1.5) / real(nz-1) ) ) / s_range
163  e0(k) = nint(2048.*e0(k))/2048. ! Force round numbers ... the above expression has irrational factors ...
164  e0(k) = min(real(1-k)*GV%Angstrom_z, e0(k)) ! Bound by surface
165  e0(k) = max(-g%max_depth, e0(k)) ! Bound by bottom
166  enddo
167  do j=js,je ; do i=is,ie
168  eta1d(nz+1) = -1.0*g%bathyT(i,j)
169  do k=nz,1,-1
170  eta1d(k) = e0(k)
171  if (eta1d(k) < (eta1d(k+1) + gv%Angstrom_z)) then
172  eta1d(k) = eta1d(k+1) + gv%Angstrom_z
173  h(i,j,k) = gv%Angstrom_z
174  else
175  h(i,j,k) = eta1d(k) - eta1d(k+1)
176  endif
177  enddo
178  enddo ; enddo
179 
180  case ( regridding_zstar ) ! Initial thicknesses for z coordinates
181  if (just_read) return ! All run-time parameters have been read, so return.
182  do j=js,je ; do i=is,ie
183  eta1d(nz+1) = -1.0*g%bathyT(i,j)
184  do k=nz,1,-1
185  eta1d(k) = -g%max_depth * real(k-1) / real(nz)
186  if (eta1d(k) < (eta1d(k+1) + min_thickness)) then
187  eta1d(k) = eta1d(k+1) + min_thickness
188  h(i,j,k) = min_thickness
189  else
190  h(i,j,k) = eta1d(k) - eta1d(k+1)
191  endif
192  enddo
193  enddo ; enddo
194 
195  case ( regridding_sigma ) ! Initial thicknesses for sigma coordinates
196  if (just_read) return ! All run-time parameters have been read, so return.
197  do j=js,je ; do i=is,ie
198  delta_h = g%bathyT(i,j) / dfloat(nz)
199  h(i,j,:) = delta_h
200  end do ; end do
201 
202 end select
203 
204 end subroutine seamount_initialize_thickness
205 
206 !> Initial values for temperature and salinity
207 subroutine seamount_initialize_temperature_salinity ( T, S, h, G, GV, param_file, &
208  eqn_of_state, just_read_params)
209  type(ocean_grid_type), intent(in) :: G !< Ocean grid structure
210  type(verticalgrid_type), intent(in) :: GV !< Vertical grid structure
211  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: T !< Potential temperature (degC)
212  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(out) :: S !< Salinity (ppt)
213  real, dimension(SZI_(G),SZJ_(G), SZK_(G)), intent(in) :: h !< Layer thickness (m or Pa)
214  type(param_file_type), intent(in) :: param_file !< Parameter file structure
215  type(eos_type), pointer :: eqn_of_state !< Equation of state structure
216  logical, optional, intent(in) :: just_read_params !< If present and true, this call will
217  !! only read parameters without changing h.
218 
219  ! Local variables
220  integer :: i, j, k, is, ie, js, je, nz, k_light
221  real :: xi0, xi1, dxi, r, S_surf, T_surf, S_range, T_range
222  real :: T_ref, T_Light, T_Dense, S_ref, S_Light, S_Dense, a1, frac_dense, k_frac, res_rat
223  logical :: just_read ! If true, just read parameters but set nothing.
224  character(len=20) :: verticalCoordinate, density_profile
225 
226  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; nz = g%ke
227 
228  just_read = .false. ; if (present(just_read_params)) just_read = just_read_params
229 
230  call get_param(param_file, mdl, "REGRIDDING_COORDINATE_MODE", verticalcoordinate, &
231  default=default_coordinate_mode, do_not_log=just_read)
232  call get_param(param_file, mdl,"INITIAL_DENSITY_PROFILE", density_profile, &
233  'Initial profile shape. Valid values are "linear", "parabolic"\n'// &
234  'and "exponential".', default='linear', do_not_log=just_read)
235  call get_param(param_file, mdl,"INITIAL_SSS", s_surf, &
236  'Initial surface salinity', units='1e-3', default=34., do_not_log=just_read)
237  call get_param(param_file, mdl,"INITIAL_SST", t_surf, &
238  'Initial surface temperature', units='C', default=0., do_not_log=just_read)
239  call get_param(param_file, mdl,"INITIAL_S_RANGE", s_range, &
240  'Initial salinity range (bottom - surface)', units='1e-3', &
241  default=2., do_not_log=just_read)
242  call get_param(param_file, mdl,"INITIAL_T_RANGE", t_range, &
243  'Initial temperature range (bottom - surface)', units='C', &
244  default=0., do_not_log=just_read)
245 
246  select case ( coordinatemode(verticalcoordinate) )
247  case ( regridding_layer ) ! Initial thicknesses for layer isopycnal coordinates
248  ! These parameters are used in MOM_fixed_initialization.F90 when CONFIG_COORD="ts_range"
249  call get_param(param_file, mdl, "T_REF", t_ref, default=10.0, do_not_log=.true.)
250  call get_param(param_file, mdl, "TS_RANGE_T_LIGHT", t_light, default=t_ref, do_not_log=.true.)
251  call get_param(param_file, mdl, "TS_RANGE_T_DENSE", t_dense, default=t_ref, do_not_log=.true.)
252  call get_param(param_file, mdl, "S_REF", s_ref, default=35.0, do_not_log=.true.)
253  call get_param(param_file, mdl, "TS_RANGE_S_LIGHT", s_light, default = s_ref, do_not_log=.true.)
254  call get_param(param_file, mdl, "TS_RANGE_S_DENSE", s_dense, default = s_ref, do_not_log=.true.)
255  call get_param(param_file, mdl, "TS_RANGE_RESOLN_RATIO", res_rat, default=1.0, do_not_log=.true.)
256  if (just_read) return ! All run-time parameters have been read, so return.
257 
258  ! Emulate the T,S used in the "ts_range" coordinate configuration code
259  k_light = gv%nk_rho_varies + 1
260  do j=js,je ; do i=is,ie
261  t(i,j,k_light) = t_light ; s(i,j,k_light) = s_light
262  enddo ; enddo
263  a1 = 2.0 * res_rat / (1.0 + res_rat)
264  do k=k_light+1,nz
265  k_frac = real(k-k_light)/real(nz-k_light)
266  frac_dense = a1 * k_frac + (1.0 - a1) * k_frac**2
267  do j=js,je ; do i=is,ie
268  t(i,j,k) = frac_dense * (t_dense - t_light) + t_light
269  s(i,j,k) = frac_dense * (s_dense - s_light) + s_light
270  enddo ; enddo
271  enddo
272  case ( regridding_sigma, regridding_zstar, regridding_rho ) ! All other coordinate use FV initialization
273  if (just_read) return ! All run-time parameters have been read, so return.
274  do j=js,je ; do i=is,ie
275  xi0 = 0.0
276  do k = 1,nz
277  xi1 = xi0 + h(i,j,k) / g%max_depth
278  select case ( trim(density_profile) )
279  case ('linear')
280  !S(i,j,k) = S_surf + S_range * 0.5 * (xi0 + xi1)
281  s(i,j,k) = s_surf + ( 0.5 * s_range ) * (xi0 + xi1) ! Coded this way to reproduce old hard-coded answers
282  t(i,j,k) = t_surf + t_range * 0.5 * (xi0 + xi1)
283  case ('parabolic')
284  s(i,j,k) = s_surf + s_range * (2.0 / 3.0) * (xi1**3 - xi0**3) / (xi1 - xi0)
285  t(i,j,k) = t_surf + t_range * (2.0 / 3.0) * (xi1**3 - xi0**3) / (xi1 - xi0)
286  case ('exponential')
287  s(i,j,k) = s_surf + s_range * (exp(xi1/r)-exp(xi0/r)) / (xi1 - xi0)
288  t(i,j,k) = t_surf + t_range * (exp(xi1/r)-exp(xi0/r)) / (xi1 - xi0)
289  case default
290  call mom_error(fatal, 'Unknown value for "INITIAL_DENSITY_PROFILE"')
291  end select
292  xi0 = xi1
293  enddo
294  enddo ; enddo
295  end select
296 
298 
299 !> \namespace seamount_initialization
300 !!
301 !! The module configures the model for the idealized seamount
302 !! test case.
303 end module seamount_initialization
integer, parameter regridding_layer
Layer mode.
subroutine, public read_axis_data(filename, axis_name, var)
Definition: MOM_io.F90:424
integer function coordinatemode(string)
Parse a string parameter specifying the coordinate mode and return the appropriate enumerated integer...
integer, parameter regridding_sigma
Sigma coordinates.
subroutine, public seamount_initialize_topography(D, G, param_file, max_depth)
Initialization of topography.
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:45
Provides the ocean grid type.
Definition: MOM_grid.F90:2
character(len= *), parameter default_coordinate_mode
Default coordinate mode.
This module contains I/O framework code.
Definition: MOM_io.F90:2
This module contains the tracer_registry_type and the subroutines that handle registration of tracers...
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
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_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 seamount_initialize_thickness(h, G, GV, param_file, just_read_params)
Initialization of thicknesses. This subroutine initializes the layer thicknesses to be uniform...
logical function, public is_root_pe()
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
integer, parameter regridding_zstar
z* coordinates
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
Contains constants for interpreting input parameters that control regridding.
subroutine, public mom_error(level, message, all_print)
integer, parameter regridding_rho
Target interface densities.
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.
The module configures the model for the idealized seamount test case.
A control structure for the equation of state.
Definition: MOM_EOS.F90:55