MOM6
MOM_interface_heights.F90
Go to the documentation of this file.
1 !> The module calculates interface heights, including free surface height.
3 
4 !***********************************************************************
5 !* GNU General Public License *
6 !* This file is a part of MOM. *
7 !* *
8 !* MOM is free software; you can redistribute it and/or modify it and *
9 !* are expected to follow the terms of the GNU General Public License *
10 !* as published by the Free Software Foundation; either version 2 of *
11 !* the License, or (at your option) any later version. *
12 !* *
13 !* MOM is distributed in the hope that it will be useful, but WITHOUT *
14 !* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY *
15 !* or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public *
16 !* License for more details. *
17 !* *
18 !* For the full text of the GNU General Public License, *
19 !* write to: Free Software Foundation, Inc., *
20 !* 675 Mass Ave, Cambridge, MA 02139, USA. *
21 !* or see: http://www.gnu.org/licenses/gpl.html *
22 !***********************************************************************
23 
24 !********+*********+*********+*********+*********+*********+*********+**
25 !* *
26 !* By Robert Hallberg, February 2001 *
27 !* *
28 !* The subroutines here calculate the heights of interfaces in a *
29 !* way that is consistent with the calculations in the pressure *
30 !* gradient acceleration calculation. In a Boussinseq model this is *
31 !* pretty simple vertical sum, but in a non-Boussinesq model it uses *
32 !* integrals of the equation of state. *
33 !* *
34 !* Macros written all in capital letters are defined in MOM_memory.h. *
35 !* *
36 !* A small fragment of the grid is shown below: *
37 !* *
38 !* j+1 x ^ x ^ x At x: q, CoriolisBu *
39 !* j+1 > o > o > At ^: v *
40 !* j x ^ x ^ x At >: u *
41 !* j > o > o > At o: h, bathyT *
42 !* j-1 x ^ x ^ x *
43 !* i-1 i i+1 At x & ^: *
44 !* i i+1 At > & o: *
45 !* *
46 !* The boundaries always run through q grid points (x). *
47 !* *
48 !********+*********+*********+*********+*********+*********+*********+**
49 
50 use mom_error_handler, only : mom_error, fatal
51 use mom_file_parser, only : log_version
52 use mom_grid, only : ocean_grid_type
55 use mom_eos, only : int_specific_vol_dp
56 
57 implicit none ; private
58 
59 #include <MOM_memory.h>
60 
61 public find_eta
62 
63 interface find_eta
64  module procedure find_eta_2d, find_eta_3d
65 end interface find_eta
66 
67 contains
68 
69 subroutine find_eta_3d(h, tv, G_Earth, G, GV, eta, eta_bt, halo_size)
70  type(ocean_grid_type), intent(in) :: G !< The ocean's grid
71  !! structure.
72  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical
73  !! grid structure.
74  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H
75  !! (usually m or kg m-2).
76  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to
77  !! various thermodynamic
78  !! variables.
79  real, intent(in) :: G_Earth !< Earth gravitational
80  !! acceleration (m/s2).
81  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1), intent(out) :: eta !< layer interface heights
82  !! (meter).
83  real, dimension(SZI_(G),SZJ_(G)), optional, intent(in) :: eta_bt !< optional barotropic
84  !! variable that gives the "correct" free surface height (Boussinesq) or total water
85  !! column mass per unit aread (non-Boussinesq). This is used to dilate the layer.
86  !! thicknesses when calculating interfaceheights, in H (m or kg m-2).
87  integer, optional, intent(in) :: halo_size !< width of halo points on
88  !! which to calculate eta.
89 
90 ! This subroutine determines the heights of all interfaces between layers,
91 ! using the appropriate form for consistency with the calculation of the
92 ! pressure gradient forces. Additionally, these height may be dilated for
93 ! consistency with the corresponding time-average quantity from the barotropic
94 ! calculation.
95 
96 ! Arguments:
97 ! (in) h - layer thickness H (meter or kg/m2)
98 ! (in) tv - structure pointing to thermodynamic variables
99 ! (in) G_Earth - Earth gravitational acceleration (m/s2)
100 ! (in) G - ocean grid structure
101 ! (in) GV - The ocean's vertical grid structure.
102 ! (out) eta - layer interface heights (meter)
103 ! (in,opt) eta_bt - optional barotropic variable that gives the "correct"
104 ! free surface height (Boussinesq) or total water column
105 ! mass per unit aread (non-Boussinesq). This is used to
106 ! dilate the layer thicknesses when calculating interface
107 ! heights, in H (m or kg m-2).
108 ! (in,opt) halo_size - width of halo points on which to calculate eta
109 
110  real :: p(szi_(g),szj_(g),szk_(g)+1)
111  real :: dz_geo(szi_(g),szj_(g),szk_(g)) ! The change in geopotential height
112  ! across a layer, in m2 s-2.
113  real :: dilate(szi_(g)) ! non-dimensional dilation factor
114  real :: htot(szi_(g)) ! total thickness H
115  real :: I_gEarth
116  integer i, j, k, isv, iev, jsv, jev, nz, halo
117 
118  halo = 0 ; if (present(halo_size)) halo = max(0,halo_size)
119 
120  isv = g%isc-halo ; iev = g%iec+halo ; jsv = g%jsc-halo ; jev = g%jec+halo
121  nz = g%ke
122 
123  if ((isv<g%isd) .or. (iev>g%ied) .or. (jsv<g%jsd) .or. (jev>g%jed)) &
124  call mom_error(fatal,"find_eta called with an overly large halo_size.")
125 
126  i_gearth = 1.0 / g_earth
127 
128 !$OMP parallel default(none) shared(isv,iev,jsv,jev,nz,eta,G,GV,h,eta_bt,tv,p, &
129 !$OMP G_Earth,dz_geo,halo,I_gEarth) &
130 !$OMP private(dilate,htot)
131 !$OMP do
132  do j=jsv,jev ; do i=isv,iev ; eta(i,j,nz+1) = -g%bathyT(i,j) ; enddo ; enddo
133 
134  if (gv%Boussinesq) then
135 !$OMP do
136  do j=jsv,jev ; do k=nz,1,-1; do i=isv,iev
137  eta(i,j,k) = eta(i,j,k+1) + h(i,j,k)*gv%H_to_m
138  enddo ; enddo ; enddo
139  if (present(eta_bt)) then
140  ! Dilate the water column to agree with the free surface height
141  ! that is used for the dynamics.
142 !$OMP do
143  do j=jsv,jev
144  do i=isv,iev
145  dilate(i) = (eta_bt(i,j)*gv%H_to_m + g%bathyT(i,j)) / &
146  (eta(i,j,1) + g%bathyT(i,j))
147  enddo
148  do k=1,nz ; do i=isv,iev
149  eta(i,j,k) = dilate(i) * (eta(i,j,k) + g%bathyT(i,j)) - g%bathyT(i,j)
150  enddo ; enddo
151  enddo
152  endif
153  else
154  if (associated(tv%eqn_of_state)) then
155  ! ### THIS SHOULD BE P_SURF, IF AVAILABLE.
156 !$OMP do
157  do j=jsv,jev
158  do i=isv,iev ; p(i,j,1) = 0.0 ; enddo
159  do k=1,nz ; do i=isv,iev
160  p(i,j,k+1) = p(i,j,k) + g_earth*gv%H_to_kg_m2*h(i,j,k)
161  enddo ; enddo
162  enddo
163 !$OMP do
164  do k=1,nz
165  call int_specific_vol_dp(tv%T(:,:,k), tv%S(:,:,k), p(:,:,k), p(:,:,k+1), &
166  0.0, g%HI, tv%eqn_of_state, dz_geo(:,:,k), halo_size=halo)
167  enddo
168 !$OMP do
169  do j=jsv,jev
170  do k=nz,1,-1 ; do i=isv,iev
171  eta(i,j,k) = eta(i,j,k+1) + i_gearth * dz_geo(i,j,k)
172  enddo ; enddo
173  enddo
174  else
175 !$OMP do
176  do j=jsv,jev ; do k=nz,1,-1; do i=isv,iev
177  eta(i,j,k) = eta(i,j,k+1) + gv%H_to_kg_m2*h(i,j,k)/gv%Rlay(k)
178  enddo ; enddo ; enddo
179  endif
180  if (present(eta_bt)) then
181  ! Dilate the water column to agree with the free surface height
182  ! from the time-averaged barotropic solution.
183 !$OMP do
184  do j=jsv,jev
185  do i=isv,iev ; htot(i) = gv%H_subroundoff ; enddo
186  do k=1,nz ; do i=isv,iev ; htot(i) = htot(i) + h(i,j,k) ; enddo ; enddo
187  do i=isv,iev ; dilate(i) = eta_bt(i,j) / htot(i) ; enddo
188  do k=1,nz ; do i=isv,iev
189  eta(i,j,k) = dilate(i) * (eta(i,j,k) + g%bathyT(i,j)) - g%bathyT(i,j)
190  enddo ; enddo
191  enddo
192  endif
193  endif
194 !$OMP end parallel
195 
196 end subroutine find_eta_3d
197 
198 
199 subroutine find_eta_2d(h, tv, G_Earth, G, GV, eta, eta_bt, halo_size)
200  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
201  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid
202  !! structure.
203  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thicknesses, in H
204  !! (usually m or kg m-2).
205  type(thermo_var_ptrs), intent(in) :: tv !< A structure pointing to
206  !! various thermodynamic
207  !! variables.
208  real, intent(in) :: G_Earth !< Earth gravitational
209  !! acceleration (m/s2).
210  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: eta !< free surface height
211  !! relative to mean sea
212  !! level (z=0) (m).
213  real, dimension(SZI_(G),SZJ_(G)), optional, intent(in) :: eta_bt !< optional barotropic
214  !! variable that gives the "correct" free surface height (Boussinesq) or total
215  !! water column mass per unit aread (non-Boussinesq), in H (m or kg m-2).
216  integer, optional, intent(in) :: halo_size !< width of halo points on
217  !! which to calculate eta.
218 
219 ! This subroutine determines the free surface height, using the appropriate
220 ! form for consistency with the calculation of the pressure gradient forces.
221 ! Additionally, the sea surface height may be adjusted for consistency with the
222 ! corresponding time-average quantity from the barotropic calculation.
223 
224 ! Arguments:
225 ! (in) h - layer thickness (meter or kg/m2)
226 ! (in) tv - structure pointing to various thermodynamic variables
227 ! (in) G_Earth - Earth gravitational acceleration (m/s2)
228 ! (in) G - ocean grid structure
229 ! (in) GV - The ocean's vertical grid structure.
230 ! (out) eta - free surface height relative to mean sea level (z=0) (m)
231 ! (in,opt) eta_bt - optional barotropic variable that gives the "correct"
232 ! free surface height (Boussinesq) or total water column
233 ! mass per unit aread (non-Boussinesq), in H (m or kg m-2)
234 ! (in,opt) halo_size - width of halo points on which to calculate eta
235 
236  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1) :: &
237  p ! The pressure in Pa.
238  real, dimension(SZI_(G),SZJ_(G),SZK_(G)) :: &
239  dz_geo ! The change in geopotential height across a layer, in m2 s-2.
240  real :: htot(szi_(g)) ! The sum of all layers' thicknesses, in kg m-2 or m.
241  real :: I_gEarth
242  integer i, j, k, is, ie, js, je, nz, halo
243 
244  halo = 0 ; if (present(halo_size)) halo = max(0,halo_size)
245  is = g%isc-halo ; ie = g%iec+halo ; js = g%jsc-halo ; je = g%jec+halo
246  nz = g%ke
247 
248  i_gearth = 1.0 / g_earth
249 
250 !$OMP parallel default(none) shared(is,ie,js,je,nz,eta,G,GV,eta_bt,h,tv,p, &
251 !$OMP G_Earth,dz_geo,halo,I_gEarth) &
252 !$OMP private(htot)
253 !$OMP do
254  do j=js,je ; do i=is,ie ; eta(i,j) = -g%bathyT(i,j) ; enddo ; enddo
255 
256  if (gv%Boussinesq) then
257  if (present(eta_bt)) then
258 !$OMP do
259  do j=js,je ; do i=is,ie
260  eta(i,j) = eta_bt(i,j)
261  enddo ; enddo
262  else
263 !$OMP do
264  do j=js,je ; do k=1,nz ; do i=is,ie
265  eta(i,j) = eta(i,j) + h(i,j,k)*gv%H_to_m
266  enddo ; enddo ; enddo
267  endif
268  else
269  if (associated(tv%eqn_of_state)) then
270 !$OMP do
271  do j=js,je
272  do i=is,ie ; p(i,j,1) = 0.0 ; enddo
273 
274  do k=1,nz ; do i=is,ie
275  p(i,j,k+1) = p(i,j,k) + g_earth*gv%H_to_kg_m2*h(i,j,k)
276  enddo ; enddo
277  enddo
278 !$OMP do
279  do k = 1, nz
280  call int_specific_vol_dp(tv%T(:,:,k), tv%S(:,:,k), p(:,:,k), p(:,:,k+1), 0.0, &
281  g%HI, tv%eqn_of_state, dz_geo(:,:,k), halo_size=halo)
282  enddo
283 !$OMP do
284  do j=js,je ; do k=1,nz ; do i=is,ie
285  eta(i,j) = eta(i,j) + i_gearth * dz_geo(i,j,k)
286  enddo ; enddo ; enddo
287  else
288 !$OMP do
289  do j=js,je ; do k=1,nz ; do i=is,ie
290  eta(i,j) = eta(i,j) + gv%H_to_kg_m2*h(i,j,k)/gv%Rlay(k)
291  enddo ; enddo ; enddo
292  endif
293  if (present(eta_bt)) then
294  ! Dilate the water column to agree with the the time-averaged column
295  ! mass from the barotropic solution.
296 !$OMP do
297  do j=js,je
298  do i=is,ie ; htot(i) = gv%H_subroundoff ; enddo
299  do k=1,nz ; do i=is,ie ; htot(i) = htot(i) + h(i,j,k) ; enddo ; enddo
300  do i=is,ie
301  eta(i,j) = (eta_bt(i,j) / htot(i)) * (eta(i,j) + g%bathyT(i,j)) - &
302  g%bathyT(i,j)
303  enddo
304  enddo
305  endif
306  endif
307 !$OMP end parallel
308 
309 end subroutine find_eta_2d
310 
311 end module mom_interface_heights
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
The module calculates interface heights, including free surface height.
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine find_eta_3d(h, tv, G_Earth, G, GV, eta, eta_bt, halo_size)
subroutine find_eta_2d(h, tv, G_Earth, G, GV, eta, eta_bt, halo_size)
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine, public mom_error(level, message, all_print)