MOM6
MOM_internal_tides.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 !********+*********+*********+*********+*********+*********+*********+**
23 !* *
24 !* By Benjamin Mater & Robert Hallberg, 2015 *
25 !* *
26 !* This program contains the subroutines that use the ray-tracing *
27 !* equations to propagate the internal tide energy density. *
28 !* *
29 !* Macros written all in capital letters are defined in MOM_memory.h. *
30 !* *
31 !* A small fragment of the grid is shown below: *
32 !* *
33 !* j+1 x ^ x ^ x At x: q *
34 !* j+1 > o > o > At ^: v, tauy *
35 !* j x ^ x ^ x At >: u, taux *
36 !* j > o > o > At o: h, fluxes. *
37 !* j-1 x ^ x ^ x *
38 !* i-1 i i+1 At x & ^: *
39 !* i i+1 At > & o: *
40 !* *
41 !* The boundaries always run through q grid points (x). *
42 !* *
43 !********+*********+*********+*********+*********+*********+*********+**
44 
45 use mom_debugging, only : is_nan
46 use mom_diag_mediator, only : post_data, query_averaging_enabled, diag_axis_init
47 use mom_diag_mediator, only : register_diag_field, diag_ctrl, safe_alloc_ptr
49 use mom_domains, only : agrid, to_south, to_west, to_all
51 use mom_domains, only : group_pass_type, start_group_pass, complete_group_pass
52 use mom_error_handler, only : mom_error, fatal, warning, mom_mesg, is_root_pe
54 use mom_grid, only : ocean_grid_type
55 use mom_io, only : slasher, vardesc
58 use mom_time_manager, only : time_type, operator(+), operator(/), operator(-)
59 use mom_time_manager, only : get_time, get_date, set_time, set_date
60 use mom_time_manager, only : time_type_to_real
63 use fms_mod, only : read_data
65 
66 ! Forcing is a structure containing pointers to the forcing fields
67 ! which may be used to drive MOM. All fluxes are positive downward.
68 ! Surface is a structure containing pointers to various fields that
69 ! may be used describe the surface state of MOM.
70 
71 !use, intrinsic :: IEEE_ARITHMETIC
72 
73 implicit none ; private
74 
75 #include <MOM_memory.h>
76 
77 public propagate_int_tide !, register_int_tide_restarts
79 public get_lowmode_loss
80 
81 type, public :: int_tide_cs ; private
82  logical :: do_int_tides ! If true, use the internal tide code.
83  integer :: nfreq = 0
84  integer :: nmode = 1
85  integer :: nangle = 24
86  integer :: energized_angle = -1
87  logical :: corner_adv ! If true, use a corner advection rather than PPM.
88  logical :: upwind_1st ! If true, use a first-order upwind scheme.
89  logical :: simple_2nd ! If true, use a simple second order (arithmetic
90  ! mean) interpolation of the edge values instead
91  ! of the higher order interpolation.
92  logical :: vol_cfl ! If true, use the ratio of the open face lengths
93  ! to the tracer cell areas when estimating CFL
94  ! numbers. Without aggress_adjust, the default is
95  ! false; it is always true with.
96  logical :: use_ppmang ! If true, use PPM for advection of energy in
97  ! angular space.
98 
99  real, allocatable, dimension(:,:) :: refl_angle
100  ! local coastline/ridge/shelf angles read from file
101  ! (could be in G control structure)
102  real :: nullangle = -999.9 ! placeholder value in cell with no reflection
103  real, allocatable, dimension(:,:) :: refl_pref
104  ! partial reflection coeff for each ``coast cell"
105  ! (could be in G control structure)
106  logical, allocatable, dimension(:,:) :: refl_pref_logical
107  ! true if reflecting cell with partial reflection
108  ! (could be in G control structure)
109  logical, allocatable, dimension(:,:) :: refl_dbl
110  ! identifies reflection cells where double reflection
111  ! is possible (i.e. ridge cells)
112  ! (could be in G control structure)
113  real, allocatable, dimension(:,:,:,:) :: cp
114  ! horizontal phase speed [m s-1]
115  real, allocatable, dimension(:,:,:,:,:) :: tke_leak_loss
116  ! energy lost due to misc background processes [W m-2]
117  real, allocatable, dimension(:,:,:,:,:) :: tke_quad_loss
118  ! energy lost due to quadratic bottom drag [W m-2]
119  real, allocatable, dimension(:,:,:,:,:) :: tke_froude_loss
120  ! energy lost due to wave breaking [W m-2]
121  real, allocatable, dimension(:,:) :: tke_itidal_loss_fixed
122  ! fixed part of the energy lost due to small-scale drag
123  ! [kg m-2] here; will be multiplied by N and En to get
124  ! into [W m-2]
125  real, allocatable, dimension(:,:,:,:,:) :: tke_itidal_loss
126  ! energy lost due to small-scale wave drag [W m-2]
127  real, allocatable, dimension(:,:) :: tot_leak_loss, tot_quad_loss, &
128  tot_itidal_loss, tot_froude_loss, tot_allprocesses_loss
129  ! energy loss rates summed over angle, freq, and mode
130  real :: q_itides ! fraction of local dissipation (nondimensional)
131  real :: en_sum ! global sum of energy for use in debugging
132  type(time_type),pointer :: time
133  ! The current model time
134  character(len=200) :: inputdir
135  ! directory to look for coastline angle file
136  real :: decay_rate ! A constant rate at which internal tide energy is
137  ! lost to the interior ocean internal wave field.
138  real :: cdrag ! The bottom drag coefficient for MEKE (non-dim).
139  logical :: apply_background_drag
140  ! If true, apply a drag due to background processes as a sink.
141  logical :: apply_bottom_drag
142  ! If true, apply a quadratic bottom drag as a sink.
143  logical :: apply_wave_drag
144  ! If true, apply scattering due to small-scale
145  ! roughness as a sink.
146  logical :: apply_froude_drag
147  ! If true, apply wave breaking as a sink.
148  real, dimension(:,:,:,:,:), pointer :: &
149  en ! The internal wave energy density as a function of
150  ! (i,j,angle,frequency,mode)
151  real, dimension(:,:,:), pointer :: &
152  en_restart ! The internal wave energy density as a function of
153  ! (i,j,angle); temporary for restart
154  real, allocatable, dimension(:) :: &
155  frequency ! The frequency of each band.
156 
157  real :: int_tide_source_x ! delete later
158  ! X Location of generation site
159  ! for internal tide for testing
160  real :: int_tide_source_y ! delete later
161  ! Y Location of generation site
162  ! for internal tide for testing
163 
164  type(diag_ctrl), pointer :: diag ! A structure that is used to regulate the
165  ! timing of diagnostic output.
166  type(wave_structure_cs), pointer :: wave_structure_csp => null()
167 
168  ! Diag handles relevant to all modes, frequencies, and angles
169  integer :: id_itide_drag = -1
170  integer :: id_refl_pref = -1, id_refl_ang = -1, id_land_mask = -1
171  integer :: id_dx_cv = -1, id_dy_cu = -1
172  integer :: id_tke_itidal_input = -1
173  ! Diag handles considering: sums over all modes, frequencies, and angles
174  integer :: id_tot_en = -1, &
175  id_tot_leak_loss = -1, &
176  id_tot_quad_loss = -1, &
177  id_tot_itidal_loss = -1, &
178  id_tot_froude_loss = -1, &
179  id_tot_allprocesses_loss = -1
180  ! Diag handles considering: all modes & freqs; summed over angles
181  integer, allocatable, dimension(:,:) :: &
182  id_en_mode, &
183  id_itidal_loss_mode, &
184  id_allprocesses_loss_mode, &
185  id_ub_mode, &
186  id_cp_mode
187  ! Diag handles considering: all modes, freqs, and angles
188  integer, allocatable, dimension(:,:) :: &
189  id_en_ang_mode, &
190  id_itidal_loss_ang_mode
191 
192 end type int_tide_cs
193 
194 type :: loop_bounds_type ; private
195  integer :: ish, ieh, jsh, jeh
196 end type loop_bounds_type
197 
198 contains
199 
200 !> This subroutine calls other subroutines in this file that are needed to
201 !! refract, propagate, and dissipate energy density of the internal tide.
202 subroutine propagate_int_tide(h, tv, cn, TKE_itidal_input, vel_btTide, Nb, dt, &
203  G, GV, CS)
204  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure.
205  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
206  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
207  intent(in) :: h !< Layer thicknesses, in H
208  !! (usually m or kg m-2).
209  type(thermo_var_ptrs), intent(in) :: tv !< Pointer to thermodynamic variables
210  !! (needed for wave structure).
211  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: TKE_itidal_input !< The energy input to the
212  !! internal waves, in W m-2.
213  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: vel_btTide !< Barotropic velocity read
214  !! from file, in m s-1.
215  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: Nb !< Near-bottom buoyancy frequency, in s-1.
216  real, intent(in) :: dt !< Length of time over which these fluxes
217  !! will be applied, in s.
218  type(int_tide_cs), pointer :: CS !< A pointer to the control structure
219  !! returned by a previous call to
220  !! int_tide_init.
221  real, dimension(SZI_(G),SZJ_(G),CS%nMode), &
222  intent(in) :: cn
223 
224  ! This subroutine calls other subroutines in this file that are needed to
225  ! refract, propagate, and dissipate energy density of the internal tide.
226  !
227  ! Arguments:
228  ! (in) h - Layer thickness, in m or kg m-2 (needed for wave structure).
229  ! (in) tv - Pointer to thermodynamic variables (needed for wave structure).
230  ! (in) cn - Internal gravity wave speeds of modes, in m s-1.
231  ! (in) TKE_itidal_input - The energy input to the internal waves, in W m-2.
232  ! (in) vel_btTide - Barotropic velocity read from file, in m s-1
233  ! (in) Nb - Near-bottom buoyancy frequency, in s-1
234  ! (in) dt - Length of time over which these fluxes will be applied, in s.
235  ! (in) G - The ocean's grid structure.
236  ! (in) GV - The ocean's vertical grid structure.
237  ! (in) CS - A pointer to the control structure returned by a previous
238  ! call to int_tide_init.
239  real, dimension(SZI_(G),SZJ_(G),2) :: &
240  test
241  real, dimension(SZI_(G),SZJ_(G),CS%nFreq,CS%nMode) :: &
242  tot_En_mode, & ! energy summed over angles only
243  Ub, Umax ! near-bottom & max horizontal velocity of wave (modal)
244  real, dimension(SZI_(G),SZJB_(G)) :: &
245  flux_heat_y, &
246  flux_prec_y
247  real, dimension(SZI_(G),SZJ_(G)) :: &
248  tot_En, & ! energy summed over angles, modes, frequencies
249  tot_leak_loss, tot_quad_loss, tot_itidal_loss, tot_Froude_loss, tot_allprocesses_loss, &
250  ! energy loss rates summed over angle, freq, and mode
251  drag_scale, & ! bottom drag scale, s-1
252  itidal_loss_mode, allprocesses_loss_mode
253  ! energy loss rates for a given mode and frequency (summed over angles)
254  real :: frac_per_sector, f2, I_rho0, I_D_here, freq2, Kmag2
255  real :: c_phase, loss_rate, Fr2_max
256  real, parameter :: cn_subRO = 1e-100 ! to prevent division by zero
257  real :: En_new, En_check ! for debugging
258  real :: En_initial, Delta_E_check ! for debugging
259  real :: TKE_Froude_loss_check, TKE_Froude_loss_tot ! for debugging
260  integer :: a, m, fr, i, j, is, ie, js, je, isd, ied, jsd, jed, nAngle, nzm
261  integer :: id_g, jd_g ! global (decomp-invar) indices (for debugging)
262  type(group_pass_type), save :: pass_test, pass_En
263 
264  if (.not.associated(cs)) return
265  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
266  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed ; nangle = cs%NAngle
267  i_rho0 = 1.0 / gv%Rho0
268 
269  ! Set the wave speeds for the modes, using cg(n) ~ cg(1)/n.**********************
270  ! This is wrong, of course, but it works reasonably in some cases.
271  ! Uncomment if wave_speed is not used to calculate the true values (BDM).
272  !do m=1,CS%nMode ; do j=jsd,jed ; do i=isd,ied
273  ! cn(i,j,m) = cn(i,j,1) / real(m)
274  !enddo ; enddo ; enddo
275 
276  ! Add the forcing.***************************************************************
277  if (cs%energized_angle <= 0) then
278  frac_per_sector = 1.0 / real(cs%nangle * cs%nmode * cs%nfreq)
279  do m=1,cs%nMode ; do fr=1,cs%nFreq ; do a=1,cs%nAngle ; do j=js,je ; do i=is,ie
280  f2 = 0.25*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j-1)**2) + &
281  (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j)**2))
282  if (cs%frequency(fr)**2 > f2) &
283  cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) + &
284  dt*frac_per_sector*(1-cs%q_itides)*tke_itidal_input(i,j)
285  enddo ; enddo ; enddo ; enddo ; enddo
286  elseif (cs%energized_angle <= cs%nAngle) then
287  frac_per_sector = 1.0 / real(cs%nmode * cs%nfreq)
288  a = cs%energized_angle
289  do m=1,cs%nMode ; do fr=1,cs%nFreq ; do j=js,je ; do i=is,ie
290  f2 = 0.25*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j-1)**2) + &
291  (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j)**2))
292  if (cs%frequency(fr)**2 > f2) &
293  cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) + &
294  dt*frac_per_sector**(1-cs%q_itides)*tke_itidal_input(i,j)
295  enddo ; enddo ; enddo ; enddo
296  else
297  call mom_error(warning, "Internal tide energy is being put into a angular "//&
298  "band that does not exist.")
299  endif
300 
301  ! Pass a test vector to check for grid rotation in the halo updates.
302  do j=jsd,jed ; do i=isd,ied ; test(i,j,1) = 1.0 ; test(i,j,2) = 0.0 ; enddo ; enddo
303  do m=1,cs%nMode ; do fr=1,cs%nFreq
304  call create_group_pass(pass_en, cs%En(:,:,:,fr,m), g%domain)
305  enddo; enddo
306  call create_group_pass(pass_test, test(:,:,1), test(:,:,2), g%domain, stagger=agrid)
307  call start_group_pass(pass_test, g%domain)
308 
309  ! Apply half the refraction.*****************************************************
310  do m=1,cs%nMode ; do fr=1,cs%nFreq
311  call refract(cs%En(:,:,:,fr,m), cn(:,:,m), cs%frequency(fr), 0.5*dt, g, cs%nAngle, cs%use_PPMang)
312  enddo ; enddo
313 
314  ! Check for En<0 - for debugging, delete later
315  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle
316  do j=js,je ; do i=is,ie
317  if (cs%En(i,j,a,fr,m)<0.0) then
318  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset ! for debugging
319  print *, 'After first refraction: En<0.0 at ig=', id_g, ', jg=', jd_g
320  print *, 'En=',cs%En(i,j,a,fr,m)
321  print *, 'Setting En to zero'; cs%En(i,j,a,fr,m) = 0.0
322  !stop
323  endif
324  enddo ; enddo
325  enddo ; enddo ; enddo
326 
327  call do_group_pass(pass_en, g%domain)
328 
329  call complete_group_pass(pass_test, g%domain)
330 
331  ! Rotate points in the halos as necessary.
332  call correct_halo_rotation(cs%En, test, g, cs%nAngle)
333 
334  ! Propagate the waves.***********************************************************
335  do m=1,cs%NMode ; do fr=1,cs%Nfreq
336  call propagate(cs%En(:,:,:,fr,m), cn(:,:,m), cs%frequency(fr), dt, g, cs, cs%NAngle)
337  enddo ; enddo
338 
339  ! Check for En<0 - for debugging, delete later
340  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle
341  do j=js,je ; do i=is,ie
342  if (cs%En(i,j,a,fr,m)<0.0) then
343  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
344  cs%En(i,j,a,fr,m) = 0.0
345  if(abs(cs%En(i,j,a,fr,m))>1.0)then! only print if large
346  print *, 'After propagation: En<0.0 at ig=', id_g, ', jg=', jd_g
347  print *, 'En=',cs%En(i,j,a,fr,m)
348  print *, 'Setting En to zero'
349  !stop
350  endif
351  endif
352  enddo ; enddo
353  enddo ; enddo ; enddo
354 
355  !! Test if energy has passed coast for debugging only; delete later
356  !do j=js,je
357  ! do i=is,ie
358  ! id_g = i + G%idg_offset ; jd_g = j + G%jdg_offset
359  ! if (id_g == 106 .and. jd_g == 55 ) then
360  !print *, 'After propagation:'
361  !print *, 'En_O =', CS%En(i,j,:,1,1), 'refl_angle=', CS%refl_angle(i,j)
362  !print *, 'En_W =', CS%En(i-1,j,:,1,1), 'refl_angle=', CS%refl_angle(i-1,j)
363  !print *, 'En_NW =', CS%En(i-1,j+1,:,1,1), 'refl_angle=', CS%refl_angle(i-1,j+1)
364  !print *, 'En_N =', CS%En(i,j+1,:,1,1), 'refl_angle=', CS%refl_angle(i,j+1)
365  !print *, 'En_NE =', CS%En(i+1,j+1,:,1,1), 'refl_angle=', CS%refl_angle(i+1,j+1)
366  !print *, 'En_E =', CS%En(i+1,j,:,1,1), 'refl_angle=', CS%refl_angle(i+1,j)
367  ! endif
368  ! enddo
369  ! enddo
370 
371  ! Apply the other half of the refraction.****************************************
372  do m=1,cs%NMode ; do fr=1,cs%Nfreq
373  call refract(cs%En(:,:,:,fr,m), cn(:,:,m), cs%frequency(fr), 0.5*dt, g, cs%NAngle, cs%use_PPMang)
374  enddo ; enddo
375 
376  ! Check for En<0 - for debugging, delete later
377  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle
378  do j=js,je ; do i=is,ie
379  if (cs%En(i,j,a,fr,m)<0.0) then
380  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset ! for debugging
381  print *, 'After second refraction: En<0.0 at ig=', id_g, ', jg=', jd_g
382  !stop
383  endif
384  enddo ; enddo
385  enddo ; enddo ; enddo
386 
387  ! Apply various dissipation mechanisms.******************************************
388  if (cs%apply_background_drag .or. cs%apply_bottom_drag &
389  .or. cs%apply_wave_drag .or. cs%apply_Froude_drag &
390  .or. (cs%id_tot_En > 0)) then
391  tot_en(:,:) = 0.0
392  tot_en_mode(:,:,:,:) = 0.0
393  do m=1,cs%NMode ; do fr=1,cs%Nfreq
394  do j=jsd,jed ; do i=isd,ied ; do a=1,cs%nAngle
395  tot_en(i,j) = tot_en(i,j) + cs%En(i,j,a,fr,m)
396  tot_en_mode(i,j,fr,m) = tot_en_mode(i,j,fr,m) + cs%En(i,j,a,fr,m)
397  enddo ; enddo ; enddo
398  enddo ; enddo
399  endif
400 
401  ! Extract the energy for mixing due to misc. processes (background leakage)------
402  if (cs%apply_background_drag) then
403  do m=1,cs%nMode ; do fr=1,cs%nFreq ; do a=1,cs%nAngle ; do j=jsd,jed ; do i=isd,ied
404  ! Calculate loss rate and apply loss over the time step ; apply the same drag timescale
405  ! to each En component (technically not correct; fix later)
406  cs%TKE_leak_loss(i,j,a,fr,m) = cs%En(i,j,a,fr,m) * cs%decay_rate ! loss rate [Wm-2]
407  cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) / (1.0 + dt *cs%decay_rate) ! implicit update
408  enddo ; enddo ; enddo ; enddo ; enddo
409  endif
410  ! Check for En<0 - for debugging, delete later
411  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle
412  do j=js,je ; do i=is,ie
413  if (cs%En(i,j,a,fr,m)<0.0) then
414  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset ! for debugging
415  print *, 'After leak loss: En<0.0 at ig=', id_g, ', jg=', jd_g
416  !stop
417  endif
418  enddo ; enddo
419  enddo ; enddo ; enddo
420 
421  ! Extract the energy for mixing due to bottom drag-------------------------------
422  if (cs%apply_bottom_drag) then
423  do j=jsd,jed ; do i=isd,ied
424  i_d_here = 1.0 / max(g%bathyT(i,j), 1.0)
425  drag_scale(i,j) = cs%cdrag * sqrt(max(0.0, vel_bttide(i,j)**2 + &
426  tot_en(i,j) * i_rho0 * i_d_here)) * i_d_here
427  enddo ; enddo
428  do m=1,cs%nMode ; do fr=1,cs%nFreq ; do a=1,cs%nAngle ; do j=jsd,jed ; do i=isd,ied
429  ! Calculate loss rate and apply loss over the time step ; apply the same drag timescale
430  ! to each En component (technically not correct; fix later)
431  cs%TKE_quad_loss(i,j,a,fr,m) = cs%En(i,j,a,fr,m) * drag_scale(i,j) ! loss rate
432  cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m) / (1.0 + dt *drag_scale(i,j)) ! implicit update
433  enddo ; enddo ; enddo ; enddo ; enddo
434  endif
435  ! Check for En<0 - for debugging, delete later
436  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle
437  do j=js,je ; do i=is,ie
438  if (cs%En(i,j,a,fr,m)<0.0) then
439  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset ! for debugging
440  print *, 'After bottom loss: En<0.0 at ig=', id_g, ', jg=', jd_g
441  !stop
442  endif
443  enddo ; enddo
444  enddo ; enddo ; enddo
445 
446  ! Extract the energy for mixing due to scattering (wave-drag)--------------------
447  ! still need to allow a portion of the extracted energy to go to higher modes.
448  ! First, find velocity profiles
449  if (cs%apply_wave_drag .or. cs%apply_Froude_drag) then
450  do m=1,cs%NMode ; do fr=1,cs%Nfreq
451  ! Calculate modal structure for given mode and frequency
452  call wave_structure(h, tv, g, gv, cn(:,:,m), m, cs%frequency(fr), &
453  cs%wave_structure_CSp, tot_en_mode(:,:,fr,m), full_halos=.true.)
454  ! Pick out near-bottom and max horizontal baroclinic velocity values at each point
455  do j=jsd,jed ; do i=isd,ied
456  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset ! for debugging
457  nzm = cs%wave_structure_CSp%num_intfaces(i,j)
458  ub(i,j,fr,m) = cs%wave_structure_CSp%Uavg_profile(i,j,nzm)
459  umax(i,j,fr,m) = maxval(cs%wave_structure_CSp%Uavg_profile(i,j,1:nzm))
460  !! for debugging print profile, etc. Delete later
461  !if(id_g .eq. 260 .and. &
462  ! jd_g .eq. 50 .and. &
463  ! tot_En_mode(i,j,1,1)>500.0) then
464  ! print *, 'Profiles for mode ',m,' and frequency ',fr
465  ! print *, 'id_g=', id_g, 'jd_g=', jd_g
466  ! print *, 'c',m,'=', cn(i,j,m)
467  ! print *, 'nzm=', nzm
468  ! print *, 'z=', CS%wave_structure_CSp%z_depths(i,j,1:nzm)
469  ! print *, 'N2=', CS%wave_structure_CSp%N2(i,j,1:nzm)
470  ! print *, 'Ub=', Ub(i,j,fr,m)
471  ! print *, 'Umax=', Umax(i,j,fr,m)
472  ! print *, 'Upro=', CS%wave_structure_CSp%Uavg_profile(i,j,1:nzm)
473  ! print *, 'Wpro=', CS%wave_structure_CSp%W_profile(i,j,1:nzm)
474  ! print *, 'En',m,'=', tot_En_mode(i,j,fr,m)
475  ! if (m==3) stop
476  !endif ! for debug - delete later
477  enddo ; enddo ! i-loop, j-loop
478  enddo ; enddo ! fr-loop, m-loop
479  endif ! apply_wave or _Froude_drag (Ub or Umax needed)
480  ! Finally, apply loss
481  if (cs%apply_wave_drag) then
482  ! Calculate loss rate and apply loss over the time step
483  call itidal_lowmode_loss(g, cs, nb, ub, cs%En, cs%TKE_itidal_loss_fixed, &
484  cs%TKE_itidal_loss, dt, full_halos=.false.)
485  endif
486  ! Check for En<0 - for debugging, delete later
487  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle
488  do j=js,je ; do i=is,ie
489  if (cs%En(i,j,a,fr,m)<0.0) then
490  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset ! for debugging
491  print *, 'After wave drag loss: En<0.0 at ig=', id_g, ', jg=', jd_g
492  !stop
493  endif
494  enddo ; enddo
495  enddo ; enddo ; enddo
496 
497  ! Extract the energy for mixing due to wave breaking-----------------------------
498  if (cs%apply_Froude_drag) then
499  ! Pick out maximum baroclinic velocity values; calculate Fr=max(u)/cg
500  do m=1,cs%NMode ; do fr=1,cs%Nfreq
501  freq2 = cs%frequency(fr)**2
502  do j=jsd,jed ; do i=isd,ied
503  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset ! for debugging
504  ! Calculate horizontal phase velocity magnitudes
505  f2 = 0.25*(g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j)**2 + &
506  g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j-1)**2 )
507  kmag2 = (freq2 - f2) / (cn(i,j,m)**2 + cn_subro**2)
508  c_phase = 0.0
509  if (kmag2 > 0.0) then
510  c_phase = sqrt(freq2/kmag2)
511  nzm = cs%wave_structure_CSp%num_intfaces(i,j)
512  fr2_max = (umax(i,j,fr,m)/c_phase)**2
513  ! Dissipate energy if Fr>1; done here with an arbitrary time scale
514  if (fr2_max > 1.0) then
515  en_initial = sum(cs%En(i,j,:,fr,m)) ! for debugging
516  ! Calculate effective decay rate (s-1) if breaking occurs over a time step
517  loss_rate = (1/fr2_max - 1.0)/dt
518  do a=1,cs%nAngle
519  ! Determine effective dissipation rate (Wm-2)
520  cs%TKE_Froude_loss(i,j,a,fr,m) = cs%En(i,j,a,fr,m) * abs(loss_rate)
521  ! Update energy
522  en_new = cs%En(i,j,a,fr,m)/fr2_max ! for debugging
523  en_check = cs%En(i,j,a,fr,m) - cs%TKE_Froude_loss(i,j,a,fr,m)*dt ! for debugging
524  ! Re-scale (reduce) energy due to breaking
525  cs%En(i,j,a,fr,m) = cs%En(i,j,a,fr,m)/fr2_max
526  ! Check (for debugging only)
527  if (abs(en_new - en_check) > 1e-10) then
528  call mom_error(warning, "MOM_internal_tides: something's wrong with Fr-breaking.")
529  print *, "En_new=", en_new
530  print *, "En_check=", en_check
531  endif
532  enddo
533  ! Check (for debugging)
534  delta_e_check = en_initial - sum(cs%En(i,j,:,fr,m))
535  tke_froude_loss_check = abs(delta_e_check)/dt
536  tke_froude_loss_tot = sum(cs%TKE_Froude_loss(i,j,:,fr,m))
537  if (abs(tke_froude_loss_check - tke_froude_loss_tot) > 1e-10) then
538  call mom_error(warning, "MOM_internal_tides: something's wrong with Fr energy update.")
539  print *, "TKE_Froude_loss_check=", tke_froude_loss_check
540  print *, "TKE_Froude_loss_tot=", tke_froude_loss_tot
541  endif
542  endif ! Fr2>1
543  endif ! Kmag2>0
544  cs%cp(i,j,fr,m) = c_phase
545  enddo ; enddo
546  enddo ; enddo
547  endif
548  ! Check for En<0 - for debugging, delete later
549  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle
550  do j=js,je ; do i=is,ie
551  if (cs%En(i,j,a,fr,m)<0.0) then
552  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
553  print *, 'After Froude loss: En<0.0 at ig=', id_g, ', jg=', jd_g
554  !stop
555  endif
556  enddo ; enddo
557  enddo ; enddo ; enddo
558 
559  ! Check for energy conservation on computational domain.*************************
560  do m=1,cs%NMode ; do fr=1,cs%Nfreq
561  !print *, 'sum_En: mode(',m,'), freq(',fr,'):'
562  call sum_en(g,cs,cs%En(:,:,:,fr,m),'prop_int_tide')
563  enddo ; enddo
564 
565  ! Output diagnostics.************************************************************
566  if (query_averaging_enabled(cs%diag)) then
567  ! Output two-dimensional diagnostistics
568  if (cs%id_tot_En > 0) call post_data(cs%id_tot_En, tot_en, cs%diag)
569  if (cs%id_itide_drag > 0) call post_data(cs%id_itide_drag, drag_scale, cs%diag)
570  if (cs%id_TKE_itidal_input > 0) call post_data(cs%id_TKE_itidal_input, &
571  tke_itidal_input, cs%diag)
572 
573  ! Output 2-D energy density (summed over angles) for each freq and mode
574  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; if (cs%id_En_mode(fr,m) > 0) then
575  tot_en(:,:) = 0.0
576  do a=1,cs%nAngle ; do j=js,je ; do i=is,ie
577  tot_en(i,j) = tot_en(i,j) + cs%En(i,j,a,fr,m)
578  enddo ; enddo ; enddo
579  call post_data(cs%id_En_mode(fr,m), tot_en, cs%diag)
580  endif ; enddo ; enddo
581 
582  ! Output 3-D (i,j,a) energy density for each freq and mode
583  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; if (cs%id_En_ang_mode(fr,m) > 0) then
584  call post_data(cs%id_En_ang_mode(fr,m), cs%En(:,:,:,fr,m) , cs%diag)
585  endif ; enddo ; enddo
586 
587  ! Output 2-D energy loss (summed over angles, freq, modes)
588  tot_leak_loss(:,:) = 0.0
589  tot_quad_loss(:,:) = 0.0
590  tot_itidal_loss(:,:) = 0.0
591  tot_froude_loss(:,:) = 0.0
592  tot_allprocesses_loss(:,:) = 0.0
593  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; do a=1,cs%nAngle ; do j=js,je ; do i=is,ie
594  tot_leak_loss(i,j) = tot_leak_loss(i,j) + cs%TKE_leak_loss(i,j,a,fr,m)
595  tot_quad_loss(i,j) = tot_quad_loss(i,j) + cs%TKE_quad_loss(i,j,a,fr,m)
596  tot_itidal_loss(i,j) = tot_itidal_loss(i,j) + cs%TKE_itidal_loss(i,j,a,fr,m)
597  tot_froude_loss(i,j) = tot_froude_loss(i,j) + cs%TKE_Froude_loss(i,j,a,fr,m)
598  enddo ; enddo ; enddo ; enddo ; enddo
599  do j=js,je ; do i=is,ie
600  tot_allprocesses_loss(i,j) = tot_leak_loss(i,j) + tot_quad_loss(i,j) + &
601  tot_itidal_loss(i,j) + tot_froude_loss(i,j)
602  enddo ; enddo
603  cs%tot_leak_loss = tot_leak_loss
604  cs%tot_quad_loss = tot_quad_loss
605  cs%tot_itidal_loss = tot_itidal_loss
606  cs%tot_Froude_loss = tot_froude_loss
607  cs%tot_allprocesses_loss = tot_allprocesses_loss
608  if (cs%id_tot_leak_loss > 0) then
609  call post_data(cs%id_tot_leak_loss, tot_leak_loss, cs%diag)
610  endif
611  if (cs%id_tot_quad_loss > 0) then
612  call post_data(cs%id_tot_quad_loss, tot_quad_loss, cs%diag)
613  endif
614  if (cs%id_tot_itidal_loss > 0) then
615  call post_data(cs%id_tot_itidal_loss, tot_itidal_loss, cs%diag)
616  endif
617  if (cs%id_tot_Froude_loss > 0) then
618  call post_data(cs%id_tot_Froude_loss, tot_froude_loss, cs%diag)
619  endif
620  if (cs%id_tot_allprocesses_loss > 0) then
621  call post_data(cs%id_tot_allprocesses_loss, tot_allprocesses_loss, cs%diag)
622  endif
623 
624  ! Output 2-D energy loss (summed over angles) for each freq and mode
625  do m=1,cs%NMode ; do fr=1,cs%Nfreq
626  if (cs%id_itidal_loss_mode(fr,m) > 0 .or. cs%id_allprocesses_loss_mode(fr,m) > 0) then
627  itidal_loss_mode(:,:) = 0.0 ! wave-drag processes (could do others as well)
628  allprocesses_loss_mode(:,:) = 0.0 ! all processes summed together
629  do a=1,cs%nAngle ; do j=js,je ; do i=is,ie
630  itidal_loss_mode(i,j) = itidal_loss_mode(i,j) + cs%TKE_itidal_loss(i,j,a,fr,m)
631  allprocesses_loss_mode(i,j) = allprocesses_loss_mode(i,j) + &
632  cs%TKE_leak_loss(i,j,a,fr,m) + cs%TKE_quad_loss(i,j,a,fr,m) + &
633  cs%TKE_itidal_loss(i,j,a,fr,m) + cs%TKE_Froude_loss(i,j,a,fr,m)
634  enddo ; enddo ; enddo
635  call post_data(cs%id_itidal_loss_mode(fr,m), itidal_loss_mode, cs%diag)
636  call post_data(cs%id_allprocesses_loss_mode(fr,m), allprocesses_loss_mode, cs%diag)
637  endif ; enddo ; enddo
638 
639  ! Output 3-D (i,j,a) energy loss for each freq and mode
640  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; if (cs%id_itidal_loss_ang_mode(fr,m) > 0) then
641  call post_data(cs%id_itidal_loss_ang_mode(fr,m), cs%TKE_itidal_loss(:,:,:,fr,m) , cs%diag)
642  endif ; enddo ; enddo
643 
644  ! Output 2-D period-averaged horizontal near-bottom mode velocity for each freq and mode
645  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; if (cs%id_Ub_mode(fr,m) > 0) then
646  call post_data(cs%id_Ub_mode(fr,m), ub(:,:,fr,m), cs%diag)
647  endif ; enddo ; enddo
648 
649  ! Output 2-D horizontal phase velocity for each freq and mode
650  do m=1,cs%NMode ; do fr=1,cs%Nfreq ; if (cs%id_cp_mode(fr,m) > 0) then
651  call post_data(cs%id_cp_mode(fr,m), cs%cp(:,:,fr,m), cs%diag)
652  endif ; enddo ; enddo
653 
654  endif
655 
656 end subroutine propagate_int_tide
657 
658 !> This subroutine checks for energy conservation on computational domain
659 subroutine sum_en(G, CS, En, label)
660  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
661  type(int_tide_cs), pointer :: CS
662  real, dimension(G%isd:G%ied,G%jsd:G%jed,CS%NAngle), intent(in) :: En
663  character(len=*), intent(in) :: label
664 
665  ! This subroutine checks for energy conservation on computational domain
666  integer :: m,fr,a
667  real :: En_sum, tmpForSumming, En_sum_diff, En_sum_pdiff
668  integer :: seconds
669  real :: Isecs_per_day = 1.0 / 86400.0
670  real :: days
671 
672  call get_time(cs%Time, seconds)
673  days = real(seconds) * Isecs_per_day
674 
675  en_sum = 0.0;
676  tmpforsumming = 0.0
677  do a=1,cs%nAngle
678  tmpforsumming = global_area_mean(en(:,:,a),g)*g%areaT_global
679  en_sum = en_sum + tmpforsumming
680  enddo
681  en_sum_diff = en_sum - cs%En_sum
682  if (cs%En_sum .ne. 0.0) then
683  en_sum_pdiff= (en_sum_diff/cs%En_sum)*100.0
684  else
685  en_sum_pdiff= 0.0;
686  endif
687  cs%En_sum = en_sum
688  !! Print to screen
689  !if (is_root_pe()) then
690  ! print *, label,':','days =', days
691  ! print *, 'En_sum=', En_sum
692  ! print *, 'En_sum_diff=', En_sum_diff
693  ! print *, 'Percent change=', En_sum_pdiff, '%'
694  ! !if (abs(En_sum_pdiff) > 1.0) then ; stop ; endif
695  !endif
696 
697 end subroutine sum_en
698 
699 !> This subroutine calculates the energy lost from the propagating internal tide due to
700 !! scattering over small-scale roughness along the lines of Jayne & St. Laurent (2001).
701 subroutine itidal_lowmode_loss(G, CS, Nb, Ub, En, TKE_loss_fixed, TKE_loss, dt, full_halos)
702  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
703  type(int_tide_cs), pointer :: CS
704  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
705  intent(in) :: Nb !< Near-bottom stratification, in s-1.
706  real, dimension(G%isd:G%ied,G%jsd:G%jed,CS%nFreq,CS%nMode), &
707  intent(inout) :: Ub !< Rms (over one period) near-bottom horizontal
708  !! mode velocity , in m s-1.
709  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
710  intent(in) :: TKE_loss_fixed !< Fixed part of energy loss,
711  !! in kg m-2 (rho*kappa*h^2).
712  real, dimension(G%isd:G%ied,G%jsd:G%jed,CS%NAngle,CS%nFreq,CS%nMode), &
713  intent(inout) :: En !< Energy density of the internal waves, in J m-2.
714  real, dimension(G%isd:G%ied,G%jsd:G%jed,CS%NAngle,CS%nFreq,CS%nMode), &
715  intent(out) :: TKE_loss !< Energy loss rate, in W m-2
716  !! (q*rho*kappa*h^2*N*U^2).
717  real, intent(in) :: dt !< Time increment, in s.
718  logical,optional, intent(in) :: full_halos !< If true, do the calculation over the
719  !! entirecomputational domain.
720 
721  ! This subroutine calculates the energy lost from the propagating internal tide due to
722  ! scattering over small-scale roughness along the lines of Jayne & St. Laurent (2001).
723  !
724  ! Arguments:
725  ! (in) Nb - near-bottom stratification, in s-1.
726  ! (in) Ub - rms (over one period) near-bottom horizontal mode velocity , in m s-1.
727  ! (inout) En - energy density of the internal waves, in J m-2.
728  ! (in) TKE_loss_fixed - fixed part of energy loss, in kg m-2 (rho*kappa*h^2)
729  ! (out) TKE_loss - energy loss rate, in W m-2 (q*rho*kappa*h^2*N*U^2)
730  ! (in) dt - time increment, in s
731  ! (in,opt) full_halos - If true, do the calculation over the entire
732  ! computational domain.
733 
734  integer :: j,i,m,fr,a, is, ie, js, je
735  real :: En_tot ! energy for a given mode, frequency, and point summed over angles
736  real :: TKE_loss_tot ! dissipation for a given mode, frequency, and point summed over angles
737  real :: TKE_sum_check ! temporary for check summing
738  real :: frac_per_sector ! fraction of energy in each wedge
739  real :: q_itides ! fraction of energy actually lost to mixing (remainder, 1-q, is
740  ! assumed to stay in propagating mode for now - BDM)
741  real :: loss_rate ! approximate loss rate for implicit calc, s-1
742  real, parameter :: En_negl = 1e-30 ! negilibly small number to prevent division by zero
743 
744  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
745 
746  q_itides = cs%q_itides
747 
748  if (present(full_halos)) then ; if (full_halos) then
749  is = g%isd ; ie = g%ied ; js = g%jsd ; je = g%jed
750  endif ; endif
751 
752  do j=js,je ; do i=is,ie ; do m=1,cs%nMode ; do fr=1,cs%nFreq
753 
754  ! Sum energy across angles
755  en_tot = 0.0
756  do a=1,cs%nAngle
757  en_tot = en_tot + en(i,j,a,fr,m)
758  enddo
759 
760  ! Calculate TKE loss rate; units of [W m-2] here.
761  tke_loss_tot = q_itides * tke_loss_fixed(i,j) * nb(i,j) * ub(i,j,fr,m)**2
762 
763  ! Update energy remaining (this is a pseudo implicit calc)
764  ! (E(t+1)-E(t))/dt = -TKE_loss(E(t+1)/E(t)), which goes to zero as E(t+1) goes to zero
765  if (en_tot > 0.0) then
766  do a=1,cs%nAngle
767  frac_per_sector = en(i,j,a,fr,m)/en_tot
768  tke_loss(i,j,a,fr,m) = frac_per_sector*tke_loss_tot ! Wm-2
769  loss_rate = tke_loss(i,j,a,fr,m) / (en(i,j,a,fr,m) + en_negl) ! s-1
770  en(i,j,a,fr,m) = en(i,j,a,fr,m) / (1.0 + dt*loss_rate)
771  enddo
772  else
773  ! no loss if no energy
774  tke_loss(i,j,:,fr,m) = 0.0
775  endif
776 
777  ! Update energy remaining (this is the old explicit calc)
778  !if (En_tot > 0.0) then
779  ! do a=1,CS%nAngle
780  ! frac_per_sector = En(i,j,a,fr,m)/En_tot
781  ! TKE_loss(i,j,a,fr,m) = frac_per_sector*TKE_loss_tot
782  ! if(TKE_loss(i,j,a,fr,m)*dt <= En(i,j,a,fr,m))then
783  ! En(i,j,a,fr,m) = En(i,j,a,fr,m) - TKE_loss(i,j,a,fr,m)*dt
784  ! else
785  ! call MOM_error(WARNING, "itidal_lowmode_loss: energy loss greater than avalable, "// &
786  ! " setting En to zero.")
787  ! En(i,j,a,fr,m) = 0.0
788  ! endif
789  ! enddo
790  !else
791  ! ! no loss if no energy
792  ! TKE_loss(i,j,:,fr,m) = 0.0
793  !endif
794 
795  enddo ; enddo ; enddo ; enddo
796 
797 end subroutine itidal_lowmode_loss
798 
799 !> This subroutine extracts the energy lost from the propagating internal which has
800 !> been summed across all angles, frequencies, and modes for a given mechanism and location.
801 !> It can be called from another module to get values from this module's (private) CS.
802 subroutine get_lowmode_loss(i,j,G,CS,mechanism,TKE_loss_sum)
803  integer, intent(in) :: i,j
804  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
805  type(int_tide_cs), pointer :: CS
806  character(len=*), intent(in) :: mechanism
807  real, intent(out) :: TKE_loss_sum !< Total energy loss rate due to specified
808  !! mechanism, in W m-2.
809 
810  ! This subroutine extracts the energy lost from the propagating internal which has
811  ! been summed across all angles, frequencies, and modes for a given mechanism and location.
812  ! It can be called from another module to get values from this module's (private) CS.
813  !
814  ! Arguments:
815  ! (out) TKE_loss_sum - total energy loss rate due to specified mechanism, in W m-2.
816 
817  if(mechanism == 'LeakDrag') tke_loss_sum = cs%tot_leak_loss(i,j) ! not used for mixing yet
818  if(mechanism == 'QuadDrag') tke_loss_sum = cs%tot_quad_loss(i,j) ! not used for mixing yet
819  if(mechanism == 'WaveDrag') tke_loss_sum = cs%tot_itidal_loss(i,j) ! currently used for mixing
820  if(mechanism == 'Froude') tke_loss_sum = cs%tot_Froude_loss(i,j) ! not used for mixing yet
821 
822 end subroutine get_lowmode_loss
823 
824 !> This subroutine does refraction on the internal waves at a single frequency.
825 subroutine refract(En, cn, freq, dt, G, NAngle, use_PPMang)
826  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
827  integer, intent(in) :: NAngle
828  real, dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
829  intent(inout) :: En !< The internal gravity wave energy density as a
830  !! function of space and angular resolution,
831  !! in J m-2 radian-1.
832  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
833  intent(in) :: cn !< Baroclinic mode speed, in m s-1.
834  real, intent(in) :: freq !< Wave frequency, in s-1.
835  real, intent(in) :: dt !< Time step, in s.
836  logical, intent(in) :: use_PPMang !< If true, use PPM for advection rather
837  !! than upwind.
838  ! This subroutine does refraction on the internal waves at a single frequency.
839 
840  ! Arguments:
841  ! (inout) En - the internal gravity wave energy density as a function of space
842  ! and angular resolution, in J m-2 radian-1.
843  ! (in) cn - baroclinic mode speed, in m s-1
844  ! (in) freq - wave frequency, in s-1
845  ! (in) dt - time step, in s
846  ! (in) use_PPMang - if true, use PPM for advection rather than upwind
847 
848  integer, parameter :: stencil = 2
849  real, dimension(SZI_(G),1-stencil:NAngle+stencil) :: &
850  En2d
851  real, dimension(1-stencil:NAngle+stencil) :: &
852  cos_angle, sin_angle
853  real, dimension(SZI_(G)) :: &
854  Dk_Dt_Kmag, Dl_Dt_Kmag
855  real, dimension(SZI_(G),0:nAngle) :: &
856  Flux_E
857  real, dimension(SZI_(G),SZJ_(G),1-stencil:NAngle+stencil) :: &
858  CFL_ang
859  real :: f2 ! The squared Coriolis parameter, in s-2.
860  real :: favg ! The average Coriolis parameter at a point, in s-1.
861  real :: df2_dy, df2_dx ! The x- and y- gradients of the squared Coriolis parameter, in s-2 m-1.
862  real :: df_dy, df_dx ! The x- and y- gradients of the Coriolis parameter, in s-1 m-1.
863  real :: dlnCn_dx ! The x-gradient of the wave speed divided by itself in m-1.
864  real :: dlnCn_dy ! The y-gradient of the wave speed divided by itself in m-1.
865  real :: Angle_size, dt_Angle_size, angle
866  real :: Ifreq, Kmag2, I_Kmag
867  real, parameter :: cn_subRO = 1e-100
868  integer :: is, ie, js, je, asd, aed, na
869  integer :: i, j, a
870 
871  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; na = size(en,3)
872  asd = 1-stencil ; aed = nangle+stencil
873 
874  ifreq = 1.0 / freq
875 
876  angle_size = (8.0*atan(1.0)) / (real(nangle))
877  dt_angle_size = dt / angle_size
878 
879  do a=asd,aed
880  angle = (real(A) - 0.5) * angle_size
881  cos_angle(a) = cos(angle) ; sin_angle(a) = sin(angle)
882  enddo
883 
884  !### There should also be refraction due to cn.grad(grid_orientation).
885  cfl_ang(:,:,:) = 0.0;
886  do j=js,je
887  ! Copy En into angle space with halos.
888  do a=1,na ; do i=is,ie
889  en2d(i,a) = en(i,j,a)
890  enddo ; enddo
891  do a=asd,0 ; do i=is,ie
892  en2d(i,a) = en2d(i,a+nangle)
893  en2d(i,nangle+stencil+a) = en2d(i,stencil+a)
894  enddo ; enddo
895 
896  ! Do the refraction.
897  do i=is,ie
898  f2 = 0.25*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j-1)**2) + &
899  (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j)**2))
900  favg = 0.25*((g%CoriolisBu(i,j) + g%CoriolisBu(i-1,j-1)) + &
901  (g%CoriolisBu(i,j-1) + g%CoriolisBu(i-1,j)))
902  df2_dx = 0.5*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i,j-1)**2) - &
903  (g%CoriolisBu(i-1,j)**2 + g%CoriolisBu(i-1,j-1)**2)) * &
904  g%IdxT(i,j)
905  df_dx = 0.5*((g%CoriolisBu(i,j) + g%CoriolisBu(i,j-1)) - &
906  (g%CoriolisBu(i-1,j) + g%CoriolisBu(i-1,j-1))) * &
907  g%IdxT(i,j)
908  dlncn_dx = 0.5*( g%IdxCu(i,j) * (cn(i+1,j) - cn(i,j)) / &
909  (0.5*(cn(i+1,j) + cn(i,j)) + cn_subro) + &
910  g%IdxCu(i-1,j) * (cn(i,j) - cn(i-1,j)) / &
911  (0.5*(cn(i,j) + cn(i-1,j)) + cn_subro) )
912  df2_dy = 0.5*((g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j)**2) - &
913  (g%CoriolisBu(i,j-1)**2 + g%CoriolisBu(i-1,j-1)**2)) * &
914  g%IdyT(i,j)
915  df_dy = 0.5*((g%CoriolisBu(i,j) + g%CoriolisBu(i-1,j)) - &
916  (g%CoriolisBu(i,j-1) + g%CoriolisBu(i-1,j-1))) * &
917  g%IdyT(i,j)
918  dlncn_dy = 0.5*( g%IdyCv(i,j) * (cn(i,j+1) - cn(i,j)) / &
919  (0.5*(cn(i,j+1) + cn(i,j)) + cn_subro) + &
920  g%IdyCv(i,j-1) * (cn(i,j) - cn(i,j-1)) / &
921  (0.5*(cn(i,j) + cn(i,j-1)) + cn_subro) )
922  kmag2 = (freq**2 - f2) / (cn(i,j)**2 + cn_subro**2)
923  if (kmag2 > 0.0) then
924  i_kmag = 1.0 / sqrt(kmag2)
925  dk_dt_kmag(i) = -ifreq * (favg*df_dx + (freq**2 - f2) * dlncn_dx) * i_kmag
926  dl_dt_kmag(i) = -ifreq * (favg*df_dy + (freq**2 - f2) * dlncn_dy) * i_kmag
927  else
928  dk_dt_kmag(i) = 0.0
929  dl_dt_kmag(i) = 0.0
930  endif
931  enddo
932 
933  ! Determine the energy fluxes in angular orientation space.
934  do a=asd,aed ; do i=is,ie
935  cfl_ang(i,j,a) = (cos_angle(a) * dl_dt_kmag(i) - sin_angle(a) * dk_dt_kmag(i)) * &
936  dt_angle_size
937  if (abs(cfl_ang(i,j,a)) > 1.0) then
938  call mom_error(warning, "refract: CFL exceeds 1.", .true.)
939  if (cfl_ang(i,j,a) > 0.0) then ; cfl_ang(i,j,a) = 1.0 ; else ; cfl_ang(i,j,a) = -1.0 ; endif
940  endif
941  enddo; enddo
942 
943  ! Advect in angular space
944  if(.not.use_ppmang) then
945  ! Use simple upwind
946  do a=0,na ; do i=is,ie
947  if (cfl_ang(i,j,a) > 0.0) then
948  flux_e(i,a) = cfl_ang(i,j,a) * en2d(i,a)
949  else
950  flux_e(i,a) = cfl_ang(i,j,a) * en2d(i,a+1)
951  endif
952  enddo; enddo
953  else
954  ! Use PPM
955  do i=is,ie
956  call ppm_angular_advect(en2d(i,:),cfl_ang(i,j,:),flux_e(i,:),nangle,dt,stencil)
957  enddo
958  endif
959 
960  ! Update and copy back to En.
961  do a=1,na ; do i=is,ie
962  !if(En2d(i,a)+(Flux_E(i,A-1)-Flux_E(i,A)) < 0.0)then ! for debugging
963  ! print *,"refract: OutFlux>Available" ; !stop
964  !endif
965  en(i,j,a) = en2d(i,a) + (flux_e(i,a-1) - flux_e(i,a))
966  enddo ; enddo
967  enddo ! j-loop
968 end subroutine refract
969 
970 !> This subroutine calculates the 1-d flux for advection in angular space
971 !! using a monotonic piecewise parabolic scheme. Should be within i and j spatial
972 !! loops.
973 subroutine ppm_angular_advect(En2d, CFL_ang, Flux_En, NAngle, dt, halo_ang)
974  integer, intent(in) :: NAngle
975  real, intent(in) :: dt
976  integer, intent(in) :: halo_ang
977  real, dimension(1-halo_ang:NAngle+halo_ang), &
978  intent(in) :: En2d
979  real, dimension(1-halo_ang:NAngle+halo_ang), &
980  intent(in) :: CFL_ang
981  real, dimension(0:NAngle), intent(out) :: Flux_En
982 
983  ! This subroutine calculates the 1-d flux for advection in angular space
984  ! using a monotonic piecewise parabolic scheme. Should be within i and j spatial
985  ! loops
986  real :: flux
987  real :: u_ang
988  real :: Angle_size
989  real :: I_Angle_size
990  real :: I_dt
991  integer :: a
992  real :: aR, aL, dMx, dMn, Ep, Ec, Em, dA, mA, a6
993 
994  i_dt = 1 / dt
995  angle_size = (8.0*atan(1.0)) / (real(nangle))
996  i_angle_size = 1 / angle_size
997  flux_en(:) = 0
998 
999  do a=0,nangle
1000  u_ang = cfl_ang(a)*angle_size*i_dt
1001  if (u_ang >= 0.0) then
1002  ! Implementation of PPM-H3
1003  ep = en2d(a+1)*i_angle_size !MEAN ANGULAR ENERGY DENSITY FOR WEDGE (Jm-2/rad)
1004  ec = en2d(a) *i_angle_size !MEAN ANGULAR ENERGY DENSITY FOR WEDGE (Jm-2/rad)
1005  em = en2d(a-1)*i_angle_size !MEAN ANGULAR ENERGY DENSITY FOR WEDGE (Jm-2/rad)
1006  al = ( 5.*ec + ( 2.*em - ep ) )/6. ! H3 estimate
1007  al = max( min(ec,em), al) ; al = min( max(ec,em), al) ! Bound
1008  ar = ( 5.*ec + ( 2.*ep - em ) )/6. ! H3 estimate
1009  ar = max( min(ec,ep), ar) ; ar = min( max(ec,ep), ar) ! Bound
1010  da = ar - al ; ma = 0.5*( ar + al )
1011  if ((ep-ec)*(ec-em) <= 0.) then
1012  al = ec ; ar = ec ! PCM for local extremum
1013  elseif ( da*(ec-ma) > (da*da)/6. ) then
1014  al = 3.*ec - 2.*ar !?
1015  elseif ( da*(ec-ma) < - (da*da)/6. ) then
1016  ar = 3.*ec - 2.*al !?
1017  endif
1018  a6 = 6.*ec - 3. * (ar + al) ! Curvature
1019  ! CALCULATE FLUX RATE (Jm-2/s)
1020  flux = u_ang*( ar + 0.5 * cfl_ang(a) * ( ( al - ar ) + a6 * ( 1. - 2./3. * cfl_ang(a) ) ) )
1021  !flux = u_ang*( aR - 0.5 * CFL_ang(A) * ( ( aR - aL ) - a6 * ( 1. - 2./3. * CFL_ang(A) ) ) )
1022  ! CALCULATE AMOUNT FLUXED (Jm-2)
1023  flux_en(a) = dt * flux
1024  !Flux_En(A) = (dt * I_Angle_size) * flux
1025  else
1026  ! Implementation of PPM-H3
1027  ep = en2d(a+2)*i_angle_size !MEAN ANGULAR ENERGY DENSITY FOR WEDGE (Jm-2/rad)
1028  ec = en2d(a+1)*i_angle_size !MEAN ANGULAR ENERGY DENSITY FOR WEDGE (Jm-2/rad)
1029  em = en2d(a) *i_angle_size !MEAN ANGULAR ENERGY DENSITY FOR WEDGE (Jm-2/rad)
1030  al = ( 5.*ec + ( 2.*em - ep ) )/6. ! H3 estimate
1031  al = max( min(ec,em), al) ; al = min( max(ec,em), al) ! Bound
1032  ar = ( 5.*ec + ( 2.*ep - em ) )/6. ! H3 estimate
1033  ar = max( min(ec,ep), ar) ; ar = min( max(ec,ep), ar) ! Bound
1034  da = ar - al ; ma = 0.5*( ar + al )
1035  if ((ep-ec)*(ec-em) <= 0.) then
1036  al = ec ; ar = ec ! PCM for local extremum
1037  elseif ( da*(ec-ma) > (da*da)/6. ) then
1038  al = 3.*ec - 2.*ar
1039  elseif ( da*(ec-ma) < - (da*da)/6. ) then
1040  ar = 3.*ec - 2.*al
1041  endif
1042  a6 = 6.*ec - 3. * (ar + al) ! Curvature
1043  ! CALCULATE FLUX RATE (Jm-2/s)
1044  flux = u_ang*( ar + 0.5 * cfl_ang(a) * ( ( al - ar ) + a6 * ( 1. - 2./3. * cfl_ang(a) ) ) )
1045  !flux = u_ang*( aL + 0.5 * CFL_ang(A) * ( ( aR - aL ) + a6 * ( 1. - 2./3. * CFL_ang(A) ) ) )
1046  ! CALCULATE AMOUNT FLUXED (Jm-2)
1047  flux_en(a) = dt * flux
1048  !Flux_En(A) = (dt * I_Angle_size) * flux
1049  endif
1050  enddo
1051 end subroutine ppm_angular_advect
1052 
1053 !> This subroutine does refraction on the internal waves at a single frequency.
1054 subroutine propagate(En, cn, freq, dt, G, CS, NAngle)
1055  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure.
1056  integer, intent(in) :: NAngle
1057  real, dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
1058  intent(inout) :: En !< The internal gravity wave energy density as a
1059  !! function of space and angular resolution,
1060  !! in J m-2 radian-1.
1061  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
1062  intent(in) :: cn !< Baroclinic mode speed, in m s-1.
1063  real, intent(in) :: freq !< Wave frequency, in s-1.
1064  real, intent(in) :: dt !< Time step, in s.
1065  type(int_tide_cs), pointer :: CS
1066  ! This subroutine does refraction on the internal waves at a single frequency.
1067 
1068  ! Arguments:
1069  ! (inout) En - the internal gravity wave energy density as a function of space
1070  ! and angular resolution, in J m-2 radian-1.
1071  ! (in) cn - baroclinic mode speed, in m s-1
1072  ! (in) freq - wave frequency, in s-1
1073  ! (in) dt - time step, in s
1074 
1075  real, dimension(G%IsdB:G%IedB,G%JsdB:G%JedB) :: &
1076  speed ! The magnitude of the group velocity at the q points for corner adv, in m s-1.
1077  integer, parameter :: stencil = 2
1078  real, dimension(SZIB_(G),SZJ_(G)) :: &
1079  speed_x ! The magnitude of the group velocity at the Cu points, in m s-1.
1080  real, dimension(SZI_(G),SZJB_(G)) :: &
1081  speed_y ! The magnitude of the group velocity at the Cv points, in m s-1.
1082  real, dimension(0:NAngle) :: &
1083  cos_angle, sin_angle
1084  real, dimension(NAngle) :: &
1085  Cgx_av, Cgy_av, dCgx, dCgy
1086  real :: f2 ! The squared Coriolis parameter, in s-2.
1087  real :: Angle_size, I_Angle_size, angle
1088  real :: Ifreq, freq2
1089  real, parameter :: cn_subRO = 1e-100
1090  type(loop_bounds_type) :: LB
1091  integer :: is, ie, js, je, asd, aed, na
1092  integer :: ish, ieh, jsh, jeh
1093  integer :: i, j, a
1094 
1095  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec ; na = size(en,3)
1096  asd = 1-stencil ; aed = nangle+stencil
1097 
1098  ifreq = 1.0 / freq
1099  freq2 = freq**2
1100 
1101  ! Define loop bounds: Need extensions on j-loop so propagate_y
1102  ! (done after propagate_x) will have updated values in the halo
1103  ! for correct PPM reconstruction. Use if no teleporting and
1104  ! no pass_var between propagate_x and propagate_y.
1105  !jsh = js-3 ; jeh = je+3 ; ish = is ; ieh = ie
1106 
1107  ! Define loop bounds: Need 1-pt extensions on loops because
1108  ! teleporting eats up a halo point. Use if teleporting.
1109  ! Also requires pass_var before propagate_y.
1110  jsh = js-1 ; jeh = je+1 ; ish = is-1 ; ieh = ie+1
1111 
1112  angle_size = (8.0*atan(1.0)) / real(nangle)
1113  i_angle_size = 1.0 / angle_size
1114 
1115  if (cs%corner_adv) then
1116  ! IMPLEMENT CORNER ADVECTION IN HORIZONTAL--------------------
1117  ! FIND AVERAGE GROUP VELOCITY (SPEED) AT CELL CORNERS;
1118  ! NOTE: THIS HAS NOT BE ADAPTED FOR REFLECTION YET (BDM)!!
1119  ! Fix indexing here later
1120  speed(:,:) = 0;
1121  do j=jsh-1,jeh ; do i=ish-1,ieh
1122  f2 = g%CoriolisBu(i,j)**2
1123  speed(i,j) = 0.25*(cn(i,j) + cn(i+1,j) + cn(i+1,j+1) + cn(i,j+1)) * &
1124  sqrt(max(freq2 - f2, 0.0)) * ifreq
1125  enddo ; enddo
1126  do a=1,na
1127  ! Apply the propagation WITH CORNER ADVECTION/FINITE VOLUME APPROACH.
1128  lb%jsh = js ; lb%jeh = je ; lb%ish = is ; lb%ieh = ie
1129  call propagate_corner_spread(en(:,:,a), a, nangle, speed, dt, g, cs, lb)
1130  end do ! a-loop
1131  else
1132  ! IMPLEMENT PPM ADVECTION IN HORIZONTAL-----------------------
1133  ! These could be in the control structure, as they do not vary.
1134  do a=0,na
1135  ! These are the angles at the cell edges...
1136  angle = (real(A) - 0.5) * angle_size
1137  cos_angle(a) = cos(angle) ; sin_angle(a) = sin(angle)
1138  enddo
1139 
1140  do a=1,na
1141  cgx_av(a) = (sin_angle(a) - sin_angle(a-1)) * i_angle_size
1142  cgy_av(a) = -(cos_angle(a) - cos_angle(a-1)) * i_angle_size
1143  dcgx(a) = sqrt(0.5 + 0.5*(sin_angle(a)*cos_angle(a) - &
1144  sin_angle(a-1)*cos_angle(a-1)) * i_angle_size - &
1145  cgx_av(a)**2)
1146  dcgy(a) = sqrt(0.5 - 0.5*(sin_angle(a)*cos_angle(a) - &
1147  sin_angle(a-1)*cos_angle(a-1)) * i_angle_size - &
1148  cgy_av(a)**2)
1149  enddo
1150 
1151  do j=jsh,jeh ; do i=ish-1,ieh
1152  f2 = 0.5*(g%CoriolisBu(i,j)**2 + g%CoriolisBu(i,j-1)**2)
1153  speed_x(i,j) = 0.5*(cn(i,j) + cn(i+1,j)) * g%mask2dCu(i,j) * &
1154  sqrt(max(freq2 - f2, 0.0)) * ifreq
1155  enddo ; enddo
1156  do j=jsh-1,jeh ; do i=ish,ieh
1157  f2 = 0.5*(g%CoriolisBu(i,j)**2 + g%CoriolisBu(i-1,j)**2)
1158  speed_y(i,j) = 0.5*(cn(i,j) + cn(i,j+1)) * g%mask2dCv(i,j) * &
1159  sqrt(max(freq2 - f2, 0.0)) * ifreq
1160  enddo ; enddo
1161 
1162  ! Apply propagation in x-direction (reflection included)
1163  lb%jsh = jsh ; lb%jeh = jeh ; lb%ish = ish ; lb%ieh = ieh
1164  call propagate_x(en(:,:,:), speed_x, cgx_av(:), dcgx(:), dt, g, cs%nAngle, cs, lb)
1165 
1166  ! Check for energy conservation on computational domain (for debugging)
1167  !call sum_En(G,CS,En(:,:,:),'post-propagate_x')
1168 
1169  ! Update halos
1170  call pass_var(en(:,:,:),g%domain)
1171 
1172  ! Apply propagation in y-direction (reflection included)
1173  ! LB%jsh = js ; LB%jeh = je ; LB%ish = is ; LB%ieh = ie ! Use if no teleport
1174  lb%jsh = jsh ; lb%jeh = jeh ; lb%ish = ish ; lb%ieh = ieh
1175  call propagate_y(en(:,:,:), speed_y, cgy_av(:), dcgy(:), dt, g, cs%nAngle, cs, lb)
1176 
1177  ! Check for energy conservation on computational domain (for debugging)
1178  !call sum_En(G,CS,En(:,:,:),'post-propagate_y')
1179 
1180  endif
1181 end subroutine propagate
1182 
1183 !> This subroutine does first-order corner advection. It was written with the hopes
1184 !! of smoothing out the garden sprinkler effect, but is too numerically diffusive to
1185 !! be of much use as of yet. It is not yet compatible with reflection schemes (BDM).
1186 subroutine propagate_corner_spread(En, energized_wedge, NAngle, speed, dt, G, CS, LB)
1187  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1188  real, dimension(G%isd:G%ied,G%jsd:G%jed), &
1189  intent(inout) :: En !< The energy density integrated over an angular
1190  !! band, in W m-2, intent in/out.
1191  real, dimension(G%IsdB:G%IedB,G%Jsd:G%Jed), &
1192  intent(in) :: speed !< The magnitude of the group velocity at the cell
1193  !! corner points, in m s-1.
1194  integer, intent(in) :: energized_wedge !< Index of current ray direction.
1195  integer, intent(in) :: NAngle
1196  real, intent(in) :: dt !< Time increment in s.
1197  type(int_tide_cs), pointer :: CS !< The control structure returned by a previous
1198  !! call to continuity_PPM_init.
1199  type(loop_bounds_type), intent(in) :: LB !< A structure with the active energy loop bounds.
1200 
1201  ! This subroutine does first-order corner advection. It was written with the hopes
1202  ! of smoothing out the garden sprinkler effect, but is too numerically diffusive to
1203  ! be of much use as of yet. It is not yet compatible with reflection schemes (BDM).
1204 
1205  ! Arguments: En - The energy density integrated over an angular band, in W m-2,
1206  ! intent in/out.
1207  ! (in) energized_wedge - index of current ray direction
1208  ! (in) speed - The magnitude of the group velocity at the cell corner
1209  ! points, in m s-1.
1210  ! (in) dt - Time increment in s.
1211  ! (in) G - The ocean's grid structure.
1212  ! (in) CS - The control structure returned by a previous call to
1213  ! continuity_PPM_init.
1214  ! (in) LB - A structure with the active energy loop bounds.
1215 
1216  integer :: i, j, k, ish, ieh, jsh, jeh, m
1217  real :: TwoPi, Angle_size
1218  real :: energized_angle ! angle through center of current wedge
1219  real :: theta ! angle at edge of wedge
1220  real :: Nsubrays ! number of sub-rays for averaging;
1221  ! count includes the two rays that bound the current wedge,
1222  ! i.e. those at -dtheta/2 and +dtheta/2 from energized angle
1223  real :: I_Nsubwedges ! inverse of number of sub-wedges
1224  real :: cos_thetaDT, sin_thetaDT ! cos(theta)*dt, sin(theta)*dt
1225  real :: xNE,xNW,xSW,xSE,yNE,yNW,ySW,ySE ! corner point coordinates of advected fluid parcel
1226  real :: CFL_xNE,CFL_xNW,CFL_xSW,CFL_xSE,CFL_yNE,CFL_yNW,CFL_ySW,CFL_ySE,CFL_max
1227  real :: xN,xS,xE,xW,yN,yS,yE,yW ! intersection point coordinates of parcel edges and grid
1228  real :: xCrn,yCrn ! grid point contained within advected fluid parcel
1229  real :: xg,yg ! grid point of interest
1230  real :: slopeN,slopeW,slopeS,slopeE, bN,bW,bS,bE ! parameters defining parcel sides
1231  real :: aNE,aN,aNW,aW,aSW,aS,aSE,aE,aC ! sub-areas of advected parcel
1232  real :: a_total ! total area of advected parcel
1233  real :: a1,a2,a3,a4 ! areas used in calculating polygon areas (sub-areas) of advected parcel
1234  real, dimension(G%IsdB:G%IedB,G%Jsd:G%Jed) :: x,y ! coordinates of cell corners
1235  real, dimension(G%IsdB:G%IedB,G%Jsd:G%Jed) :: Idx,Idy ! inverse of dx,dy at cell corners
1236  real, dimension(G%IsdB:G%IedB,G%Jsd:G%Jed) :: dx,dy ! dx,dy at cell corners
1237  real, dimension(2) :: E_new ! energy in cell after advection for subray; set size here to
1238  ! define Nsubrays - this should be made an input option later!
1239 
1240  ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1241  twopi = (8.0*atan(1.0))
1242  nsubrays = real(size(e_new))
1243  i_nsubwedges = 1./(nsubrays - 1)
1244 
1245  angle_size = twopi / real(nangle)
1246  energized_angle = angle_size * real(energized_wedge - 1) ! for a=1 aligned with x-axis
1247  !energized_angle = Angle_size * real(energized_wedge - 1) + 2.0*Angle_size !
1248  !energized_angle = Angle_size * real(energized_wedge - 1) + 0.5*Angle_size !
1249  x = g%geoLonBu
1250  y = g%geoLatBu
1251  idx = g%IdxBu; dx = g%dxBu
1252  idy = g%IdyBu; dy = g%dyBu
1253 
1254  do j=jsh,jeh; do i=ish,ieh
1255  do m=1,int(nsubrays)
1256  theta = energized_angle - 0.5*angle_size + real(m - 1)*Angle_size*I_Nsubwedges
1257  if (theta < 0.0) then
1258  theta = theta + twopi
1259  elseif (theta > twopi) then
1260  theta = theta - twopi
1261  endif
1262  cos_thetadt = cos(theta)*dt
1263  sin_thetadt = sin(theta)*dt
1264 
1265  ! corner point coordinates of advected fluid parcel ----------
1266  xg = x(i,j); yg = y(i,j)
1267  xne = xg - speed(i,j)*cos_thetadt
1268  yne = yg - speed(i,j)*sin_thetadt
1269  cfl_xne = (xg-xne)*idx(i,j)
1270  cfl_yne = (yg-yne)*idy(i,j)
1271 
1272  xg = x(i-1,j); yg = y(i-1,j)
1273  xnw = xg - speed(i-1,j)*cos_thetadt
1274  ynw = yg - speed(i-1,j)*sin_thetadt
1275  cfl_xnw = (xg-xnw)*idx(i-1,j)
1276  cfl_ynw = (yg-ynw)*idy(i-1,j)
1277 
1278  xg = x(i-1,j-1); yg = y(i-1,j-1)
1279  xsw = xg - speed(i-1,j-1)*cos_thetadt
1280  ysw = yg - speed(i-1,j-1)*sin_thetadt
1281  cfl_xsw = (xg-xsw)*idx(i-1,j-1)
1282  cfl_ysw = (yg-ysw)*idy(i-1,j-1)
1283 
1284  xg = x(i,j-1); yg = y(i,j-1)
1285  xse = xg - speed(i,j-1)*cos_thetadt
1286  yse = yg - speed(i,j-1)*sin_thetadt
1287  cfl_xse = (xg-xse)*idx(i,j-1)
1288  cfl_yse = (yg-yse)*idy(i,j-1)
1289 
1290  cfl_max = max(abs(cfl_xne),abs(cfl_xnw),abs(cfl_xsw), &
1291  abs(cfl_xse),abs(cfl_yne),abs(cfl_ynw), &
1292  abs(cfl_ysw),abs(cfl_yse))
1293  if (cfl_max > 1.0) then
1294  call mom_error(warning, "propagate_corner_spread: CFL exceeds 1.", .true.)
1295  endif
1296 
1297  ! intersection point coordinates of parcel edges and cell edges ---
1298  if (0.0 <= theta .and. theta < 0.25*twopi) then
1299  xn = x(i-1,j-1)
1300  yw = y(i-1,j-1)
1301  elseif (0.25*twopi <= theta .and. theta < 0.5*twopi) then
1302  xn = x(i,j-1)
1303  yw = y(i,j-1)
1304  elseif (0.5*twopi <= theta .and. theta < 0.75*twopi) then
1305  xn = x(i,j)
1306  yw = y(i,j)
1307  elseif (0.75*twopi <= theta .and. theta <= 1.00*twopi) then
1308  xn = x(i-1,j)
1309  yw = y(i-1,j)
1310  endif
1311  xs = xn
1312  ye = yw
1313 
1314  ! north intersection
1315  slopen = (yne - ynw)/(xne - xnw)
1316  bn = -slopen*xne + yne
1317  yn = slopen*xn + bn
1318  ! west intersection
1319  if (xnw == xsw) then
1320  xw = xnw
1321  else
1322  slopew = (ynw - ysw)/(xnw - xsw)
1323  bw = -slopew*xnw + ynw
1324  xw = (yw - bw)/slopew
1325  endif
1326  ! south intersection
1327  slopes = (ysw - yse)/(xsw - xse)
1328  bs = -slopes*xsw + ysw
1329  ys = slopes*xs + bs
1330  ! east intersection
1331  if (xne == xse) then
1332  xe = xne
1333  else
1334  slopee = (yse - yne)/(xse - xne)
1335  be = -slopee*xse + yse
1336  xe = (ye - be)/slopee
1337  endif
1338 
1339  ! areas --------------------------------------------
1340  ane = 0.0; an = 0.0; anw = 0.0; ! initialize areas
1341  aw = 0.0; asw = 0.0; as = 0.0; ! initialize areas
1342  ase = 0.0; ae = 0.0; ac = 0.0; ! initialize areas
1343  if (0.0 <= theta .and. theta < 0.25*twopi) then
1344  xcrn = x(i-1,j-1); ycrn = y(i-1,j-1);
1345  ! west area
1346  a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1347  a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1348  a3 = (yw - ynw)*(0.5*(xw + xnw))
1349  a4 = (ynw - yn)*(0.5*(xnw + xn))
1350  aw = a1 + a2 + a3 + a4
1351  ! southwest area
1352  a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1353  a2 = (ys - ysw)*(0.5*(xs + xsw))
1354  a3 = (ysw - yw)*(0.5*(xsw + xw))
1355  a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1356  asw = a1 + a2 + a3 + a4
1357  ! south area
1358  a1 = (ye - yse)*(0.5*(xe + xse))
1359  a2 = (yse - ys)*(0.5*(xse + xs))
1360  a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1361  a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1362  as = a1 + a2 + a3 + a4
1363  ! area within cell
1364  a1 = (yne - ye)*(0.5*(xne + xe))
1365  a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1366  a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1367  a4 = (yn - yne)*(0.5*(xn + xne))
1368  ac = a1 + a2 + a3 + a4
1369  elseif (0.25*twopi <= theta .and. theta < 0.5*twopi) then
1370  xcrn = x(i,j-1); ycrn = y(i,j-1);
1371  ! south area
1372  a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1373  a2 = (ys - ysw)*(0.5*(xs + xsw))
1374  a3 = (ysw - yw)*(0.5*(xsw + xw))
1375  a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1376  as = a1 + a2 + a3 + a4
1377  ! southeast area
1378  a1 = (ye - yse)*(0.5*(xe + xse))
1379  a2 = (yse - ys)*(0.5*(xse + xs))
1380  a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1381  a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1382  ase = a1 + a2 + a3 + a4
1383  ! east area
1384  a1 = (yne - ye)*(0.5*(xne + xe))
1385  a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1386  a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1387  a4 = (yn - yne)*(0.5*(xn + xne))
1388  ae = a1 + a2 + a3 + a4
1389  ! area within cell
1390  a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1391  a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1392  a3 = (yw - ynw)*(0.5*(xw + xnw))
1393  a4 = (ynw - yn)*(0.5*(xnw + xn))
1394  ac = a1 + a2 + a3 + a4
1395  elseif (0.5*twopi <= theta .and. theta < 0.75*twopi) then
1396  xcrn = x(i,j); ycrn = y(i,j);
1397  ! east area
1398  a1 = (ye - yse)*(0.5*(xe + xse))
1399  a2 = (yse - ys)*(0.5*(xse + xs))
1400  a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1401  a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1402  ae = a1 + a2 + a3 + a4
1403  ! northeast area
1404  a1 = (yne - ye)*(0.5*(xne + xe))
1405  a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1406  a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1407  a4 = (yn - yne)*(0.5*(xn + xne))
1408  ane = a1 + a2 + a3 + a4
1409  ! north area
1410  a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1411  a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1412  a3 = (yw - ynw)*(0.5*(xw + xnw))
1413  a4 = (ynw - yn)*(0.5*(xnw + xn))
1414  an = a1 + a2 + a3 + a4
1415  ! area within cell
1416  a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1417  a2 = (ys - ysw)*(0.5*(xs + xsw))
1418  a3 = (ysw - yw)*(0.5*(xsw + xw))
1419  a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1420  ac = a1 + a2 + a3 + a4
1421  elseif (0.75*twopi <= theta .and. theta <= 1.00*twopi) then
1422  xcrn = x(i-1,j); ycrn = y(i-1,j);
1423  ! north area
1424  a1 = (yne - ye)*(0.5*(xne + xe))
1425  a2 = (ye - ycrn)*(0.5*(xe + xcrn))
1426  a3 = (ycrn - yn)*(0.5*(xcrn + xn))
1427  a4 = (yn - yne)*(0.5*(xn + xne))
1428  an = a1 + a2 + a3 + a4
1429  ! northwest area
1430  a1 = (yn - ycrn)*(0.5*(xn + xcrn))
1431  a2 = (ycrn - yw)*(0.5*(xcrn + xw))
1432  a3 = (yw - ynw)*(0.5*(xw + xnw))
1433  a4 = (ynw - yn)*(0.5*(xnw + xn))
1434  anw = a1 + a2 + a3 + a4;
1435  ! west area
1436  a1 = (ycrn - ys)*(0.5*(xcrn + xs))
1437  a2 = (ys - ysw)*(0.5*(xs + xsw))
1438  a3 = (ysw - yw)*(0.5*(xsw + xw))
1439  a4 = (yw - ycrn)*(0.5*(xw + xcrn))
1440  aw = a1 + a2 + a3 + a4
1441  ! area within cell
1442  a1 = (ye - yse)*(0.5*(xe + xse))
1443  a2 = (yse - ys)*(0.5*(xse + xs))
1444  a3 = (ys - ycrn)*(0.5*(xs + xcrn))
1445  a4 = (ycrn - ye)*(0.5*(xcrn + xe))
1446  ac = a1 + a2 + a3 + a4
1447  endif
1448 
1449  ! energy weighting ----------------------------------------
1450  a_total = ane + an + anw + aw + asw + as + ase + ae + ac
1451  e_new(m) = (ane*en(i+1,j+1) + an*en(i,j+1) + anw*en(i-1,j+1) + &
1452  aw*en(i-1,j) + asw*en(i-1,j-1) + as*en(i,j-1) + &
1453  ase*en(i+1,j-1) + ae*en(i+1,j) + ac*en(i,j)) / (dx(i,j)*dy(i,j))
1454  enddo ! m-loop
1455  ! update energy in cell
1456  en(i,j) = sum(e_new)/nsubrays
1457  enddo; enddo
1458 end subroutine propagate_corner_spread
1459 
1460 ! #@# This subroutine needs a doxygen description
1461 subroutine propagate_x(En, speed_x, Cgx_av, dCgx, dt, G, Nangle, CS, LB)
1462  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1463  integer, intent(in) :: NAngle
1464  real, dimension(G%isd:G%ied,G%jsd:G%jed,Nangle), &
1465  intent(inout) :: En !< The energy density integrated over an angular
1466  !! band, in J m-2, intent in/out.
1467  real, dimension(G%IsdB:G%IedB,G%jsd:G%jed), &
1468  intent(in) :: speed_x !< The magnitude of the group velocity at the
1469  !! Cu points, in m s-1.
1470  real, dimension(Nangle), intent(in) :: Cgx_av, dCgx
1471  real, intent(in) :: dt !< Time increment in s.
1472  type(int_tide_cs), pointer :: CS !< The control structure returned by a previous call
1473  !! to continuity_PPM_init.
1474  type(loop_bounds_type), intent(in) :: LB !< A structure with the active energy loop bounds.
1475 
1476  ! Arguments: En - The energy density integrated over an angular band, in J m-2,
1477  ! intent in/out.
1478  ! (in) speed_x - The magnitude of the group velocity at the Cu
1479  ! points, in m s-1.
1480  ! (in) dt - Time increment in s.
1481  ! (in) G - The ocean's grid structure.
1482  ! (in) CS - The control structure returned by a previous call to
1483  ! continuity_PPM_init.
1484  ! (in) LB - A structure with the active energy loop bounds.
1485  real, dimension(SZI_(G),SZJ_(G)) :: &
1486  EnL, EnR ! Left and right face energy densities, in J m-2.
1487  real, dimension(SZIB_(G),SZJ_(G)) :: &
1488  flux_x ! The internal wave energy flux, in J s-1.
1489  real, dimension(SZIB_(G)) :: &
1490  cg_p, cg_m, flux1, flux2
1491  !real, dimension(SZI_(G),SZJB_(G),Nangle) :: En_m, En_p
1492  real, dimension(SZI_(G),SZJB_(G),Nangle) :: &
1493  Fdt_m, Fdt_p! Left and right energy fluxes, in J
1494  integer :: i, j, k, ish, ieh, jsh, jeh, a
1495 
1496  ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1497  do a=1,nangle
1498  ! This sets EnL and EnR.
1499  if (cs%upwind_1st) then
1500  do j=jsh,jeh ; do i=ish-1,ieh+1
1501  enl(i,j) = en(i,j,a) ; enr(i,j) = en(i,j,a)
1502  enddo ; enddo
1503  else
1504  call ppm_reconstruction_x(en(:,:,a), enl, enr, g, lb, simple_2nd=cs%simple_2nd)
1505  endif
1506 
1507  do j=jsh,jeh
1508  ! This is done once with single speed (GARDEN SPRINKLER EFFECT POSSIBLE)
1509  do i=ish-1,ieh
1510  cg_p(i) = speed_x(i,j) * (cgx_av(a))
1511  enddo
1512  call zonal_flux_en(cg_p, en(:,j,a), enl(:,j), enr(:,j), flux1, &
1513  dt, g, j, ish, ieh, cs%vol_CFL)
1514  do i=ish-1,ieh ; flux_x(i,j) = flux1(i); enddo
1515  enddo
1516 
1517  do j=jsh,jeh ; do i=ish,ieh
1518  fdt_m(i,j,a) = dt*flux_x(i-1,j) ! left face influx (J)
1519  fdt_p(i,j,a) = -dt*flux_x(i,j) ! right face influx (J)
1520  enddo ; enddo
1521 
1522  ! test with old (take out later)
1523  !do j=LB%jsh,LB%jeh ; do i=LB%ish,LB%ieh
1524  ! En(i,j,a) = En(i,j,a) - dt* G%IareaT(i,j) * (flux_x(I,j) - flux_x(I-1,j))
1525  !enddo ; enddo
1526 
1527  enddo ! a-loop
1528 
1529  ! Only reflect newly arrived energy; existing energy in incident wedge
1530  ! is not reflected and will eventually propagate out of cell.
1531  ! (only reflects if En > 0)
1532  call reflect(fdt_m(:,:,:), nangle, cs, g, lb)
1533  call teleport(fdt_m(:,:,:), nangle, cs, g, lb)
1534  call reflect(fdt_p(:,:,:), nangle, cs, g, lb)
1535  call teleport(fdt_p(:,:,:), nangle, cs, g, lb)
1536 
1537  ! Update reflected energy (Jm-2)
1538  do j=jsh,jeh ; do i=ish,ieh
1539  !do a=1,CS%nAngle
1540  ! if((En(i,j,a) + G%IareaT(i,j)*(Fdt_m(i,j,a) + Fdt_p(i,j,a))) < 0.0)then ! for debugging
1541  ! print *,"propagate_x: OutFlux>Available" ; !stop
1542  ! endif
1543  !enddo
1544  en(i,j,:) = en(i,j,:) + g%IareaT(i,j)*(fdt_m(i,j,:) + fdt_p(i,j,:))
1545  enddo ; enddo
1546 
1547 end subroutine propagate_x
1548 
1549 ! #@# This subroutine needs a doxygen description.
1550 subroutine propagate_y(En, speed_y, Cgy_av, dCgy, dt, G, Nangle, CS, LB)
1551  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1552  integer, intent(in) :: NAngle
1553  real, dimension(G%isd:G%ied,G%jsd:G%jed,Nangle), &
1554  intent(inout) :: En !< The energy density integrated over an angular
1555  !! band, in J m-2, intent in/out.
1556  real, dimension(G%isd:G%ied,G%JsdB:G%JedB), &
1557  intent(in) :: speed_y !< The magnitude of the group velocity at the
1558  !! Cv points, in m s-1.
1559  real, dimension(Nangle), intent(in) :: Cgy_av, dCgy
1560  real, intent(in) :: dt !< Time increment in s.
1561  type(int_tide_cs), pointer :: CS !< The control structure returned by a previous call
1562  !! to continuity_PPM_init.
1563  type(loop_bounds_type), intent(in) :: LB !< A structure with the active energy loop bounds.
1564 
1565  ! Arguments: En - The energy density integrated over an angular band, in J m-2,
1566  ! intent in/out.
1567  ! (in) speed_y - The magnitude of the group velocity at the Cv
1568  ! points, in m s-1.
1569  ! (in) dt - Time increment in s.
1570  ! (in) G - The ocean's grid structure.
1571  ! (in) CS - The control structure returned by a previous call to
1572  ! continuity_PPM_init.
1573  ! (in) LB - A structure with the active energy loop bounds.
1574  real, dimension(SZI_(G),SZJ_(G)) :: &
1575  EnL, EnR ! South and north face energy densities, in J m-2.
1576  real, dimension(SZI_(G),SZJB_(G)) :: &
1577  flux_y ! The internal wave energy flux, in J s-1.
1578  real, dimension(SZI_(G)) :: &
1579  cg_p, cg_m, flux1, flux2
1580  !real, dimension(SZI_(G),SZJB_(G),Nangle) :: En_m, En_p
1581  real, dimension(SZI_(G),SZJB_(G),Nangle) :: &
1582  Fdt_m, Fdt_p! South and north energy fluxes, in J
1583  integer :: i, j, k, ish, ieh, jsh, jeh, a
1584 
1585  ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1586  do a=1,nangle
1587  ! This sets EnL and EnR.
1588  if (cs%upwind_1st) then
1589  do j=jsh-1,jeh+1 ; do i=ish,ieh
1590  enl(i,j) = en(i,j,a) ; enr(i,j) = en(i,j,a)
1591  enddo ; enddo
1592  else
1593  call ppm_reconstruction_y(en(:,:,a), enl, enr, g, lb, simple_2nd=cs%simple_2nd)
1594  endif
1595 
1596  do j=jsh-1,jeh
1597  ! This is done once with single speed (GARDEN SPRINKLER EFFECT POSSIBLE)
1598  do i=ish,ieh
1599  cg_p(i) = speed_y(i,j) * (cgy_av(a))
1600  enddo
1601  call merid_flux_en(cg_p, en(:,:,a), enl(:,:), enr(:,:), flux1, &
1602  dt, g, j, ish, ieh, cs%vol_CFL)
1603  do i=ish,ieh ; flux_y(i,j) = flux1(i); enddo
1604  enddo
1605 
1606  do j=jsh,jeh ; do i=ish,ieh
1607  fdt_m(i,j,a) = dt*flux_y(i,j-1) ! south face influx (J)
1608  fdt_p(i,j,a) = -dt*flux_y(i,j) ! north face influx (J)
1609  !if((En(i,j,a) + G%IareaT(i,j)*(Fdt_m(i,j,a) + Fdt_p(i,j,a))) < 0.0)then ! for debugging
1610  ! print *,"propagate_y: OutFlux>Available prior to reflection" ; !stop
1611  ! print *,"flux_y_south=",flux_y(i,J-1)
1612  ! print *,"flux_y_north=",flux_y(i,J)
1613  ! print *,"En=",En(i,j,a)
1614  ! print *,"cn_south=", speed_y(i,J-1) * (Cgy_av(a))
1615  ! print *,"cn_north=", speed_y(i,J) * (Cgy_av(a))
1616  !endif
1617  enddo ; enddo
1618 
1619  ! test with old (take out later)
1620  !do j=jsh,jeh ; do i=ish,ieh
1621  ! En(i,j,a) = En(i,j,a) - dt* G%IareaT(i,j) * (flux_y(i,J) - flux_y(i,J-1))
1622  !enddo ; enddo
1623 
1624  enddo ! a-loop
1625 
1626  ! Only reflect newly arrived energy; existing energy in incident wedge
1627  ! is not reflected and will eventually propagate out of cell.
1628  ! (only reflects if En > 0)
1629  call reflect(fdt_m(:,:,:), nangle, cs, g, lb)
1630  call teleport(fdt_m(:,:,:), nangle, cs, g, lb)
1631  call reflect(fdt_p(:,:,:), nangle, cs, g, lb)
1632  call teleport(fdt_p(:,:,:), nangle, cs, g, lb)
1633 
1634  ! Update reflected energy (Jm-2)
1635  do j=jsh,jeh ; do i=ish,ieh
1636  !do a=1,CS%nAngle
1637  ! if((En(i,j,a) + G%IareaT(i,j)*(Fdt_m(i,j,a) + Fdt_p(i,j,a))) < 0.0)then ! for debugging
1638  ! print *,"propagate_y: OutFlux>Available" ; !stop
1639  ! endif
1640  !enddo
1641  en(i,j,:) = en(i,j,:) + g%IareaT(i,j)*(fdt_m(i,j,:) + fdt_p(i,j,:))
1642  enddo ; enddo
1643 
1644 end subroutine propagate_y
1645 
1646 !> This subroutines evaluates the zonal mass or volume fluxes in a layer.
1647 subroutine zonal_flux_en(u, h, hL, hR, uh, dt, G, j, ish, ieh, vol_CFL)
1648  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1649  real, dimension(SZIB_(G)), intent(in) :: u !< The zonal velocity, in m s-1.
1650  real, dimension(SZI_(G)), intent(in) :: h !< Energy density used to calculate the fluxes,
1651  !! in J m-2.
1652  real, dimension(SZI_(G)), intent(in) :: hL !< Left- Energy densities in the reconstruction,
1653  !! in J m-2.
1654  real, dimension(SZI_(G)), intent(in) :: hR !< Right- Energy densities in the reconstruction,
1655  !! in J m-2.
1656  real, dimension(SZIB_(G)), intent(inout) :: uh !< The zonal energy transport,
1657  !! in J s-1.
1658  real, intent(in) :: dt !< Time increment in s.
1659  integer, intent(in) :: j, ish, ieh !< The index range to work on.
1660  logical, intent(in) :: vol_CFL !< If true, rescale the ratio of face areas to
1661  !! the cell areas when estimating the CFL number.
1662 
1663  ! This subroutines evaluates the zonal mass or volume fluxes in a layer.
1664  !
1665  ! Arguments: u - Zonal velocity, in m s-1.
1666  ! (in) h - Energy density used to calculate the fluxes, in J m-2.
1667  ! (in) hL, hR - Left- and right- Energy densities in the reconstruction, in J m-2.
1668  ! (out) uh - The zonal energy transport, in J s-1.
1669  ! (in) dt - Time increment in s.
1670  ! (in) G - The ocean's grid structure.
1671  ! (in) j, ish, ieh - The index range to work on.
1672  ! (in) vol_CFL - If true, rescale the ratio of face areas to the cell
1673  ! areas when estimating the CFL number.
1674  real :: CFL ! The CFL number based on the local velocity and grid spacing, ND.
1675  real :: curv_3 ! A measure of the thickness curvature over a grid length,
1676  ! with the same units as h_in.
1677  integer :: i
1678 
1679  do i=ish-1,ieh
1680  ! Set new values of uh and duhdu.
1681  if (u(i) > 0.0) then
1682  if (vol_cfl) then ; cfl = (u(i) * dt) * (g%dy_Cu(i,j) * g%IareaT(i,j))
1683  else ; cfl = u(i) * dt * g%IdxT(i,j) ; endif
1684  curv_3 = (hl(i) + hr(i)) - 2.0*h(i)
1685  uh(i) = g%dy_Cu(i,j) * u(i) * &
1686  (hr(i) + cfl * (0.5*(hl(i) - hr(i)) + curv_3*(cfl - 1.5)))
1687  elseif (u(i) < 0.0) then
1688  if (vol_cfl) then ; cfl = (-u(i) * dt) * (g%dy_Cu(i,j) * g%IareaT(i+1,j))
1689  else ; cfl = -u(i) * dt * g%IdxT(i+1,j) ; endif
1690  curv_3 = (hl(i+1) + hr(i+1)) - 2.0*h(i+1)
1691  uh(i) = g%dy_Cu(i,j) * u(i) * &
1692  (hl(i+1) + cfl * (0.5*(hr(i+1)-hl(i+1)) + curv_3*(cfl - 1.5)))
1693  else
1694  uh(i) = 0.0
1695  endif
1696  enddo
1697 end subroutine zonal_flux_en
1698 
1699 !> This subroutines evaluates the meridional mass or volume fluxes in a layer.
1700 subroutine merid_flux_en(v, h, hL, hR, vh, dt, G, J, ish, ieh, vol_CFL)
1701  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1702  real, dimension(SZI_(G)), intent(in) :: v !< The meridional velocity, in m s-1.
1703  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h !< Energy density used to calculate the
1704  !! fluxes, in J m-2.
1705  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: hL !< Left- Energy densities in the
1706  !! reconstruction, in J m-2.
1707  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: hR !< Right- Energy densities in the
1708  !! reconstruction, in J m-2.
1709  real, dimension(SZI_(G)), intent(inout) :: vh !< The meridional energy transport,
1710  !! in J s-1.
1711  real, intent(in) :: dt !< Time increment in s.
1712  integer, intent(in) :: J, ish, ieh !< The index range to work on.
1713  logical, intent(in) :: vol_CFL !< If true, rescale the ratio of face
1714  !! areas to the cell areas when estimating
1715  !! the CFL number.
1716  ! This subroutines evaluates the meridional mass or volume fluxes in a layer.
1717  !
1718  ! Arguments: v - Meridional velocity, in m s-1.
1719  ! (in) h - Energy density used to calculate the fluxes, in J m-2.
1720  ! (in) hL, hR - Left- and right- Energy densities in the reconstruction, in J m-2.
1721  ! (out) vh - The meridional energy transport, in J s-1.
1722  ! (in) dt - Time increment in s.
1723  ! (in) G - The ocean's grid structure.
1724  ! (in) J, ish, ieh - The index range to work on.
1725  ! (in) vol_CFL - If true, rescale the ratio of face areas to the cell
1726  ! areas when estimating the CFL number.
1727  real :: CFL ! The CFL number based on the local velocity and grid spacing, ND.
1728  real :: curv_3 ! A measure of the thickness curvature over a grid length,
1729  ! with the same units as h_in.
1730  integer :: i
1731 
1732  do i=ish,ieh
1733  if (v(i) > 0.0) then
1734  if (vol_cfl) then ; cfl = (v(i) * dt) * (g%dx_Cv(i,j) * g%IareaT(i,j))
1735  else ; cfl = v(i) * dt * g%IdyT(i,j) ; endif
1736  curv_3 = hl(i,j) + hr(i,j) - 2.0*h(i,j)
1737  vh(i) = g%dx_Cv(i,j) * v(i) * ( hr(i,j) + cfl * &
1738  (0.5*(hl(i,j) - hr(i,j)) + curv_3*(cfl - 1.5)) )
1739  elseif (v(i) < 0.0) then
1740  if (vol_cfl) then ; cfl = (-v(i) * dt) * (g%dx_Cv(i,j) * g%IareaT(i,j+1))
1741  else ; cfl = -v(i) * dt * g%IdyT(i,j+1) ; endif
1742  curv_3 = hl(i,j+1) + hr(i,j+1) - 2.0*h(i,j+1)
1743  vh(i) = g%dx_Cv(i,j) * v(i) * ( hl(i,j+1) + cfl * &
1744  (0.5*(hr(i,j+1)-hl(i,j+1)) + curv_3*(cfl - 1.5)) )
1745  else
1746  vh(i) = 0.0
1747  endif
1748  enddo
1749 end subroutine merid_flux_en
1750 
1751 !> This subroutine does reflection of the internal waves at a single frequency.
1752 subroutine reflect(En, NAngle, CS, G, LB)
1753  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1754  integer, intent(in) :: NAngle
1755  real, dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
1756  intent(inout) :: En
1757  type(int_tide_cs), pointer :: CS
1758  type(loop_bounds_type), intent(in) :: LB
1759 
1760  ! This subroutine does reflection of the internal waves at a single frequency.
1761 
1762  real, dimension(G%isd:G%ied,G%jsd:G%jed) :: angle_c
1763  ! angle of boudary wrt equator
1764  real, dimension(G%isd:G%ied,G%jsd:G%jed) :: part_refl
1765  ! fraction of wave energy reflected
1766  ! values should collocate with angle_c
1767  logical, dimension(G%isd:G%ied,G%jsd:G%jed) :: ridge
1768  ! tags of cells with double reflection
1769 
1770  real :: TwoPi ! 2*pi
1771  real :: Angle_size ! size of beam wedge (rad)
1772  real :: angle_wall ! angle of coast/ridge/shelf wrt equator
1773  real, dimension(1:NAngle) :: angle_i ! angle of incident ray wrt equator
1774  real :: angle_r ! angle of reflected ray wrt equator
1775  real, dimension(1:Nangle) :: En_reflected
1776  integer :: i, j, a, a_r, na
1777  !integer :: isd, ied, jsd, jed ! start and end local indices on data domain
1778  ! ! (values include halos)
1779  integer :: isc, iec, jsc, jec ! start and end local indices on PE
1780  ! (values exclude halos)
1781  integer :: ish, ieh, jsh, jeh ! start and end local indices on data domain
1782  ! leaving out outdated halo points (march in)
1783  integer :: id_g, jd_g ! global (decomp-invar) indices
1784 
1785  !isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
1786  isc = g%isc ; iec = g%iec ; jsc = g%jsc ; jec = g%jec
1787  ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1788 
1789  twopi = 8.0*atan(1.0);
1790  angle_size = twopi / (real(nangle))
1791 
1792  do a=1,nangle
1793  ! These are the angles at the cell centers
1794  ! (should do this elsewhere since doesn't change with time)
1795  angle_i(a) = angle_size * real(a - 1) ! for a=1 aligned with x-axis
1796  enddo
1797 
1798  angle_c = cs%refl_angle
1799  part_refl = cs%refl_pref
1800  ridge = cs%refl_dbl
1801  en_reflected(:) = 0.0
1802 
1803  !do j=jsc-1,jec+1
1804  do j=jsh,jeh
1805  jd_g = j + g%jdg_offset
1806  !do i=isc-1,iec+1
1807  do i=ish,ieh
1808  id_g = i + g%idg_offset
1809  ! redistribute energy in angular space if ray will hit boundary
1810  ! i.e., if energy is in a reflecting cell
1811  if (angle_c(i,j) .ne. cs%nullangle) then
1812  do a=1,nangle
1813  if (en(i,j,a) > 0.0) then
1814  ! if ray is incident, keep specified boundary angle
1815  if (sin(angle_i(a) - angle_c(i,j)) >= 0.0) then
1816  angle_wall = angle_c(i,j)
1817  ! if ray is not incident but in ridge cell, use complementary angle
1818  elseif (ridge(i,j)) then
1819  angle_wall = angle_c(i,j) + 0.5*twopi
1820  if (angle_wall > twopi) then
1821  angle_wall = angle_wall - twopi*floor(abs(angle_wall)/twopi)
1822  elseif (angle_wall < 0.0) then
1823  angle_wall = angle_wall + twopi*ceiling(abs(angle_wall)/twopi)
1824  endif
1825  ! if ray is not incident and not in a ridge cell, keep specified angle
1826  else
1827  angle_wall = angle_c(i,j)
1828  endif
1829  ! do reflection
1830  if (sin(angle_i(a) - angle_wall) >= 0.0) then
1831  angle_r = 2.0*angle_wall - angle_i(a)
1832  if (angle_r > twopi) then
1833  angle_r = angle_r - twopi*floor(abs(angle_r)/twopi)
1834  elseif (angle_r < 0.0) then
1835  angle_r = angle_r + twopi*ceiling(abs(angle_r)/twopi)
1836  endif
1837  a_r = nint(angle_r/angle_size) + 1
1838  do while (a_r > nangle) ; a_r = a_r - nangle ; enddo
1839  if (a .ne. a_r) then
1840  en_reflected(a_r) = part_refl(i,j)*en(i,j,a)
1841  en(i,j,a) = (1.0-part_refl(i,j))*en(i,j,a)
1842  endif
1843  endif
1844  endif
1845  enddo ! a-loop
1846  en(i,j,:) = en(i,j,:) + en_reflected(:)
1847  en_reflected(:) = 0.0
1848  endif
1849  enddo ! i-loop
1850  enddo ! j-loop
1851 
1852  ! Check to make sure no energy gets onto land (only run for debugging)
1853  !do j=jsc,jec
1854  ! jd_g = j + G%jdg_offset
1855  ! do i=isc,iec
1856  ! id_g = i + G%idg_offset
1857  ! do a=1,NAngle
1858  ! if (En(i,j,a) > 0.001 .and. G%mask2dT(i,j) == 0) then
1859  ! print *, 'En=', En(i,j,a), 'a=', a, 'ig_g=',id_g, 'jg_g=',jd_g
1860  ! !stop 'Energy detected out of bounds!'
1861  ! endif
1862  ! enddo ! a-loop
1863  ! enddo ! i-loop
1864  !enddo ! j-loop
1865 
1866 end subroutine reflect
1867 
1868 !> This subroutine moves energy across lines of partial reflection to prevent
1869 !! reflection of energy that is supposed to get across.
1870 subroutine teleport(En, NAngle, CS, G, LB)
1871  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
1872  integer, intent(in) :: NAngle
1873  real, dimension(G%isd:G%ied,G%jsd:G%jed,NAngle), &
1874  intent(inout) :: En
1875  type(int_tide_cs), pointer :: CS
1876  type(loop_bounds_type), intent(in) :: LB
1877 
1878  ! This subroutine moves energy across lines of partial reflection to prevent
1879  ! reflection of energy that is supposed to get across.
1880 
1881  real, dimension(G%isd:G%ied,G%jsd:G%jed) :: angle_c
1882  ! angle of boudary wrt equator
1883  real, dimension(G%isd:G%ied,G%jsd:G%jed) :: part_refl
1884  ! fraction of wave energy reflected
1885  ! values should collocate with angle_c
1886  logical, dimension(G%isd:G%ied,G%jsd:G%jed) :: pref_cell
1887  ! flag for partial reflection
1888  logical, dimension(G%isd:G%ied,G%jsd:G%jed) :: ridge
1889  ! tags of cells with double reflection
1890  real :: TwoPi ! size of beam wedge (rad)
1891  real :: Angle_size ! size of beam wedge (rad)
1892  real, dimension(1:NAngle) :: angle_i ! angle of incident ray wrt equator
1893  real, dimension(1:NAngle) :: cos_angle, sin_angle
1894  real :: En_tele ! energy to be "teleported"
1895  integer :: i, j, a
1896  !integer :: isd, ied, jsd, jed ! start and end local indices on data domain
1897  ! ! (values include halos)
1898  !integer :: isc, iec, jsc, jec ! start and end local indices on PE
1899  ! ! (values exclude halos)
1900  integer :: ish, ieh, jsh, jeh ! start and end local indices on data domain
1901  ! leaving out outdated halo points (march in)
1902  integer :: id_g, jd_g ! global (decomp-invar) indices
1903  integer :: jos, ios ! offsets
1904  real :: cos_normal, sin_normal, angle_wall
1905  ! cos/sin of cross-ridge normal, ridge angle
1906 
1907  !isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
1908  !isc = G%isc ; iec = G%iec ; jsc = G%jsc ; jec = G%jec
1909  ish = lb%ish ; ieh = lb%ieh ; jsh = lb%jsh ; jeh = lb%jeh
1910 
1911  twopi = 8.0*atan(1.0)
1912  angle_size = twopi / (real(nangle))
1913 
1914  do a=1,nangle
1915  ! These are the angles at the cell centers
1916  ! (should do this elsewhere since doesn't change with time)
1917  angle_i(a) = angle_size * real(a - 1) ! for a=1 aligned with x-axis
1918  cos_angle(a) = cos(angle_i(a)) ; sin_angle(a) = sin(angle_i(a))
1919  enddo
1920 
1921  angle_c = cs%refl_angle
1922  part_refl = cs%refl_pref
1923  pref_cell = cs%refl_pref_logical
1924  ridge = cs%refl_dbl
1925 
1926  do j=jsh,jeh
1927  do i=ish,ieh
1928  id_g = i + g%idg_offset ; jd_g = j + g%jdg_offset
1929  if (pref_cell(i,j)) then
1930  do a=1,nangle
1931  if (en(i,j,a) > 0) then
1932  ! if ray is incident, keep specified boundary angle
1933  if (sin(angle_i(a) - angle_c(i,j)) >= 0.0) then
1934  angle_wall = angle_c(i,j)
1935  ! if ray is not incident but in ridge cell, use complementary angle
1936  elseif (ridge(i,j)) then
1937  angle_wall = angle_c(i,j) + 0.5*twopi
1938  ! if ray is not incident and not in a ridge cell, keep specified angle
1939  else
1940  angle_wall = angle_c(i,j)
1941  endif
1942  ! teleport if incident
1943  if (sin(angle_i(a) - angle_wall) >= 0.0) then
1944  en_tele = en(i,j,a)
1945  cos_normal = cos(angle_wall + 0.25*twopi)
1946  sin_normal = sin(angle_wall + 0.25*twopi)
1947  ! find preferred zonal offset based on shelf/ridge angle
1948  ios = int(sign(1.,cos_normal))
1949  ! find preferred meridional offset based on shelf/ridge angle
1950  jos = int(sign(1.,sin_normal))
1951  ! find receptive ocean cell in direction of offset
1952  if (.not. pref_cell(i+ios,j+jos)) then
1953  en(i,j,a) = en(i,j,a) - en_tele
1954  en(i+ios,j+jos,a) = en(i+ios,j+jos,a) + en_tele
1955  else
1956  call mom_error(warning, "teleport: no receptive ocean cell", .true.)
1957  print *, 'idg=',id_g,'jd_g=',jd_g,'a=',a
1958  stop
1959  endif
1960  endif ! incidence check
1961  endif ! energy check
1962  enddo ! a-loop
1963  endif ! pref check
1964  enddo ! i-loop
1965  enddo ! j-loop
1966 
1967 end subroutine teleport
1968 
1969 !> This subroutine rotates points in the halos where required to accomodate
1970 !! changes in grid orientation, such as at the tripolar fold.
1971 subroutine correct_halo_rotation(En, test, G, NAngle)
1972  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1973  real, dimension(:,:,:,:,:), intent(inout) :: En
1974  real, dimension(SZI_(G),SZJ_(G),2), intent(in) :: test
1975  integer, intent(in) :: NAngle
1976  ! This subroutine rotates points in the halos where required to accomodate
1977  ! changes in grid orientation, such as at the tripolar fold.
1978 
1979  real, dimension(G%isd:G%ied,NAngle) :: En2d
1980  integer, dimension(G%isd:G%ied) :: a_shift
1981  integer :: i_first, i_last, a_new
1982  integer :: a, i, j, isd, ied, jsd, jed, m, fr
1983  character(len=80) :: mesg
1984  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
1985 
1986  do j=jsd,jed
1987  i_first = ied+1 ; i_last = isd-1
1988  do i=isd,ied
1989  a_shift(i) = 0
1990  if (test(i,j,1) /= 1.0) then
1991  if (i<i_first) i_first = i
1992  if (i>i_last) i_last = i
1993 
1994  if (test(i,j,1) == -1.0) then ; a_shift(i) = nangle/2
1995  elseif (test(i,j,2) == 1.0) then ; a_shift(i) = -nangle/4
1996  elseif (test(i,j,2) == -1.0) then ; a_shift(i) = nangle/4
1997  else
1998  write(mesg,'("Unrecognized rotation test vector ",2ES9.2," at ",F7.2," E, ",&
1999  &F7.2," N; i,j=",2i4)') &
2000  test(i,j,1), test(i,j,2), g%GeoLonT(i,j), g%GeoLatT(i,j), i, j
2001  call mom_error(fatal, mesg)
2002  endif
2003  endif
2004  enddo
2005 
2006  if (i_first <= i_last) then
2007  ! At least one point in this row needs to be rotated.
2008  do m=1,size(en,5) ; do fr=1,size(en,4)
2009  do a=1,nangle ; do i=i_first,i_last ; if (a_shift(i) /= 0) then
2010  a_new = a + a_shift(i)
2011  if (a_new < 1) a_new = a_new + nangle
2012  if (a_new > nangle) a_new = a_new - nangle
2013  en2d(i,a_new) = en(i,j,a,fr,m)
2014  endif ; enddo ; enddo
2015  do a=1,nangle ; do i=i_first,i_last ; if (a_shift(i) /= 0) then
2016  en(i,j,a,fr,m) = en2d(i,a)
2017  endif ; enddo ; enddo
2018  enddo ; enddo
2019  endif
2020  enddo
2021 end subroutine correct_halo_rotation
2022 
2023 !> This subroutine calculates left/right edge values for PPM reconstruction.
2024 subroutine ppm_reconstruction_x(h_in, h_l, h_r, G, LB, simple_2nd)
2025  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
2026  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Energy density in a sector (2D).
2027  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_l !< Left edge value of reconstruction (2D).
2028  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_r !< Right edge value of reconstruction (2D).
2029  type(loop_bounds_type), intent(in) :: LB !< A structure with the active loop bounds.
2030  logical, optional, intent(in) :: simple_2nd !< If true, use the arithmetic mean
2031  !! energy densities as default edge values
2032  !! for a simple 2nd order scheme.
2033 
2034  ! This subroutine calculates left/right edge values for PPM reconstruction.
2035  ! Arguments: h_in - Energy density in a sector (2D)
2036  ! (out) h_l,h_r - left/right edge value of reconstruction (2D)
2037  ! (in) G - The ocean's grid structure.
2038  ! (in) LB - A structure with the active loop bounds.
2039  ! (in, opt) simple_2nd - If true, use the arithmetic mean energy densities as
2040  ! default edge values for a simple 2nd order scheme.
2041 
2042  ! Local variables with useful mnemonic names.
2043  real, dimension(SZI_(G),SZJ_(G)) :: slp ! The slopes.
2044  real, parameter :: oneSixth = 1./6.
2045  real :: h_ip1, h_im1
2046  real :: dMx, dMn
2047  logical :: use_CW84, use_2nd
2048  character(len=256) :: mesg
2049  integer :: i, j, isl, iel, jsl, jel, stencil
2050 
2051  use_2nd = .false. ; if (present(simple_2nd)) use_2nd = simple_2nd
2052  isl = lb%ish-1 ; iel = lb%ieh+1 ; jsl = lb%jsh ; jel = lb%jeh
2053 
2054  ! This is the stencil of the reconstruction, not the scheme overall.
2055  stencil = 2 ; if (use_2nd) stencil = 1
2056 
2057  if ((isl-stencil < g%isd) .or. (iel+stencil > g%ied)) then
2058  write(mesg,'("In MOM_internal_tides, PPM_reconstruction_x called with a ", &
2059  & "x-halo that needs to be increased by ",i2,".")') &
2060  stencil + max(g%isd-isl,iel-g%ied)
2061  call mom_error(fatal,mesg)
2062  endif
2063  if ((jsl < g%jsd) .or. (jel > g%jed)) then
2064  write(mesg,'("In MOM_internal_tides, PPM_reconstruction_x called with a ", &
2065  & "y-halo that needs to be increased by ",i2,".")') &
2066  max(g%jsd-jsl,jel-g%jed)
2067  call mom_error(fatal,mesg)
2068  endif
2069 
2070  if (use_2nd) then
2071  do j=jsl,jel ; do i=isl,iel
2072  h_im1 = g%mask2dT(i-1,j) * h_in(i-1,j) + (1.0-g%mask2dT(i-1,j)) * h_in(i,j)
2073  h_ip1 = g%mask2dT(i+1,j) * h_in(i+1,j) + (1.0-g%mask2dT(i+1,j)) * h_in(i,j)
2074  h_l(i,j) = 0.5*( h_im1 + h_in(i,j) )
2075  h_r(i,j) = 0.5*( h_ip1 + h_in(i,j) )
2076  enddo ; enddo
2077  else
2078  do j=jsl,jel ; do i=isl-1,iel+1
2079  if ((g%mask2dT(i-1,j) * g%mask2dT(i,j) * g%mask2dT(i+1,j)) == 0.0) then
2080  slp(i,j) = 0.0
2081  else
2082  ! This uses a simple 2nd order slope.
2083  slp(i,j) = 0.5 * (h_in(i+1,j) - h_in(i-1,j))
2084  ! Monotonic constraint, see Eq. B2 in Lin 1994, MWR (132)
2085  dmx = max(h_in(i+1,j), h_in(i-1,j), h_in(i,j)) - h_in(i,j)
2086  dmn = h_in(i,j) - min(h_in(i+1,j), h_in(i-1,j), h_in(i,j))
2087  slp(i,j) = sign(1.,slp(i,j)) * min(abs(slp(i,j)), 2. * min(dmx, dmn))
2088  ! * (G%mask2dT(i-1,j) * G%mask2dT(i,j) * G%mask2dT(i+1,j))
2089  endif
2090  enddo; enddo
2091 
2092  do j=jsl,jel ; do i=isl,iel
2093  ! Neighboring values should take into account any boundaries. The 3
2094  ! following sets of expressions are equivalent.
2095  ! h_im1 = h_in(i-1,j,k) ; if (G%mask2dT(i-1,j) < 0.5) h_im1 = h_in(i,j)
2096  ! h_ip1 = h_in(i+1,j,k) ; if (G%mask2dT(i+1,j) < 0.5) h_ip1 = h_in(i,j)
2097  h_im1 = g%mask2dT(i-1,j) * h_in(i-1,j) + (1.0-g%mask2dT(i-1,j)) * h_in(i,j)
2098  h_ip1 = g%mask2dT(i+1,j) * h_in(i+1,j) + (1.0-g%mask2dT(i+1,j)) * h_in(i,j)
2099  ! Left/right values following Eq. B2 in Lin 1994, MWR (132)
2100  h_l(i,j) = 0.5*( h_im1 + h_in(i,j) ) + onesixth*( slp(i-1,j) - slp(i,j) )
2101  h_r(i,j) = 0.5*( h_ip1 + h_in(i,j) ) + onesixth*( slp(i,j) - slp(i+1,j) )
2102  enddo; enddo
2103  endif
2104 
2105  call ppm_limit_pos(h_in, h_l, h_r, 0.0, g, isl, iel, jsl, jel)
2106 end subroutine ppm_reconstruction_x
2107 
2108 !> This subroutine calculates left/right edge valus for PPM reconstruction.
2109 subroutine ppm_reconstruction_y(h_in, h_l, h_r, G, LB, simple_2nd)
2110  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
2111  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Energy density in a sector (2D).
2112  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_l !< Left edge value of reconstruction (2D).
2113  real, dimension(SZI_(G),SZJ_(G)), intent(out) :: h_r !< Right edge value of reconstruction (2D).
2114  type(loop_bounds_type), intent(in) :: LB !< A structure with the active loop bounds.
2115  logical, optional, intent(in) :: simple_2nd !< If true, use the arithmetic mean
2116  !! energy densities as default edge values
2117  !! for a simple 2nd order scheme.
2118 
2119  ! This subroutine calculates left/right edge valus for PPM reconstruction.
2120  ! Arguments: h_in - Energy density in a sector (2D)
2121  ! (out) h_l,h_r - left/right edge value of reconstruction (2D)
2122  ! (in) G - The ocean's grid structure.
2123  ! (in) LB - A structure with the active loop bounds.
2124  ! (in, opt) simple_2nd - If true, use the arithmetic mean energy densities as
2125  ! default edge values for a simple 2nd order scheme.
2126 
2127  ! Local variables with useful mnemonic names.
2128  real, dimension(SZI_(G),SZJ_(G)) :: slp ! The slopes.
2129  real, parameter :: oneSixth = 1./6.
2130  real :: h_jp1, h_jm1
2131  real :: dMx, dMn
2132  logical :: use_2nd
2133  character(len=256) :: mesg
2134  integer :: i, j, isl, iel, jsl, jel, stencil
2135 
2136  use_2nd = .false. ; if (present(simple_2nd)) use_2nd = simple_2nd
2137  isl = lb%ish ; iel = lb%ieh ; jsl = lb%jsh-1 ; jel = lb%jeh+1
2138 
2139  ! This is the stencil of the reconstruction, not the scheme overall.
2140  stencil = 2 ; if (use_2nd) stencil = 1
2141 
2142  if ((isl < g%isd) .or. (iel > g%ied)) then
2143  write(mesg,'("In MOM_internal_tides, PPM_reconstruction_y called with a ", &
2144  & "x-halo that needs to be increased by ",i2,".")') &
2145  max(g%isd-isl,iel-g%ied)
2146  call mom_error(fatal,mesg)
2147  endif
2148  if ((jsl-stencil < g%jsd) .or. (jel+stencil > g%jed)) then
2149  write(mesg,'("In MOM_internal_tides, PPM_reconstruction_y called with a ", &
2150  & "y-halo that needs to be increased by ",i2,".")') &
2151  stencil + max(g%jsd-jsl,jel-g%jed)
2152  call mom_error(fatal,mesg)
2153  endif
2154 
2155  if (use_2nd) then
2156  do j=jsl,jel ; do i=isl,iel
2157  h_jm1 = g%mask2dT(i,j-1) * h_in(i,j-1) + (1.0-g%mask2dT(i,j-1)) * h_in(i,j)
2158  h_jp1 = g%mask2dT(i,j+1) * h_in(i,j+1) + (1.0-g%mask2dT(i,j+1)) * h_in(i,j)
2159  h_l(i,j) = 0.5*( h_jm1 + h_in(i,j) )
2160  h_r(i,j) = 0.5*( h_jp1 + h_in(i,j) )
2161  enddo ; enddo
2162  else
2163  do j=jsl-1,jel+1 ; do i=isl,iel
2164  if ((g%mask2dT(i,j-1) * g%mask2dT(i,j) * g%mask2dT(i,j+1)) == 0.0) then
2165  slp(i,j) = 0.0
2166  else
2167  ! This uses a simple 2nd order slope.
2168  slp(i,j) = 0.5 * (h_in(i,j+1) - h_in(i,j-1))
2169  ! Monotonic constraint, see Eq. B2 in Lin 1994, MWR (132)
2170  dmx = max(h_in(i,j+1), h_in(i,j-1), h_in(i,j)) - h_in(i,j)
2171  dmn = h_in(i,j) - min(h_in(i,j+1), h_in(i,j-1), h_in(i,j))
2172  slp(i,j) = sign(1.,slp(i,j)) * min(abs(slp(i,j)), 2. * min(dmx, dmn))
2173  ! * (G%mask2dT(i,j-1) * G%mask2dT(i,j) * G%mask2dT(i,j+1))
2174  endif
2175  enddo ; enddo
2176 
2177  do j=jsl,jel ; do i=isl,iel
2178  ! Neighboring values should take into account any boundaries. The 3
2179  ! following sets of expressions are equivalent.
2180  h_jm1 = g%mask2dT(i,j-1) * h_in(i,j-1) + (1.0-g%mask2dT(i,j-1)) * h_in(i,j)
2181  h_jp1 = g%mask2dT(i,j+1) * h_in(i,j+1) + (1.0-g%mask2dT(i,j+1)) * h_in(i,j)
2182  ! Left/right values following Eq. B2 in Lin 1994, MWR (132)
2183  h_l(i,j) = 0.5*( h_jm1 + h_in(i,j) ) + onesixth*( slp(i,j-1) - slp(i,j) )
2184  h_r(i,j) = 0.5*( h_jp1 + h_in(i,j) ) + onesixth*( slp(i,j) - slp(i,j+1) )
2185  enddo ; enddo
2186  endif
2187 
2188  call ppm_limit_pos(h_in, h_l, h_r, 0.0, g, isl, iel, jsl, jel)
2189 end subroutine ppm_reconstruction_y
2190 
2191 !> This subroutine limits the left/right edge values of the PPM reconstruction
2192 !! to give a reconstruction that is positive-definite. Here this is
2193 !! reinterpreted as giving a constant thickness if the mean thickness is less
2194 !! than h_min, with a minimum of h_min otherwise.
2195 subroutine ppm_limit_pos(h_in, h_L, h_R, h_min, G, iis, iie, jis, jie)
2196  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure.
2197  real, dimension(SZI_(G),SZJ_(G)), intent(in) :: h_in !< Thickness of layer (2D).
2198  real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: h_L !< Left edge value (2D).
2199  real, dimension(SZI_(G),SZJ_(G)), intent(inout) :: h_R !< Right edge value (2D).
2200  real, intent(in) :: h_min !< The minimum thickness that can be
2201  !! obtained by a concave parabolic fit.
2202  integer, intent(in) :: iis, iie, jis, jie !< Index range for
2203  !! computation.
2204 
2205  ! This subroutine limits the left/right edge values of the PPM reconstruction
2206  ! to give a reconstruction that is positive-definite. Here this is
2207  ! reinterpreted as giving a constant thickness if the mean thickness is less
2208  ! than h_min, with a minimum of h_min otherwise.
2209  ! Arguments: h_in - thickness of layer (2D)
2210  ! (inout) h_L - left edge value (2D)
2211  ! (inout) h_R - right edge value (2D)
2212  ! (in) h_min - The minimum thickness that can be obtained by a
2213  ! concave parabolic fit.
2214  ! (in) iis, iie, jis, jie - Index range for computation.
2215  ! (in) G - The ocean's grid structure.
2216 
2217  ! Local variables
2218  real :: curv, dh, scale
2219  character(len=256) :: mesg
2220  integer :: i,j
2221 
2222  do j=jis,jie ; do i=iis,iie
2223  ! This limiter prevents undershooting minima within the domain with
2224  ! values less than h_min.
2225  curv = 3.0*(h_l(i,j) + h_r(i,j) - 2.0*h_in(i,j))
2226  if (curv > 0.0) then ! Only minima are limited.
2227  dh = h_r(i,j) - h_l(i,j)
2228  if (abs(dh) < curv) then ! The parabola's minimum is within the cell.
2229  if (h_in(i,j) <= h_min) then
2230  h_l(i,j) = h_in(i,j) ; h_r(i,j) = h_in(i,j)
2231  elseif (12.0*curv*(h_in(i,j) - h_min) < (curv**2 + 3.0*dh**2)) then
2232  ! The minimum value is h_in - (curv^2 + 3*dh^2)/(12*curv), and must
2233  ! be limited in this case. 0 < scale < 1.
2234  scale = 12.0*curv*(h_in(i,j) - h_min) / (curv**2 + 3.0*dh**2)
2235  h_l(i,j) = h_in(i,j) + scale*(h_l(i,j) - h_in(i,j))
2236  h_r(i,j) = h_in(i,j) + scale*(h_r(i,j) - h_in(i,j))
2237  endif
2238  endif
2239  endif
2240  enddo ; enddo
2241 end subroutine ppm_limit_pos
2242 
2243 ! subroutine register_int_tide_restarts(G, param_file, CS, restart_CS)
2244 ! type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure
2245 ! type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time parameters
2246 ! type(int_tide_CS), pointer :: CS
2247 ! type(MOM_restart_CS), pointer :: restart_CS
2248 
2249 ! ! This subroutine is not currently in use!!
2250 
2251 ! ! Arguments: G - The ocean's grid structure.
2252 ! ! (in) param_file - A structure indicating the open file to parse for
2253 ! ! model parameter values.
2254 ! ! (in/out) CS - A pointer that is set to point to the control structure
2255 ! ! for this module.
2256 ! ! (in) restart_CS - A pointer to the restart control structure.
2257 ! ! This subroutine is used to allocate and register any fields in this module
2258 ! ! that should be written to or read from the restart file.
2259 ! logical :: use_int_tides
2260 ! type(vardesc) :: vd
2261 ! integer :: num_freq, num_angle , num_mode, period_1
2262 ! integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB, a
2263 ! isd = G%isd ; ied = G%ied ; jsd = G%jsd ; jed = G%jed
2264 ! IsdB = G%IsdB ; IedB = G%IedB ; JsdB = G%JsdB ; JedB = G%JedB
2265 
2266 ! if (associated(CS)) then
2267 ! call MOM_error(WARNING, "register_int_tide_restarts called "//&
2268 ! "with an associated control structure.")
2269 ! return
2270 ! endif
2271 
2272 ! use_int_tides = .false.
2273 ! call read_param(param_file, "INTERNAL_TIDES", use_int_tides)
2274 ! if (.not.use_int_tides) return
2275 
2276 ! allocate(CS)
2277 
2278 ! num_angle = 24
2279 ! call read_param(param_file, "INTERNAL_TIDE_ANGLES", num_angle)
2280 ! allocate(CS%En_restart(isd:ied, jsd:jed, num_angle))
2281 ! CS%En_restart(:,:,:) = 0.0
2282 
2283 ! vd = vardesc("En_restart", &
2284 ! "The internal wave energy density as a function of (i,j,angle,frequency,mode)", &
2285 ! 'h','1','1',"J m-2")
2286 ! call register_restart_field(CS%En_restart, vd, .false., restart_CS)
2287 
2288 ! !--------------------check----------------------------------------------
2289 ! if (is_root_pe()) then
2290 ! print *,'register_int_tide_restarts: CS and CS%En_restart allocated!'
2291 ! print *,'register_int_tide_restarts: CS%En_restart registered!'
2292 ! print *,'register_int_tide_restarts: done!'
2293 ! endif
2294 ! !-----------------------------------------------------------------------
2295 
2296 ! end subroutine register_int_tide_restarts
2297 
2298 ! #@# This subroutine needs a doxygen comment.
2299 subroutine internal_tides_init(Time, G, GV, param_file, diag, CS)
2300  type(time_type), target, intent(in) :: Time !< The current model time.
2301  type(ocean_grid_type), intent(inout) :: G !< The ocean's grid structure.
2302  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure.
2303  type(param_file_type), intent(in) :: param_file !< A structure to parse for run-time
2304  !! parameters.
2305  type(diag_ctrl), target, intent(in) :: diag !< A structure that is used to regulate
2306  !! diagnostic output.
2307  type(int_tide_cs),pointer :: CS !< A pointer that is set to point to the control
2308  !! structure for this module.
2309 
2310  ! Arguments: Time - The current model time.
2311  ! (in) G - The ocean's grid structure.
2312  ! (in) GV - The ocean's vertical grid structure.
2313  ! (in) param_file - A structure indicating the open file to parse for
2314  ! model parameter values.
2315  ! (in) diag - A structure that is used to regulate diagnostic output.
2316  ! (in/out) CS - A pointer that is set to point to the control structure
2317  ! for this module
2318  real :: Angle_size ! size of wedges, rad
2319  real, allocatable :: angles(:) ! orientations of wedge centers, rad
2320  real, allocatable, dimension(:,:) :: h2 ! topographic roughness scale, m^2
2321  real :: kappa_itides, kappa_h2_factor
2322  ! characteristic topographic wave number
2323  ! and a scaling factor
2324  real, allocatable :: ridge_temp(:,:)
2325  ! array for temporary storage of flags
2326  ! of cells with double-reflecting ridges
2327  logical :: use_int_tides, use_temperature
2328  integer :: num_angle, num_freq, num_mode, m, fr, period_1
2329  integer :: isd, ied, jsd, jed, a, id_ang, i, j
2330  type(axes_grp) :: axes_ang
2331  ! This include declares and sets the variable "version".
2332 #include "version_variable.h"
2333  character(len=40) :: mdl = "MOM_internal_tides" ! This module's name.
2334  character(len=16), dimension(8) :: freq_name
2335  character(len=40) :: var_name
2336  character(len=160) :: var_descript
2337  character(len=200) :: filename
2338  character(len=200) :: refl_angle_file, land_mask_file
2339  character(len=200) :: refl_pref_file, refl_dbl_file
2340  character(len=200) :: dy_Cu_file, dx_Cv_file
2341  character(len=200) :: h2_file
2342 
2343  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
2344 
2345  if (associated(cs)) then
2346  call mom_error(warning, "internal_tides_init called "//&
2347  "with an associated control structure.")
2348  return
2349  else
2350  allocate(cs)
2351  endif
2352 
2353  use_int_tides = .false.
2354  call read_param(param_file, "INTERNAL_TIDES", use_int_tides)
2355  cs%do_int_tides = use_int_tides
2356  if (.not.use_int_tides) return
2357 
2358  use_temperature = .true.
2359  call read_param(param_file, "ENABLE_THERMODYNAMICS", use_temperature)
2360  if (.not.use_temperature) call mom_error(fatal, &
2361  "register_int_tide_restarts: internal_tides only works with "//&
2362  "ENABLE_THERMODYNAMICS defined.")
2363 
2364  ! Set number of frequencies, angles, and modes to consider
2365  num_freq = 1 ; num_angle = 24 ; num_mode = 1
2366  call read_param(param_file, "INTERNAL_TIDE_FREQS", num_freq)
2367  call read_param(param_file, "INTERNAL_TIDE_ANGLES", num_angle)
2368  call read_param(param_file, "INTERNAL_TIDE_MODES", num_mode)
2369  if (.not.((num_freq > 0) .and. (num_angle > 0) .and. (num_mode > 0))) return
2370  cs%nFreq = num_freq ; cs%nAngle = num_angle ; cs%nMode = num_mode
2371 
2372  ! Allocate energy density array
2373  allocate(cs%En(isd:ied, jsd:jed, num_angle, num_freq, num_mode))
2374  cs%En(:,:,:,:,:) = 0.0
2375 
2376  ! Allocate phase speed array
2377  allocate(cs%cp(isd:ied, jsd:jed, num_freq, num_mode))
2378  cs%cp(:,:,:,:) = 0.0
2379 
2380  ! Allocate and populate frequency array (each a multiple of first for now)
2381  allocate(cs%frequency(num_freq))
2382  call read_param(param_file, "FIRST_MODE_PERIOD", period_1); ! ADDED BDM
2383  do fr=1,num_freq
2384  cs%frequency(fr) = (8.0*atan(1.0) * (real(fr)) / period_1) ! ADDED BDM
2385  enddo
2386 
2387  ! Read all relevant parameters and write them to the model log.
2388 
2389  cs%Time => time ! direct a pointer to the current model time target
2390 
2391  call get_param(param_file, mdl, "INPUTDIR", cs%inputdir, default=".")
2392  cs%inputdir = slasher(cs%inputdir)
2393 
2394  call log_version(param_file, mdl, version, "")
2395 
2396  call get_param(param_file, mdl, "INTERNAL_TIDE_FREQS", num_freq, &
2397  "The number of distinct internal tide frequency bands \n"//&
2398  "that will be calculated.", default=1)
2399  call get_param(param_file, mdl, "INTERNAL_TIDE_MODES", num_mode, &
2400  "The number of distinct internal tide modes \n"//&
2401  "that will be calculated.", default=1)
2402  call get_param(param_file, mdl, "INTERNAL_TIDE_ANGLES", num_angle, &
2403  "The number of angular resolution bands for the internal \n"//&
2404  "tide calculations.", default=24)
2405 
2406  if (use_int_tides) then
2407  if ((num_freq <= 0) .and. (num_mode <= 0) .and. (num_angle <= 0)) then
2408  call mom_error(warning, "Internal tides were enabled, but the number "//&
2409  "of requested frequencies, modes and angles were not all positive.")
2410  return
2411  endif
2412  else
2413  if ((num_freq > 0) .and. (num_mode > 0) .and. (num_angle > 0)) then
2414  call mom_error(warning, "Internal tides were not enabled, even though "//&
2415  "the number of requested frequencies, modes and angles were all "//&
2416  "positive.")
2417  return
2418  endif
2419  endif
2420 
2421  if (cs%NFreq /= num_freq) call mom_error(fatal, "Internal_tides_init: "//&
2422  "Inconsistent number of frequencies.")
2423  if (cs%NAngle /= num_angle) call mom_error(fatal, "Internal_tides_init: "//&
2424  "Inconsistent number of angles.")
2425  if (cs%NMode /= num_mode) call mom_error(fatal, "Internal_tides_init: "//&
2426  "Inconsistent number of modes.")
2427  if (4*(num_angle/4) /= num_angle) call mom_error(fatal, &
2428  "Internal_tides_init: INTERNAL_TIDE_ANGLES must be a multiple of 4.")
2429 
2430  cs%diag => diag
2431 
2432  call get_param(param_file, mdl, "INTERNAL_TIDE_DECAY_RATE", cs%decay_rate, &
2433  "The rate at which internal tide energy is lost to the \n"//&
2434  "interior ocean internal wave field.", units="s-1", default=0.0)
2435  call get_param(param_file, mdl, "INTERNAL_TIDE_VOLUME_BASED_CFL", cs%vol_CFL, &
2436  "If true, use the ratio of the open face lengths to the \n"//&
2437  "tracer cell areas when estimating CFL numbers in the \n"//&
2438  "internal tide code.", default=.false.)
2439  call get_param(param_file, mdl, "INTERNAL_TIDE_CORNER_ADVECT", cs%corner_adv, &
2440  "If true, internal tide ray-tracing advection uses a \n"//&
2441  " corner-advection scheme rather than PPM.\n", default=.false.)
2442  call get_param(param_file, mdl, "INTERNAL_TIDE_SIMPLE_2ND_PPM", cs%simple_2nd, &
2443  "If true, CONTINUITY_PPM uses a simple 2nd order \n"//&
2444  "(arithmetic mean) interpolation of the edge values. \n"//&
2445  "This may give better PV conservation propterties. While \n"//&
2446  "it formally reduces the accuracy of the continuity \n"//&
2447  "solver itself in the strongly advective limit, it does \n"//&
2448  "not reduce the overall order of accuracy of the dynamic \n"//&
2449  "core.", default=.false.)
2450  call get_param(param_file, mdl, "INTERNAL_TIDE_UPWIND_1ST", cs%upwind_1st, &
2451  "If true, the internal tide ray-tracing advection uses \n"//&
2452  "1st-order upwind advection. This scheme is highly \n"//&
2453  "continuity solver. This scheme is highly \n"//&
2454  "diffusive but may be useful for debugging.", default=.false.)
2455  call get_param(param_file, mdl, "INTERNAL_TIDE_BACKGROUND_DRAG", &
2456  cs%apply_background_drag, "If true, the internal tide \n"//&
2457  "ray-tracing advection uses a background drag term as a sink.",&
2458  default=.false.)
2459  call get_param(param_file, mdl, "INTERNAL_TIDE_QUAD_DRAG", cs%apply_bottom_drag, &
2460  "If true, the internal tide ray-tracing advection uses \n"//&
2461  "a quadratic bottom drag term as a sink.", default=.false.)
2462  call get_param(param_file, mdl, "INTERNAL_TIDE_WAVE_DRAG", cs%apply_wave_drag, &
2463  "If true, apply scattering due to small-scale roughness as a sink.", &
2464  default=.false.)
2465  call get_param(param_file, mdl, "INTERNAL_TIDE_FROUDE_DRAG", cs%apply_Froude_drag, &
2466  "If true, apply wave breaking as a sink.", &
2467  default=.false.)
2468  call get_param(param_file, mdl, "CDRAG", cs%cdrag, &
2469  "CDRAG is the drag coefficient relating the magnitude of \n"//&
2470  "the velocity field to the bottom stress.", units="nondim", &
2471  default=0.003)
2472  call get_param(param_file, mdl, "INTERNAL_TIDE_ENERGIZED_ANGLE", cs%energized_angle, &
2473  "If positive, only one angular band of the internal tides \n"//&
2474  "gets all of the energy. (This is for debugging.)", default=-1)
2475  call get_param(param_file, mdl, "USE_PPM_ANGULAR", cs%use_PPMang, &
2476  "If true, use PPM for advection of energy in angular \n"//&
2477  "space.", default=.false.)
2478  call get_param(param_file, mdl, "GAMMA_ITIDES", cs%q_itides, &
2479  "The fraction of the internal tidal energy that is \n"//&
2480  "dissipated locally with INT_TIDE_DISSIPATION. \n"//&
2481  "THIS NAME COULD BE BETTER.", &
2482  units="nondim", default=0.3333)
2483  call get_param(param_file, mdl, "KAPPA_ITIDES", kappa_itides, &
2484  "A topographic wavenumber used with INT_TIDE_DISSIPATION. \n"//&
2485  "The default is 2pi/10 km, as in St.Laurent et al. 2002.", &
2486  units="m-1", default=8.e-4*atan(1.0))
2487  call get_param(param_file, mdl, "KAPPA_H2_FACTOR", kappa_h2_factor, &
2488  "A scaling factor for the roughness amplitude with n"//&
2489  "INT_TIDE_DISSIPATION.", units="nondim", default=1.0)
2490 
2491  ! Allocate various arrays needed for loss rates
2492  allocate(h2(isd:ied,jsd:jed)) ; h2(:,:) = 0.0
2493  allocate(cs%TKE_itidal_loss_fixed(isd:ied,jsd:jed))
2494  cs%TKE_itidal_loss_fixed = 0.0
2495  allocate(cs%TKE_leak_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2496  cs%TKE_leak_loss(:,:,:,:,:) = 0.0
2497  allocate(cs%TKE_quad_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2498  cs%TKE_quad_loss(:,:,:,:,:) = 0.0
2499  allocate(cs%TKE_itidal_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2500  cs%TKE_itidal_loss(:,:,:,:,:) = 0.0
2501  allocate(cs%TKE_Froude_loss(isd:ied,jsd:jed,num_angle,num_freq,num_mode))
2502  cs%TKE_Froude_loss(:,:,:,:,:) = 0.0
2503  allocate(cs%tot_leak_loss(isd:ied,jsd:jed)) ; cs%tot_leak_loss(:,:) = 0.0
2504  allocate(cs%tot_quad_loss(isd:ied,jsd:jed) ) ; cs%tot_quad_loss(:,:) = 0.0
2505  allocate(cs%tot_itidal_loss(isd:ied,jsd:jed)) ; cs%tot_itidal_loss(:,:) = 0.0
2506  allocate(cs%tot_Froude_loss(isd:ied,jsd:jed)) ; cs%tot_Froude_loss(:,:) = 0.0
2507 
2508  ! Compute the fixed part of the bottom drag loss from baroclinic modes
2509  call get_param(param_file, mdl, "H2_FILE", h2_file, &
2510  "The path to the file containing the sub-grid-scale \n"//&
2511  "topographic roughness amplitude with INT_TIDE_DISSIPATION.", &
2512  fail_if_missing=.true.)
2513  filename = trim(cs%inputdir) // trim(h2_file)
2514  call log_param(param_file, mdl, "INPUTDIR/H2_FILE", filename)
2515  call read_data(filename, 'h2', h2, domain=g%domain%mpp_domain, timelevel=1)
2516  do j=g%jsc,g%jec ; do i=g%isc,g%iec
2517  ! Restrict rms topo to 10 percent of column depth.
2518  h2(i,j) = min(0.01*g%bathyT(i,j)**2, h2(i,j))
2519  ! Compute the fixed part; units are [kg m-2] here;
2520  ! will be multiplied by N and En to get into [W m-2]
2521  cs%TKE_itidal_loss_fixed(i,j) = 0.5*kappa_h2_factor*gv%Rho0*&
2522  kappa_itides * h2(i,j)
2523  enddo; enddo
2524 
2525  ! Read in prescribed coast/ridge/shelf angles from file
2526  call get_param(param_file, mdl, "REFL_ANGLE_FILE", refl_angle_file, &
2527  "The path to the file containing the local angle of \n"//&
2528  "the coastline/ridge/shelf with respect to the equator.", &
2529  fail_if_missing=.false.)
2530  filename = trim(cs%inputdir) // trim(refl_angle_file)
2531  call log_param(param_file, mdl, "INPUTDIR/REFL_ANGLE_FILE", filename)
2532  allocate(cs%refl_angle(isd:ied,jsd:jed)) ; cs%refl_angle(:,:) = cs%nullangle
2533  call read_data(filename, 'refl_angle', cs%refl_angle, &
2534  domain=g%domain%mpp_domain, timelevel=1)
2535  ! replace NANs with null value
2536  do j=g%jsc,g%jec ; do i=g%isc,g%iec
2537  if(is_nan(cs%refl_angle(i,j))) cs%refl_angle(i,j) = cs%nullangle
2538  enddo ; enddo
2539  call pass_var(cs%refl_angle,g%domain)
2540 
2541  ! Read in prescribed partial reflection coefficients from file
2542  call get_param(param_file, mdl, "REFL_PREF_FILE", refl_pref_file, &
2543  "The path to the file containing the reflection coefficients.", &
2544  fail_if_missing=.false.)
2545  filename = trim(cs%inputdir) // trim(refl_pref_file)
2546  call log_param(param_file, mdl, "INPUTDIR/REFL_PREF_FILE", filename)
2547  allocate(cs%refl_pref(isd:ied,jsd:jed)) ; cs%refl_pref(:,:) = 1.0
2548  call read_data(filename, 'refl_pref', cs%refl_pref, &
2549  domain=g%domain%mpp_domain, timelevel=1)
2550  !CS%refl_pref = CS%refl_pref*1 ! adjust partial reflection if desired
2551  call pass_var(cs%refl_pref,g%domain)
2552 
2553  ! Tag reflection cells with partial reflection (done here for speed)
2554  allocate(cs%refl_pref_logical(isd:ied,jsd:jed)) ; cs%refl_pref_logical(:,:) = .false.
2555  do j=jsd,jed
2556  do i=isd,ied
2557  ! flag cells with partial reflection
2558  if (cs%refl_angle(i,j) .ne. cs%nullangle .and. &
2559  cs%refl_pref(i,j) < 1.0 .and. cs%refl_pref(i,j) > 0.0) then
2560  cs%refl_pref_logical(i,j) = .true.
2561  endif
2562  enddo
2563  enddo
2564 
2565  ! Read in double-reflective (ridge) tags from file
2566  call get_param(param_file, mdl, "REFL_DBL_FILE", refl_dbl_file, &
2567  "The path to the file containing the double-reflective ridge tags.", &
2568  fail_if_missing=.false.)
2569  filename = trim(cs%inputdir) // trim(refl_dbl_file)
2570  call log_param(param_file, mdl, "INPUTDIR/REFL_DBL_FILE", filename)
2571  allocate(ridge_temp(isd:ied,jsd:jed)) ; ridge_temp(:,:) = 0.0
2572  call read_data(filename, 'refl_dbl', ridge_temp, &
2573  domain=g%domain%mpp_domain, timelevel=1)
2574  call pass_var(ridge_temp,g%domain)
2575  allocate(cs%refl_dbl(isd:ied,jsd:jed)) ; cs%refl_dbl(:,:) = .false.
2576  do i=isd,ied; do j=jsd,jed
2577  if (ridge_temp(i,j) == 1) then; cs%refl_dbl(i,j) = .true.
2578  else ; cs%refl_dbl(i,j) = .false. ; endif
2579  enddo; enddo
2580 
2581  ! Read in prescribed land mask from file (if overwriting -BDM).
2582  ! This should be done in MOM_initialize_topography subroutine
2583  ! defined in MOM_fixed_initialization.F90 (BDM)
2584  !call get_param(param_file, mdl, "LAND_MASK_FILE", land_mask_file, &
2585  ! "The path to the file containing the land mask.", &
2586  ! fail_if_missing=.false.)
2587  !filename = trim(CS%inputdir) // trim(land_mask_file)
2588  !call log_param(param_file, mdl, "INPUTDIR/LAND_MASK_FILE", filename)
2589  !G%mask2dCu(:,:) = 1 ; G%mask2dCv(:,:) = 1 ; G%mask2dT(:,:) = 1
2590  !call read_data(filename, 'land_mask', G%mask2dCu, &
2591  ! domain=G%domain%mpp_domain, timelevel=1)
2592  !call read_data(filename, 'land_mask', G%mask2dCv, &
2593  ! domain=G%domain%mpp_domain, timelevel=1)
2594  !call read_data(filename, 'land_mask', G%mask2dT, &
2595  ! domain=G%domain%mpp_domain, timelevel=1)
2596  !call pass_var(G%mask2dCu,G%domain)
2597  !call pass_var(G%mask2dCv,G%domain)
2598  !call pass_var(G%mask2dT,G%domain)
2599 
2600  ! Read in prescribed partial east face blockages from file (if overwriting -BDM)
2601  !call get_param(param_file, mdl, "dy_Cu_FILE", dy_Cu_file, &
2602  ! "The path to the file containing the east face blockages.", &
2603  ! fail_if_missing=.false.)
2604  !filename = trim(CS%inputdir) // trim(dy_Cu_file)
2605  !call log_param(param_file, mdl, "INPUTDIR/dy_Cu_FILE", filename)
2606  !G%dy_Cu(:,:) = 0.0
2607  !call read_data(filename, 'dy_Cu', G%dy_Cu, &
2608  ! domain=G%domain%mpp_domain, timelevel=1)
2609  !call pass_var(G%dy_Cu,G%domain)
2610 
2611  ! Read in prescribed partial north face blockages from file (if overwriting -BDM)
2612  !call get_param(param_file, mdl, "dx_Cv_FILE", dx_Cv_file, &
2613  ! "The path to the file containing the north face blockages.", &
2614  ! fail_if_missing=.false.)
2615  !filename = trim(CS%inputdir) // trim(dx_Cv_file)
2616  !call log_param(param_file, mdl, "INPUTDIR/dx_Cv_FILE", filename)
2617  !G%dx_Cv(:,:) = 0.0
2618  !call read_data(filename, 'dx_Cv', G%dx_Cv, &
2619  ! domain=G%domain%mpp_domain, timelevel=1)
2620  !call pass_var(G%dx_Cv,G%domain)
2621 
2622  ! For debugging - delete later
2623  call get_param(param_file, mdl, "INTERNAL_TIDE_SOURCE_X", cs%int_tide_source_x, &
2624  "X Location of generation site for internal tide", default=1.)
2625  call get_param(param_file, mdl, "INTERNAL_TIDE_SOURCE_Y", cs%int_tide_source_y, &
2626  "Y Location of generation site for internal tide", default=1.)
2627 
2628  ! Register maps of reflection parameters
2629  cs%id_refl_ang = register_diag_field('ocean_model', 'refl_angle', diag%axesT1, &
2630  time, 'Local angle of coastline/ridge/shelf with respect to equator', 'rad')
2631  cs%id_refl_pref = register_diag_field('ocean_model', 'refl_pref', diag%axesT1, &
2632  time, 'Partial reflection coefficients', '')
2633  cs%id_dx_Cv = register_diag_field('ocean_model', 'dx_Cv', diag%axesT1, &
2634  time, 'North face unblocked width', 'm') ! used if overriding (BDM)
2635  cs%id_dy_Cu = register_diag_field('ocean_model', 'dy_Cu', diag%axesT1, &
2636  time, 'East face unblocked width', 'm') ! used if overriding (BDM)
2637  cs%id_land_mask = register_diag_field('ocean_model', 'land_mask', diag%axesT1, &
2638  time, 'Land mask', 'logical') ! used if overriding (BDM)
2639  ! Output reflection parameters as diags here (not needed every timestep)
2640  if (cs%id_refl_ang > 0) call post_data(cs%id_refl_ang, cs%refl_angle, cs%diag)
2641  if (cs%id_refl_pref > 0) call post_data(cs%id_refl_pref, cs%refl_pref, cs%diag)
2642  if (cs%id_dx_Cv > 0) call post_data(cs%id_dx_Cv, g%dx_Cv, cs%diag)
2643  if (cs%id_dy_Cu > 0) call post_data(cs%id_dy_Cu, g%dy_Cu, cs%diag)
2644  if (cs%id_land_mask > 0) call post_data(cs%id_land_mask, g%mask2dT, cs%diag)
2645 
2646  ! Register 2-D energy density (summed over angles, freq, modes)
2647  cs%id_tot_En = register_diag_field('ocean_model', 'ITide_tot_En', diag%axesT1, &
2648  time, 'Internal tide total energy density', 'J m-2')
2649  ! Register 2-D drag scale used for quadratic bottom drag
2650  cs%id_itide_drag = register_diag_field('ocean_model', 'ITide_drag', diag%axesT1, &
2651  time, 'Interior and bottom drag internal tide decay timescale', 's-1')
2652  !Register 2-D energy input into internal tides
2653  cs%id_TKE_itidal_input = register_diag_field('ocean_model', 'TKE_itidal_input', diag%axesT1, &
2654  time, 'Conversion from barotropic to baroclinic tide, \n'//&
2655  'a fraction of which goes into rays', 'W m-2')
2656  ! Register 2-D energy losses (summed over angles, freq, modes)
2657  cs%id_tot_leak_loss = register_diag_field('ocean_model', 'ITide_tot_leak_loss', diag%axesT1, &
2658  time, 'Internal tide energy loss to background drag', 'W m-2')
2659  cs%id_tot_quad_loss = register_diag_field('ocean_model', 'ITide_tot_quad_loss', diag%axesT1, &
2660  time, 'Internal tide energy loss to bottom drag', 'W m-2')
2661  cs%id_tot_itidal_loss = register_diag_field('ocean_model', 'ITide_tot_itidal_loss', diag%axesT1, &
2662  time, 'Internal tide energy loss to wave drag', 'W m-2')
2663  cs%id_tot_Froude_loss = register_diag_field('ocean_model', 'ITide_tot_Froude_loss', diag%axesT1, &
2664  time, 'Internal tide energy loss to wave breaking', 'W m-2')
2665  cs%id_tot_allprocesses_loss = register_diag_field('ocean_model', 'ITide_tot_allprocesses_loss', diag%axesT1, &
2666  time, 'Internal tide energy loss summed over all processes', 'W m-2')
2667 
2668  allocate(cs%id_En_mode(cs%nFreq,cs%nMode)) ; cs%id_En_mode(:,:) = -1
2669  allocate(cs%id_En_ang_mode(cs%nFreq,cs%nMode)) ; cs%id_En_ang_mode(:,:) = -1
2670  allocate(cs%id_itidal_loss_mode(cs%nFreq,cs%nMode)) ; cs%id_itidal_loss_mode(:,:) = -1
2671  allocate(cs%id_allprocesses_loss_mode(cs%nFreq,cs%nMode)) ; cs%id_allprocesses_loss_mode(:,:) = -1
2672  allocate(cs%id_itidal_loss_ang_mode(cs%nFreq,cs%nMode)) ; cs%id_itidal_loss_ang_mode(:,:) = -1
2673  allocate(cs%id_Ub_mode(cs%nFreq,cs%nMode)) ; cs%id_Ub_mode(:,:) = -1
2674  allocate(cs%id_cp_mode(cs%nFreq,cs%nMode)) ; cs%id_cp_mode(:,:) = -1
2675 
2676  allocate(angles(cs%NAngle)) ; angles(:) = 0.0
2677  angle_size = (8.0*atan(1.0)) / (real(num_angle))
2678  do a=1,num_angle ; angles(a) = (real(a) - 1) * angle_size ; enddo
2679 
2680  id_ang = diag_axis_init("angle", angles, "Radians", "N", "Angular Orienation of Fluxes")
2681  call define_axes_group(diag, (/ diag%axesT1%handles(1), diag%axesT1%handles(2), id_ang /), axes_ang)
2682 
2683  do fr=1,cs%nFreq ; write(freq_name(fr), '("freq",i1)') fr ; enddo
2684  do m=1,cs%nMode ; do fr=1,cs%nFreq
2685  ! Register 2-D energy density (summed over angles) for each freq and mode
2686  write(var_name, '("Itide_En_freq",i1,"_mode",i1)') fr, m
2687  write(var_descript, '("Internal tide energy density in frequency ",i1," mode ",i1)') fr, m
2688  cs%id_En_mode(fr,m) = register_diag_field('ocean_model', var_name, &
2689  diag%axesT1, time, var_descript, 'J m-2')
2690  call mom_mesg("Registering "//trim(var_name)//", Described as: "//var_descript, 5)
2691 
2692  ! Register 3-D (i,j,a) energy density for each freq and mode
2693  write(var_name, '("Itide_En_ang_freq",i1,"_mode",i1)') fr, m
2694  write(var_descript, '("Internal tide angular energy density in frequency ",i1," mode ",i1)') fr, m
2695  cs%id_En_ang_mode(fr,m) = register_diag_field('ocean_model', var_name, &
2696  axes_ang, time, var_descript, 'J m-2 band-1')
2697  call mom_mesg("Registering "//trim(var_name)//", Described as: "//var_descript, 5)
2698 
2699  ! Register 2-D energy loss (summed over angles) for each freq and mode
2700  ! wave-drag only
2701  write(var_name, '("Itide_wavedrag_loss_freq",i1,"_mode",i1)') fr, m
2702  write(var_descript, '("Internal tide energy loss due to wave-drag from frequency ",i1," mode ",i1)') fr, m
2703  cs%id_itidal_loss_mode(fr,m) = register_diag_field('ocean_model', var_name, &
2704  diag%axesT1, time, var_descript, 'W m-2')
2705  call mom_mesg("Registering "//trim(var_name)//", Described as: "//var_descript, 5)
2706  ! all loss processes
2707  write(var_name, '("Itide_allprocesses_loss_freq",i1,"_mode",i1)') fr, m
2708  write(var_descript, '("Internal tide energy loss due to all processes from frequency ",i1," mode ",i1)') fr, m
2709  cs%id_allprocesses_loss_mode(fr,m) = register_diag_field('ocean_model', var_name, &
2710  diag%axesT1, time, var_descript, 'W m-2')
2711  call mom_mesg("Registering "//trim(var_name)//", Described as: "//var_descript, 5)
2712 
2713  ! Register 3-D (i,j,a) energy loss for each freq and mode
2714  ! wave-drag only
2715  write(var_name, '("Itide_wavedrag_loss_ang_freq",i1,"_mode",i1)') fr, m
2716  write(var_descript, '("Internal tide energy loss due to wave-drag from frequency ",i1," mode ",i1)') fr, m
2717  cs%id_itidal_loss_ang_mode(fr,m) = register_diag_field('ocean_model', var_name, &
2718  axes_ang, time, var_descript, 'W m-2 band-1')
2719  call mom_mesg("Registering "//trim(var_name)//", Described as: "//var_descript, 5)
2720 
2721  ! Register 2-D period-averaged near-bottom horizonal velocity for each freq and mode
2722  write(var_name, '("Itide_Ub_freq",i1,"_mode",i1)') fr, m
2723  write(var_descript, '("Near-bottom horizonal velocity for frequency ",i1," mode ",i1)') fr, m
2724  cs%id_Ub_mode(fr,m) = register_diag_field('ocean_model', var_name, &
2725  diag%axesT1, time, var_descript, 'm s-1')
2726  call mom_mesg("Registering "//trim(var_name)//", Described as: "//var_descript, 5)
2727 
2728  ! Register 2-D horizonal phase velocity for each freq and mode
2729  write(var_name, '("Itide_cp_freq",i1,"_mode",i1)') fr, m
2730  write(var_descript, '("Horizonal phase velocity for frequency ",i1," mode ",i1)') fr, m
2731  cs%id_cp_mode(fr,m) = register_diag_field('ocean_model', var_name, &
2732  diag%axesT1, time, var_descript, 'm s-1')
2733  call mom_mesg("Registering "//trim(var_name)//", Described as: "//var_descript, 5)
2734 
2735  enddo ; enddo
2736 
2737  ! Initialize wave_structure (not sure if this should be here - BDM)
2738  call wave_structure_init(time, g, param_file, diag, cs%wave_structure_CSp)
2739 
2740 end subroutine internal_tides_init
2741 
2742 
2743 subroutine internal_tides_end(CS)
2744  type(int_tide_cs), pointer :: CS
2745  ! Arguments: CS - A pointer to the control structure returned by a previous
2746  ! call to internal_tides_init, it will be deallocated here.
2747 
2748  if (associated(cs)) then
2749  if (associated(cs%En)) deallocate(cs%En)
2750  if (allocated(cs%frequency)) deallocate(cs%frequency)
2751  if (allocated(cs%id_En_mode)) deallocate(cs%id_En_mode)
2752  if (allocated(cs%id_Ub_mode)) deallocate(cs%id_Ub_mode)
2753  if (allocated(cs%id_cp_mode)) deallocate(cs%id_cp_mode)
2754  deallocate(cs)
2755  endif
2756  cs => null()
2757 end subroutine internal_tides_end
2758 
2759 
2760 end module mom_internal_tides
The following structure contains pointers to various fields which may be used describe the surface st...
subroutine propagate(En, cn, freq, dt, G, CS, NAngle)
This subroutine does refraction on the internal waves at a single frequency.
subroutine, public wave_structure(h, tv, G, GV, cn, ModeNum, freq, CS, En, full_halos)
This subroutine determines the internal wave velocity structure for any mode.
subroutine propagate_x(En, speed_x, Cgx_av, dCgx, dt, G, Nangle, CS, LB)
subroutine zonal_flux_en(u, h, hL, hR, uh, dt, G, j, ish, ieh, vol_CFL)
This subroutines evaluates the zonal mass or volume fluxes in a layer.
subroutine, public internal_tides_init(Time, G, GV, param_file, diag, CS)
integer, parameter, public to_all
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
subroutine propagate_corner_spread(En, energized_wedge, NAngle, speed, dt, G, CS, LB)
This subroutine does first-order corner advection. It was written with the hopes of smoothing out the...
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Provides the ocean grid type.
Definition: MOM_grid.F90:2
subroutine, public do_group_pass(group, MOM_dom)
subroutine refract(En, cn, freq, dt, G, NAngle, use_PPMang)
This subroutine does refraction on the internal waves at a single frequency.
subroutine, public get_lowmode_loss(i, j, G, CS, mechanism, TKE_loss_sum)
This subroutine extracts the energy lost from the propagating internal which has been summed across a...
subroutine, public internal_tides_end(CS)
subroutine, public define_axes_group(diag_cs, handles, axes, nz, vertical_coordinate_number, x_cell_method, y_cell_method, v_cell_method, is_h_point, is_q_point, is_u_point, is_v_point, is_layer, is_interface, is_native, needs_remapping, needs_interpolating, xyave_axes)
Defines a group of "axes" from list of handles.
subroutine, public wave_structure_init(Time, G, param_file, diag, CS)
This module contains I/O framework code.
Definition: MOM_io.F90:2
subroutine propagate_y(En, speed_y, Cgy_av, dCgy, dt, G, Nangle, CS, LB)
subroutine correct_halo_rotation(En, test, G, NAngle)
This subroutine rotates points in the halos where required to accomodate changes in grid orientation...
subroutine ppm_reconstruction_x(h_in, h_l, h_r, G, LB, simple_2nd)
This subroutine calculates left/right edge values for PPM reconstruction.
logical function, public query_averaging_enabled(diag_cs, time_int, time_end)
subroutine, public propagate_int_tide(h, tv, cn, TKE_itidal_input, vel_btTide, Nb, dt, G, GV, CS)
This subroutine calls other subroutines in this file that are needed to refract, propagate, and dissipate energy density of the internal tide.
subroutine, public start_group_pass(group, MOM_dom)
A group of 1D axes that comprise a 1D/2D/3D mesh.
subroutine itidal_lowmode_loss(G, CS, Nb, Ub, En, TKE_loss_fixed, TKE_loss, dt, full_halos)
This subroutine calculates the energy lost from the propagating internal tide due to scattering over ...
subroutine sum_en(G, CS, En, label)
This subroutine checks for energy conservation on computational domain.
logical function, public is_root_pe()
subroutine, public complete_group_pass(group, MOM_dom)
subroutine merid_flux_en(v, h, hL, hR, vh, dt, G, J, ish, ieh, vol_CFL)
This subroutines evaluates the meridional mass or volume fluxes in a layer.
subroutine, public mom_mesg(message, verb, all_print)
Type for describing a variable, typically a tracer.
Definition: MOM_io.F90:51
subroutine teleport(En, NAngle, CS, G, LB)
This subroutine moves energy across lines of partial reflection to prevent reflection of energy that ...
subroutine ppm_reconstruction_y(h_in, h_l, h_r, G, LB, simple_2nd)
This subroutine calculates left/right edge valus for PPM reconstruction.
subroutine, public save_restart(directory, time, G, CS, time_stamped, filename, GV)
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
subroutine ppm_limit_pos(h_in, h_L, h_R, h_min, G, iis, iie, jis, jie)
This subroutine limits the left/right edge values of the PPM reconstruction to give a reconstruction ...
subroutine, public restart_init(param_file, CS, restart_root)
subroutine ppm_angular_advect(En2d, CFL_ang, Flux_En, NAngle, dt, halo_ang)
This subroutine calculates the 1-d flux for advection in angular space using a monotonic piecewise pa...
real function, public global_area_mean(var, G)
integer function, public register_diag_field(module_name, field_name, axes, init_time, long_name, units, missing_value, range, mask_variant, standard_name, verbose, do_not_log, err_msg, interp_method, tile_count, cmor_field_name, cmor_long_name, cmor_units, cmor_standard_name, cell_methods, x_cell_method, y_cell_method, v_cell_method, conversion, v_extensive)
Returns the "diag_mediator" handle for a group (native, CMOR, z-coord, ...) of diagnostics derived fr...
subroutine, public mom_error(level, message, all_print)
subroutine reflect(En, NAngle, CS, G, LB)
This subroutine does reflection of the internal waves at a single frequency.