MOM6
shelfwave_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
24 use mom_error_handler, only : mom_mesg, mom_error, fatal, warning, is_root_pe
26 use mom_grid, only : ocean_grid_type
30 use mom_time_manager, only : time_type, set_time, time_type_to_real
31 
32 implicit none ; private
33 
34 #include <MOM_memory.h>
35 
36 character(len=40) :: mdl = "shelfwave_initialization" ! This module's name.
37 
38 ! -----------------------------------------------------------------------------
39 ! The following routines are visible to the outside world
40 ! -----------------------------------------------------------------------------
44 
45 !> Control structure for shelfwave open boundaries.
46 type, public :: shelfwave_obc_cs ; private
47  real :: lx = 100.0 !< Long-shore length scale of bathymetry.
48  real :: ly = 50.0 !< Cross-shore length scale.
49  real :: f0 = 1.e-4 !< Coriolis parameter.
50  real :: jj = 1 !< Cross-shore wave mode.
51  real :: kk !< Parameter.
52  real :: ll !< Longshore wavenumber.
53  real :: alpha !< 1/Ly.
54  real :: omega !< Frequency.
55 end type shelfwave_obc_cs
56 
57 contains
58 
59 !> Add shelfwave to OBC registry.
60 function register_shelfwave_obc(param_file, CS, OBC_Reg)
61  type(param_file_type), intent(in) :: param_file !< parameter file.
62  type(shelfwave_obc_cs), pointer :: CS !< shelfwave control structure.
63  type(obc_registry_type), pointer :: OBC_Reg !< OBC registry.
64  logical :: register_shelfwave_OBC
65  ! Local variables
66  real :: kk, ll, PI, len_lat
67 
68  character(len=32) :: casename = "shelfwave" !< This case's name.
69 
70  pi = 4.0*atan(1.0)
71 
72  if (associated(cs)) then
73  call mom_error(warning, "register_shelfwave_OBC called with an "// &
74  "associated control structure.")
75  return
76  endif
77  allocate(cs)
78 
79  ! Register the tracer for horizontal advection & diffusion.
80  call register_obc(casename, param_file, obc_reg)
81  call get_param(param_file, mdl,"F_0",cs%f0, &
82  do_not_log=.true.)
83  call get_param(param_file, mdl,"LENLAT",len_lat, &
84  do_not_log=.true.)
85  call get_param(param_file, mdl,"SHELFWAVE_X_WAVELENGTH",cs%Lx, &
86  "Length scale of shelfwave in x-direction.",&
87  units="Same as x,y", default=100.)
88  call get_param(param_file, mdl,"SHELFWAVE_Y_LENGTH_SCALE",cs%Ly, &
89  "Length scale of exponential dropoff of topography\n"//&
90  "in the y-direction.", &
91  units="Same as x,y", default=50.)
92  call get_param(param_file, mdl,"SHELFWAVE_Y_MODE",cs%jj, &
93  "Cross-shore wave mode.", &
94  units="nondim", default=1.)
95  cs%alpha = 1. / cs%Ly
96  cs%ll = 2. * pi / cs%Lx
97  cs%kk = cs%jj * pi / len_lat
98  cs%omega = 2 * cs%alpha * cs%f0 * cs%ll / &
99  (cs%kk*cs%kk + cs%alpha*cs%alpha + cs%ll*cs%ll)
100  register_shelfwave_obc = .true.
101 
102 end function register_shelfwave_obc
103 
104 !> Clean up the shelfwave OBC from registry.
105 subroutine shelfwave_obc_end(CS)
106  type(shelfwave_obc_cs), pointer :: CS !< shelfwave control structure.
107 
108  if (associated(cs)) then
109  deallocate(cs)
110  endif
111 end subroutine shelfwave_obc_end
112 
113 !> Initialization of topography.
114 subroutine shelfwave_initialize_topography ( D, G, param_file, max_depth )
115  ! Arguments
116  type(dyn_horgrid_type), intent(in) :: G !< The dynamic horizontal grid type
117  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
118  intent(out) :: D !< Ocean bottom depth in m
119  type(param_file_type), intent(in) :: param_file !< Parameter file structure
120  real, intent(in) :: max_depth !< Maximum depth of model in m
121 
122  ! Local variables
123  integer :: i, j
124  real :: y, rLy, Ly, H0
125 
126  call get_param(param_file, mdl,"SHELFWAVE_Y_LENGTH_SCALE",ly, &
127  default=50., do_not_log=.true.)
128  call get_param(param_file, mdl,"MINIMUM_DEPTH",h0, &
129  default=10., do_not_log=.true.)
130 
131  rly = 0. ; if (ly>0.) rly = 1. / ly
132  do i=g%isc,g%iec
133  do j=g%jsc,g%jec
134  ! Compute normalized zonal coordinates (x,y=0 at center of domain)
135  y = ( g%geoLatT(i,j) - g%south_lat )
136  d(i,j) = h0 * exp(2 * rly * y)
137  enddo
138  enddo
139 
140 end subroutine shelfwave_initialize_topography
141 
142 !> This subroutine sets the properties of flow at open boundary conditions.
143 subroutine shelfwave_set_obc_data(OBC, CS, G, h, Time)
144  type(ocean_obc_type), pointer :: OBC !< This open boundary condition type specifies
145  !! whether, where, and what open boundary
146  !! conditions are used.
147  type(shelfwave_obc_cs), pointer :: CS !< tidal bay control structure.
148  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
149  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< layer thickness.
150  type(time_type), intent(in) :: Time !< model time.
151 
152  ! The following variables are used to set up the transport in the tidal_bay example.
153  real :: my_amp, time_sec
154  real :: cos_wt, cos_ky, sin_wt, sin_ky, omega, alpha
155  real :: x, y, jj, kk, ll
156  character(len=40) :: mdl = "shelfwave_set_OBC_data" ! This subroutine's name.
157  integer :: i, j, k, is, ie, js, je, isd, ied, jsd, jed, n
158  integer :: IsdB, IedB, JsdB, JedB
159  type(obc_segment_type), pointer :: segment
160 
161  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
162  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
163  isdb = g%IsdB ; iedb = g%IedB ; jsdb = g%JsdB ; jedb = g%JedB
164 
165  if (.not.associated(obc)) return
166 
167  time_sec = time_type_to_real(time)
168  omega = cs%omega
169  alpha = cs%alpha
170  my_amp = 1.0
171  jj = cs%jj
172  kk = cs%kk
173  ll = cs%ll
174  do n = 1, obc%number_of_segments
175  segment => obc%segment(n)
176  if (.not. segment%on_pe) cycle
177  if (segment%direction /= obc_direction_w) cycle
178 
179  isdb = segment%HI%IsdB ; iedb = segment%HI%IedB
180  jsd = segment%HI%jsd ; jed = segment%HI%jed
181  do j=jsd,jed ; do i=isdb,iedb
182  x = g%geoLonCu(i,j) - g%west_lon
183  y = g%geoLatCu(i,j) - g%south_lat
184  sin_wt = sin(ll*x - omega*time_sec)
185  cos_wt = cos(ll*x - omega*time_sec)
186  sin_ky = sin(kk * y)
187  cos_ky = cos(kk * y)
188  segment%normal_vel_bt(i,j) = my_amp * exp(- alpha * y) * cos_wt * &
189  (alpha * sin_ky + kk * cos_ky)
190 ! segment%tangential_vel_bt(I,j) = my_amp * ll * exp(- alpha * y) * sin_wt * sin_ky
191 ! segment%vorticity_bt(I,j) = my_amp * exp(- alpha * y) * cos_wt * sin_ky&
192 ! (ll*ll + kk*kk + alpha*alpha)
193  enddo ; enddo
194  enddo
195 
196 end subroutine shelfwave_set_obc_data
197 
198 !> \namespace shelfwave_initialization
199 !!
200 !! The module configures the model for the idealized shelfwave
201 !! test case.
202 end module shelfwave_initialization
integer, parameter, public obc_direction_w
Indicates the boundary is an effective western boundary.
subroutine, public shelfwave_obc_end(CS)
Clean up the shelfwave OBC from registry.
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Provides the ocean grid type.
Definition: MOM_grid.F90:2
Open boundary segment data structure.
subroutine, public register_obc(name, param_file, Reg)
register open boundary objects for boundary updates.
subroutine, public shelfwave_set_obc_data(OBC, CS, G, h, Time)
This subroutine sets the properties of flow at open boundary conditions.
The module configures the model for the idealized shelfwave test case.
Type to carry basic OBC information needed for updating values.
logical function, public is_root_pe()
logical function, public register_shelfwave_obc(param_file, CS, OBC_Reg)
Add shelfwave to OBC registry.
subroutine, public mom_mesg(message, verb, all_print)
Control structure for shelfwave open boundaries.
subroutine, public shelfwave_initialize_topography(D, G, param_file, max_depth)
Initialization of topography.
integer, parameter, public obc_none
Controls where open boundary conditions are applied.
subroutine, public mom_error(level, message, all_print)