MOM6
MOM_tidal_mixing.F90
1 !> Interface to vertical tidal mixing schemes including CVMix tidal mixing.
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 use mom_diag_mediator, only : diag_ctrl, time_type, register_diag_field
7 use mom_diag_mediator, only : safe_alloc_ptr, post_data
8 use mom_debugging, only : hchksum
9 use mom_eos, only : calculate_density
10 use mom_error_handler, only : mom_error, is_root_pe, fatal, warning, note
11 use mom_file_parser, only : openparameterblock, closeparameterblock
13 use mom_grid, only : ocean_grid_type
14 use mom_io, only : slasher, mom_read_data, field_size
15 use mom_remapping, only : remapping_cs, initialize_remapping, remapping_core_h
16 use mom_string_functions, only : uppercase, lowercase
20 use cvmix_tidal, only : cvmix_init_tidal, cvmix_compute_simmons_invariant
21 use cvmix_tidal, only : cvmix_coeffs_tidal, cvmix_tidal_params_type
22 use cvmix_tidal, only : cvmix_compute_schmittner_invariant, cvmix_compute_schmittnercoeff
23 use cvmix_tidal, only : cvmix_coeffs_tidal_schmittner
24 use cvmix_kinds_and_types, only : cvmix_global_params_type
25 use cvmix_put_get, only : cvmix_put
26 
27 implicit none ; private
28 
29 #include <MOM_memory.h>
30 
31 public tidal_mixing_init
32 public setup_tidal_diagnostics
33 public calculate_tidal_mixing
34 public post_tidal_diagnostics
35 public tidal_mixing_end
36 
37 ! A note on unit descriptions in comments: MOM6 uses units that can be rescaled for dimensional
38 ! consistency testing. These are noted in comments with units like Z, H, L, and T, along with
39 ! their mks counterparts with notation like "a velocity [Z T-1 ~> m s-1]". If the units
40 ! vary with the Boussinesq approximation, the Boussinesq variant is given first.
41 
42 !> Containers for tidal mixing diagnostics
43 type, public :: tidal_mixing_diags ; private
44  real, pointer, dimension(:,:,:) :: &
45  kd_itidal => null(),& !< internal tide diffusivity at interfaces [Z2 T-1 ~> m2 s-1].
46  fl_itidal => null(),& !< vertical flux of tidal turbulent dissipation [Z3 T-3 ~> m3 s-3]
47  kd_niku => null(),& !< lee-wave diffusivity at interfaces [Z2 T-1 ~> m2 s-1].
48  kd_niku_work => null(),& !< layer integrated work by lee-wave driven mixing [kg Z3 m-3 T-3 ~> W m-2]
49  kd_itidal_work => null(),& !< layer integrated work by int tide driven mixing [kg Z3 m-3 T-3 ~> W m-2]
50  kd_lowmode_work => null(),& !< layer integrated work by low mode driven mixing [kg Z3 m-3 T-3 ~> W m-2]
51  n2_int => null(),& !< Bouyancy frequency squared at interfaces [s-2]
52  vert_dep_3d => null(),& !< The 3-d mixing energy deposition [W m-3]
53  schmittner_coeff_3d => null() !< The coefficient in the Schmittner et al mixing scheme, in UNITS?
54  real, pointer, dimension(:,:,:) :: tidal_qe_md => null() !< Input tidal energy dissipated locally,
55  !! interpolated to model vertical coordinate [W m-3?]
56  real, pointer, dimension(:,:,:) :: kd_lowmode => null() !< internal tide diffusivity at interfaces
57  !! due to propagating low modes [Z2 T-1 ~> m2 s-1].
58  real, pointer, dimension(:,:,:) :: fl_lowmode => null() !< vertical flux of tidal turbulent
59  !! dissipation due to propagating low modes [Z3 T-3 ~> m3 s-3]
60  real, pointer, dimension(:,:) :: &
61  tke_itidal_used => null(),& !< internal tide TKE input at ocean bottom [kg Z3 m-3 T-3 ~> W m-2]
62  n2_bot => null(),& !< bottom squared buoyancy frequency [T-2 ~> s-2]
63  n2_meanz => null(),& !< vertically averaged buoyancy frequency [T-2 ~> s-2]
64  polzin_decay_scale_scaled => null(),& !< vertical scale of decay for tidal dissipation
65  polzin_decay_scale => null(),& !< vertical decay scale for tidal diss with Polzin [m]
66  simmons_coeff_2d => null() !< The Simmons et al mixing coefficient
67 
68 end type
69 
70 !> Control structure with parameters for the tidal mixing module.
71 type, public :: tidal_mixing_cs
72  ! TODO: private
73  logical :: debug = .true. !< If true, do more extensive debugging checks. This is hard-coded.
74 
75  ! Parameters
76  logical :: int_tide_dissipation = .false. !< Internal tide conversion (from barotropic)
77  !! with the schemes of St Laurent et al (2002) & Simmons et al (2004)
78 
79  integer :: int_tide_profile !< A coded integer indicating the vertical profile
80  !! for dissipation of the internal waves. Schemes that are
81  !! currently encoded are St Laurent et al (2002) and Polzin (2009).
82  logical :: lee_wave_dissipation = .false. !< Enable lee-wave driven mixing, following
83  !! Nikurashin (2010), with a vertical energy
84  !! deposition profile specified by Lee_wave_profile to be
85  !! St Laurent et al (2002) or Simmons et al (2004) scheme
86 
87  integer :: lee_wave_profile !< A coded integer indicating the vertical profile
88  !! for dissipation of the lee waves. Schemes that are
89  !! currently encoded are St Laurent et al (2002) and
90  !! Polzin (2009).
91  real :: int_tide_decay_scale !< decay scale for internal wave TKE [Z ~> m].
92 
93  real :: mu_itides !< efficiency for conversion of dissipation
94  !! to potential energy [nondim]
95 
96  real :: gamma_itides !< fraction of local dissipation [nondim]
97 
98  real :: gamma_lee !< fraction of local dissipation for lee waves
99  !! (Nikurashin's energy input) [nondim]
100  real :: decay_scale_factor_lee !< Scaling factor for the decay scale of lee
101  !! wave energy dissipation [nondim]
102 
103  real :: min_zbot_itides !< minimum depth for internal tide conversion [Z ~> m].
104  logical :: lowmode_itidal_dissipation = .false. !< If true, consider mixing due to breaking low
105  !! modes that have been remotely generated using an internal tidal
106  !! dissipation scheme to specify the vertical profile of the energy
107  !! input to drive diapycnal mixing, along the lines of St. Laurent
108  !! et al. (2002) and Simmons et al. (2004).
109 
110  real :: nu_polzin !< The non-dimensional constant used in Polzin form of
111  !! the vertical scale of decay of tidal dissipation
112 
113  real :: nbotref_polzin !< Reference value for the buoyancy frequency at the
114  !! ocean bottom used in Polzin formulation of the
115  !! vertical scale of decay of tidal dissipation [T-1 ~> s-1]
116  real :: polzin_decay_scale_factor !< Scaling factor for the decay length scale
117  !! of the tidal dissipation profile in Polzin [nondim]
118  real :: polzin_decay_scale_max_factor !< The decay length scale of tidal dissipation
119  !! profile in Polzin formulation should not exceed
120  !! Polzin_decay_scale_max_factor * depth of the ocean [nondim].
121  real :: polzin_min_decay_scale !< minimum decay scale of the tidal dissipation
122  !! profile in Polzin formulation [Z ~> m].
123 
124  real :: tke_itide_max !< maximum internal tide conversion [kg Z3 m-3 T-3 ~> W m-2]
125  !! available to mix above the BBL
126 
127  real :: utide !< constant tidal amplitude [Z T-1 ~> m s-1] if READ_TIDEAMP is false.
128  real :: kappa_itides !< topographic wavenumber and non-dimensional scaling [Z-1 ~> m-1].
129  real :: kappa_h2_factor !< factor for the product of wavenumber * rms sgs height
130  character(len=200) :: inputdir !< The directory in which to find input files
131 
132  logical :: use_cvmix_tidal = .false. !< true if CVMix is to be used for determining
133  !! diffusivity due to tidal mixing
134 
135  real :: min_thickness !< Minimum thickness allowed [m]
136 
137  ! CVMix-specific parameters
138  integer :: cvmix_tidal_scheme = -1 !< 1 for Simmons, 2 for Schmittner
139  type(cvmix_tidal_params_type) :: cvmix_tidal_params !< A CVMix-specific type with parameters for tidal mixing
140  type(cvmix_global_params_type) :: cvmix_glb_params !< CVMix-specific for Prandtl number only
141  real :: tidal_max_coef !< CVMix-specific maximum allowable tidal diffusivity. [m^2/s]
142  real :: tidal_diss_lim_tc !< CVMix-specific dissipation limit depth for
143  !! tidal-energy-constituent data [Z ~> m].
144  type(remapping_cs) :: remap_cs !< The control structure for remapping
145 
146  ! Data containers
147  real, pointer, dimension(:,:) :: tke_niku => null() !< Lee wave driven Turbulent Kinetic Energy input
148  !! [kg Z3 m-3 T-3 ~> W m-2]
149  real, pointer, dimension(:,:) :: tke_itidal => null() !< The internal Turbulent Kinetic Energy input divided
150  !! by the bottom stratfication [kg Z3 m-3 T-2 ~> J m-2].
151  real, pointer, dimension(:,:) :: nb => null() !< The near bottom buoyancy frequency [T-1 ~> s-1].
152  real, pointer, dimension(:,:) :: mask_itidal => null() !< A mask of where internal tide energy is input
153  real, pointer, dimension(:,:) :: h2 => null() !< Squared bottom depth variance [m2].
154  real, pointer, dimension(:,:) :: tideamp => null() !< RMS tidal amplitude [m s-1]
155  real, allocatable, dimension(:) :: h_src !< tidal constituent input layer thickness [m]
156  real, allocatable, dimension(:,:) :: tidal_qe_2d !< Tidal energy input times the local dissipation
157  !! fraction, q*E(x,y), with the CVMix implementation
158  !! of Jayne et al tidal mixing [W m-2].
159  !! TODO: make this E(x,y) only
160  real, allocatable, dimension(:,:,:) :: tidal_qe_3d_in !< q*E(x,y,z) with the Schmittner parameterization [W m-3?]
161 
162  logical :: answers_2018 !< If true, use the order of arithmetic and expressions that recover the
163  !! answers from the end of 2018. Otherwise, use updated and more robust
164  !! forms of the same expressions.
165 
166  ! Diagnostics
167  type(diag_ctrl), pointer :: diag => null() !< structure to regulate diagnostic output timing
168  type(tidal_mixing_diags), pointer :: dd => null() !< A pointer to a structure of diagnostic arrays
169 
170  !>@{ Diagnostic identifiers
171  integer :: id_tke_itidal = -1
172  integer :: id_tke_leewave = -1
173  integer :: id_kd_itidal = -1
174  integer :: id_kd_niku = -1
175  integer :: id_kd_lowmode = -1
176  integer :: id_kd_itidal_work = -1
177  integer :: id_kd_niku_work = -1
178  integer :: id_kd_lowmode_work = -1
179  integer :: id_nb = -1
180  integer :: id_n2_bot = -1
181  integer :: id_n2_meanz = -1
182  integer :: id_fl_itidal = -1
183  integer :: id_fl_lowmode = -1
184  integer :: id_polzin_decay_scale = -1
185  integer :: id_polzin_decay_scale_scaled = -1
186  integer :: id_n2_int = -1
187  integer :: id_simmons_coeff = -1
188  integer :: id_schmittner_coeff = -1
189  integer :: id_tidal_qe_md = -1
190  integer :: id_vert_dep = -1
191  !!@}
192 
193 end type tidal_mixing_cs
194 
195 !!@{ Coded parmameters for specifying mixing schemes
196 character*(20), parameter :: stlaurent_profile_string = "STLAURENT_02"
197 character*(20), parameter :: polzin_profile_string = "POLZIN_09"
198 integer, parameter :: stlaurent_02 = 1
199 integer, parameter :: polzin_09 = 2
200 character*(20), parameter :: simmons_scheme_string = "SIMMONS"
201 character*(20), parameter :: schmittner_scheme_string = "SCHMITTNER"
202 integer, parameter :: simmons = 1
203 integer, parameter :: schmittner = 2
204 !!@}
205 
206 contains
207 
208 !> Initializes internal tidal dissipation scheme for diapycnal mixing
209 logical function tidal_mixing_init(Time, G, GV, US, param_file, diag, CS)
210  type(time_type), intent(in) :: time !< The current time.
211  type(ocean_grid_type), intent(in) :: g !< Grid structure.
212  type(verticalgrid_type), intent(in) :: gv !< Vertical grid structure.
213  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
214  type(param_file_type), intent(in) :: param_file !< Run-time parameter file handle
215  type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure.
216  type(tidal_mixing_cs), pointer :: cs !< This module's control structure.
217 
218  ! Local variables
219  logical :: read_tideamp
220  logical :: default_2018_answers
221  character(len=20) :: tmpstr, int_tide_profile_str
222  character(len=20) :: cvmix_tidal_scheme_str, tidal_energy_type
223  character(len=200) :: filename, h2_file, niku_tke_input_file
224  character(len=200) :: tidal_energy_file, tideamp_file
225  real :: utide, hamp, prandtl_tidal, max_frac_rough
226  real :: niku_scale ! local variable for scaling the Nikurashin TKE flux data
227  integer :: i, j, is, ie, js, je
228  integer :: isd, ied, jsd, jed
229  ! This include declares and sets the variable "version".
230 # include "version_variable.h"
231  character(len=40) :: mdl = "MOM_tidal_mixing" !< This module's name.
232 
233  if (associated(cs)) then
234  call mom_error(warning, "tidal_mixing_init called when control structure "// &
235  "is already associated.")
236  return
237  endif
238  allocate(cs)
239  allocate(cs%dd)
240 
241  cs%debug = cs%debug.and.is_root_pe()
242 
243  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
244  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
245 
246  cs%diag => diag
247 
248  ! Read parameters
249  call log_version(param_file, mdl, version, &
250  "Vertical Tidal Mixing Parameterization")
251  call get_param(param_file, mdl, "USE_CVMix_TIDAL", cs%use_CVMix_tidal, &
252  "If true, turns on tidal mixing via CVMix", &
253  default=.false.)
254 
255  call get_param(param_file, mdl, "INPUTDIR", cs%inputdir, default=".",do_not_log=.true.)
256  cs%inputdir = slasher(cs%inputdir)
257  call get_param(param_file, mdl, "INT_TIDE_DISSIPATION", cs%int_tide_dissipation, &
258  "If true, use an internal tidal dissipation scheme to "//&
259  "drive diapycnal mixing, along the lines of St. Laurent "//&
260  "et al. (2002) and Simmons et al. (2004).", default=cs%use_CVMix_tidal)
261 
262  ! return if tidal mixing is inactive
263  tidal_mixing_init = cs%int_tide_dissipation
264  if (.not. tidal_mixing_init) return
265 
266  call get_param(param_file, mdl, "DEFAULT_2018_ANSWERS", default_2018_answers, &
267  "This sets the default value for the various _2018_ANSWERS parameters.", &
268  default=.true.)
269  call get_param(param_file, mdl, "TIDAL_MIXING_2018_ANSWERS", cs%answers_2018, &
270  "If true, use the order of arithmetic and expressions that recover the "//&
271  "answers from the end of 2018. Otherwise, use updated and more robust "//&
272  "forms of the same expressions.", default=default_2018_answers)
273 
274  if (cs%int_tide_dissipation) then
275 
276  ! Read in CVMix tidal scheme if CVMix tidal mixing is on
277  if (cs%use_CVMix_tidal) then
278  call get_param(param_file, mdl, "CVMIX_TIDAL_SCHEME", cvmix_tidal_scheme_str, &
279  "CVMIX_TIDAL_SCHEME selects the CVMix tidal mixing "//&
280  "scheme with INT_TIDE_DISSIPATION. Valid values are:\n"//&
281  "\t SIMMONS - Use the Simmons et al (2004) tidal \n"//&
282  "\t mixing scheme.\n"//&
283  "\t SCHMITTNER - Use the Schmittner et al (2014) tidal \n"//&
284  "\t mixing scheme.", &
285  default=simmons_scheme_string)
286  cvmix_tidal_scheme_str = uppercase(cvmix_tidal_scheme_str)
287 
288  select case (cvmix_tidal_scheme_str)
289  case (simmons_scheme_string) ; cs%CVMix_tidal_scheme = simmons
290  case (schmittner_scheme_string) ; cs%CVMix_tidal_scheme = schmittner
291  case default
292  call mom_error(fatal, "tidal_mixing_init: Unrecognized setting "// &
293  "#define CVMIX_TIDAL_SCHEME "//trim(cvmix_tidal_scheme_str)//" found in input file.")
294  end select
295  endif ! CS%use_CVMix_tidal
296 
297  ! Read in vertical profile of tidal energy dissipation
298  if ( cs%CVMix_tidal_scheme.eq.schmittner .or. .not. cs%use_CVMix_tidal) then
299  call get_param(param_file, mdl, "INT_TIDE_PROFILE", int_tide_profile_str, &
300  "INT_TIDE_PROFILE selects the vertical profile of energy "//&
301  "dissipation with INT_TIDE_DISSIPATION. Valid values are:\n"//&
302  "\t STLAURENT_02 - Use the St. Laurent et al exponential \n"//&
303  "\t decay profile.\n"//&
304  "\t POLZIN_09 - Use the Polzin WKB-stretched algebraic \n"//&
305  "\t decay profile.", &
306  default=stlaurent_profile_string)
307  int_tide_profile_str = uppercase(int_tide_profile_str)
308 
309  select case (int_tide_profile_str)
310  case (stlaurent_profile_string) ; cs%int_tide_profile = stlaurent_02
311  case (polzin_profile_string) ; cs%int_tide_profile = polzin_09
312  case default
313  call mom_error(fatal, "tidal_mixing_init: Unrecognized setting "// &
314  "#define INT_TIDE_PROFILE "//trim(int_tide_profile_str)//" found in input file.")
315  end select
316  endif
317 
318  elseif (cs%use_CVMix_tidal) then
319  call mom_error(fatal, "tidal_mixing_init: Cannot set INT_TIDE_DISSIPATION to False "// &
320  "when USE_CVMix_TIDAL is set to True.")
321  endif
322 
323  call get_param(param_file, mdl, "LEE_WAVE_DISSIPATION", cs%Lee_wave_dissipation, &
324  "If true, use an lee wave driven dissipation scheme to "//&
325  "drive diapycnal mixing, along the lines of Nikurashin "//&
326  "(2010) and using the St. Laurent et al. (2002) "//&
327  "and Simmons et al. (2004) vertical profile", default=.false.)
328  if (cs%lee_wave_dissipation) then
329  if (cs%use_CVMix_tidal) then
330  call mom_error(fatal, "tidal_mixing_init: Lee wave driven dissipation scheme cannot "// &
331  "be used when CVMix tidal mixing scheme is active.")
332  endif
333  call get_param(param_file, mdl, "LEE_WAVE_PROFILE", tmpstr, &
334  "LEE_WAVE_PROFILE selects the vertical profile of energy "//&
335  "dissipation with LEE_WAVE_DISSIPATION. Valid values are:\n"//&
336  "\t STLAURENT_02 - Use the St. Laurent et al exponential \n"//&
337  "\t decay profile.\n"//&
338  "\t POLZIN_09 - Use the Polzin WKB-stretched algebraic \n"//&
339  "\t decay profile.", &
340  default=stlaurent_profile_string)
341  tmpstr = uppercase(tmpstr)
342  select case (tmpstr)
343  case (stlaurent_profile_string) ; cs%lee_wave_profile = stlaurent_02
344  case (polzin_profile_string) ; cs%lee_wave_profile = polzin_09
345  case default
346  call mom_error(fatal, "tidal_mixing_init: Unrecognized setting "// &
347  "#define LEE_WAVE_PROFILE "//trim(tmpstr)//" found in input file.")
348  end select
349  endif
350 
351  call get_param(param_file, mdl, "INT_TIDE_LOWMODE_DISSIPATION", cs%Lowmode_itidal_dissipation, &
352  "If true, consider mixing due to breaking low modes that "//&
353  "have been remotely generated; as with itidal drag on the "//&
354  "barotropic tide, use an internal tidal dissipation scheme to "//&
355  "drive diapycnal mixing, along the lines of St. Laurent "//&
356  "et al. (2002) and Simmons et al. (2004).", default=.false.)
357 
358  if ((cs%Int_tide_dissipation .and. (cs%int_tide_profile == polzin_09)) .or. &
359  (cs%lee_wave_dissipation .and. (cs%lee_wave_profile == polzin_09))) then
360  if (cs%use_CVMix_tidal) then
361  call mom_error(fatal, "tidal_mixing_init: Polzin scheme cannot "// &
362  "be used when CVMix tidal mixing scheme is active.")
363  endif
364  call get_param(param_file, mdl, "NU_POLZIN", cs%Nu_Polzin, &
365  "When the Polzin decay profile is used, this is a "//&
366  "non-dimensional constant in the expression for the "//&
367  "vertical scale of decay for the tidal energy dissipation.", &
368  units="nondim", default=0.0697)
369  call get_param(param_file, mdl, "NBOTREF_POLZIN", cs%Nbotref_Polzin, &
370  "When the Polzin decay profile is used, this is the "//&
371  "reference value of the buoyancy frequency at the ocean "//&
372  "bottom in the Polzin formulation for the vertical "//&
373  "scale of decay for the tidal energy dissipation.", &
374  units="s-1", default=9.61e-4, scale=us%T_to_s)
375  call get_param(param_file, mdl, "POLZIN_DECAY_SCALE_FACTOR", &
376  cs%Polzin_decay_scale_factor, &
377  "When the Polzin decay profile is used, this is a "//&
378  "scale factor for the vertical scale of decay of the tidal "//&
379  "energy dissipation.", default=1.0, units="nondim")
380  call get_param(param_file, mdl, "POLZIN_SCALE_MAX_FACTOR", &
381  cs%Polzin_decay_scale_max_factor, &
382  "When the Polzin decay profile is used, this is a factor "//&
383  "to limit the vertical scale of decay of the tidal "//&
384  "energy dissipation to POLZIN_DECAY_SCALE_MAX_FACTOR "//&
385  "times the depth of the ocean.", units="nondim", default=1.0)
386  call get_param(param_file, mdl, "POLZIN_MIN_DECAY_SCALE", cs%Polzin_min_decay_scale, &
387  "When the Polzin decay profile is used, this is the "//&
388  "minimum vertical decay scale for the vertical profile\n"//&
389  "of internal tide dissipation with the Polzin (2009) formulation", &
390  units="m", default=0.0, scale=us%m_to_Z)
391  endif
392 
393  if (cs%Int_tide_dissipation .or. cs%Lee_wave_dissipation) then
394  call get_param(param_file, mdl, "INT_TIDE_DECAY_SCALE", cs%Int_tide_decay_scale, &
395  "The decay scale away from the bottom for tidal TKE with "//&
396  "the new coding when INT_TIDE_DISSIPATION is used.", &
397  !units="m", default=0.0)
398  units="m", default=500.0, scale=us%m_to_Z) ! TODO: confirm this new default
399  call get_param(param_file, mdl, "MU_ITIDES", cs%Mu_itides, &
400  "A dimensionless turbulent mixing efficiency used with "//&
401  "INT_TIDE_DISSIPATION, often 0.2.", units="nondim", default=0.2)
402  call get_param(param_file, mdl, "GAMMA_ITIDES", cs%Gamma_itides, &
403  "The fraction of the internal tidal energy that is "//&
404  "dissipated locally with INT_TIDE_DISSIPATION. "//&
405  "THIS NAME COULD BE BETTER.", &
406  units="nondim", default=0.3333)
407  call get_param(param_file, mdl, "MIN_ZBOT_ITIDES", cs%min_zbot_itides, &
408  "Turn off internal tidal dissipation when the total "//&
409  "ocean depth is less than this value.", units="m", default=0.0, scale=us%m_to_Z)
410  endif
411 
412  if ( (cs%Int_tide_dissipation .or. cs%Lee_wave_dissipation) .and. &
413  .not. cs%use_CVMix_tidal) then
414 
415  call safe_alloc_ptr(cs%Nb,isd,ied,jsd,jed)
416  call safe_alloc_ptr(cs%h2,isd,ied,jsd,jed)
417  call safe_alloc_ptr(cs%TKE_itidal,isd,ied,jsd,jed)
418  call safe_alloc_ptr(cs%mask_itidal,isd,ied,jsd,jed) ; cs%mask_itidal(:,:) = 1.0
419 
420  call get_param(param_file, mdl, "KAPPA_ITIDES", cs%kappa_itides, &
421  "A topographic wavenumber used with INT_TIDE_DISSIPATION. "//&
422  "The default is 2pi/10 km, as in St.Laurent et al. 2002.", &
423  units="m-1", default=8.e-4*atan(1.0), scale=us%Z_to_m)
424 
425  call get_param(param_file, mdl, "UTIDE", cs%utide, &
426  "The constant tidal amplitude used with INT_TIDE_DISSIPATION.", &
427  units="m s-1", default=0.0, scale=us%m_to_Z*us%T_to_s)
428  call safe_alloc_ptr(cs%tideamp,is,ie,js,je) ; cs%tideamp(:,:) = cs%utide
429 
430  call get_param(param_file, mdl, "KAPPA_H2_FACTOR", cs%kappa_h2_factor, &
431  "A scaling factor for the roughness amplitude with "//&
432  "INT_TIDE_DISSIPATION.", units="nondim", default=1.0)
433  call get_param(param_file, mdl, "TKE_ITIDE_MAX", cs%TKE_itide_max, &
434  "The maximum internal tide energy source available to mix "//&
435  "above the bottom boundary layer with INT_TIDE_DISSIPATION.", &
436  units="W m-2", default=1.0e3, scale=us%m_to_Z**3*us%T_to_s**3)
437 
438  call get_param(param_file, mdl, "READ_TIDEAMP", read_tideamp, &
439  "If true, read a file (given by TIDEAMP_FILE) containing "//&
440  "the tidal amplitude with INT_TIDE_DISSIPATION.", default=.false.)
441  if (read_tideamp) then
442  if (cs%use_CVMix_tidal) then
443  call mom_error(fatal, "tidal_mixing_init: Tidal amplitude files are "// &
444  "not compatible with CVMix tidal mixing. ")
445  endif
446  call get_param(param_file, mdl, "TIDEAMP_FILE", tideamp_file, &
447  "The path to the file containing the spatially varying "//&
448  "tidal amplitudes with INT_TIDE_DISSIPATION.", default="tideamp.nc")
449  filename = trim(cs%inputdir) // trim(tideamp_file)
450  call log_param(param_file, mdl, "INPUTDIR/TIDEAMP_FILE", filename)
451  call mom_read_data(filename, 'tideamp', cs%tideamp, g%domain, timelevel=1, scale=us%m_to_Z*us%T_to_s)
452  endif
453 
454  call get_param(param_file, mdl, "H2_FILE", h2_file, &
455  "The path to the file containing the sub-grid-scale "//&
456  "topographic roughness amplitude with INT_TIDE_DISSIPATION.", &
457  fail_if_missing=(.not.cs%use_CVMix_tidal))
458  filename = trim(cs%inputdir) // trim(h2_file)
459  call log_param(param_file, mdl, "INPUTDIR/H2_FILE", filename)
460  call mom_read_data(filename, 'h2', cs%h2, g%domain, timelevel=1, scale=us%m_to_Z**2)
461 
462  call get_param(param_file, mdl, "FRACTIONAL_ROUGHNESS_MAX", max_frac_rough, &
463  "The maximum topographic roughness amplitude as a fraction of the mean depth, "//&
464  "or a negative value for no limitations on roughness.", &
465  units="nondim", default=0.1)
466 
467  do j=js,je ; do i=is,ie
468  if (g%bathyT(i,j) < cs%min_zbot_itides) cs%mask_itidal(i,j) = 0.0
469  cs%tideamp(i,j) = cs%tideamp(i,j) * cs%mask_itidal(i,j) * g%mask2dT(i,j)
470 
471  ! Restrict rms topo to a fraction (often 10 percent) of the column depth.
472  if (cs%answers_2018 .and. (max_frac_rough >= 0.0)) then
473  hamp = min(max_frac_rough*g%bathyT(i,j), sqrt(cs%h2(i,j)))
474  cs%h2(i,j) = hamp*hamp
475  else
476  if (max_frac_rough >= 0.0) &
477  cs%h2(i,j) = min((max_frac_rough*g%bathyT(i,j))**2, cs%h2(i,j))
478  endif
479 
480  utide = cs%tideamp(i,j)
481  ! Compute the fixed part of internal tidal forcing.
482  ! The units here are [kg Z3 m-3 T-2 ~> J m-2 = kg s-2] here.
483  cs%TKE_itidal(i,j) = 0.5 * cs%kappa_h2_factor * gv%Rho0 * &
484  cs%kappa_itides * cs%h2(i,j) * utide*utide
485  enddo ; enddo
486 
487  endif
488 
489  if (cs%Lee_wave_dissipation) then
490 
491  call get_param(param_file, mdl, "NIKURASHIN_TKE_INPUT_FILE",niku_tke_input_file, &
492  "The path to the file containing the TKE input from lee "//&
493  "wave driven mixing. Used with LEE_WAVE_DISSIPATION.", &
494  fail_if_missing=.true.)
495  call get_param(param_file, mdl, "NIKURASHIN_SCALE",niku_scale, &
496  "A non-dimensional factor by which to scale the lee-wave "//&
497  "driven TKE input. Used with LEE_WAVE_DISSIPATION.", &
498  units="nondim", default=1.0)
499 
500  filename = trim(cs%inputdir) // trim(niku_tke_input_file)
501  call log_param(param_file, mdl, "INPUTDIR/NIKURASHIN_TKE_INPUT_FILE", &
502  filename)
503  call safe_alloc_ptr(cs%TKE_Niku,is,ie,js,je) ; cs%TKE_Niku(:,:) = 0.0
504  call mom_read_data(filename, 'TKE_input', cs%TKE_Niku, g%domain, timelevel=1, & ! ??? timelevel -aja
505  scale=us%m_to_Z**3*us%T_to_s**3)
506  cs%TKE_Niku(:,:) = niku_scale * cs%TKE_Niku(:,:)
507 
508  call get_param(param_file, mdl, "GAMMA_NIKURASHIN",cs%Gamma_lee, &
509  "The fraction of the lee wave energy that is dissipated "//&
510  "locally with LEE_WAVE_DISSIPATION.", units="nondim", &
511  default=0.3333)
512  call get_param(param_file, mdl, "DECAY_SCALE_FACTOR_LEE",cs%Decay_scale_factor_lee, &
513  "Scaling for the vertical decay scaleof the local "//&
514  "dissipation of lee waves dissipation.", units="nondim", &
515  default=1.0)
516  else
517  cs%Decay_scale_factor_lee = -9.e99 ! This should never be used if CS%Lee_wave_dissipation = False
518  endif
519 
520  ! Configure CVMix
521  if (cs%use_CVMix_tidal) then
522 
523  ! Read in CVMix params
524  !call openParameterBlock(param_file,'CVMix_TIDAL')
525  call get_param(param_file, mdl, "TIDAL_MAX_COEF", cs%tidal_max_coef, &
526  "largest acceptable value for tidal diffusivity", &
527  units="m^2/s", default=50e-4) ! the default is 50e-4 in CVMix, 100e-4 in POP.
528  call get_param(param_file, mdl, "TIDAL_DISS_LIM_TC", cs%tidal_diss_lim_tc, &
529  "Min allowable depth for dissipation for tidal-energy-constituent data. "//&
530  "No dissipation contribution is applied above TIDAL_DISS_LIM_TC.", &
531  units="m", default=0.0, scale=us%m_to_Z)
532  call get_param(param_file, mdl, "TIDAL_ENERGY_FILE",tidal_energy_file, &
533  "The path to the file containing tidal energy "//&
534  "dissipation. Used with CVMix tidal mixing schemes.", &
535  fail_if_missing=.true.)
536  call get_param(param_file, mdl, 'MIN_THICKNESS', cs%min_thickness, default=0.001, &
537  do_not_log=.true.)
538  call get_param(param_file, mdl, "PRANDTL_TIDAL", prandtl_tidal, &
539  "Prandtl number used by CVMix tidal mixing schemes "//&
540  "to convert vertical diffusivities into viscosities.", &
541  units="nondim", default=1.0, &
542  do_not_log=.true.)
543  call cvmix_put(cs%CVMix_glb_params,'Prandtl',prandtl_tidal)
544 
545  tidal_energy_file = trim(cs%inputdir) // trim(tidal_energy_file)
546  call get_param(param_file, mdl, "TIDAL_ENERGY_TYPE",tidal_energy_type, &
547  "The type of input tidal energy flux dataset. Valid values are"//&
548  "\t Jayne\n"//&
549  "\t ER03 \n",&
550  fail_if_missing=.true.)
551  ! Check whether tidal energy input format and CVMix tidal mixing scheme are consistent
552  if ( .not. ( &
553  (uppercase(tidal_energy_type(1:4)).eq.'JAYN' .and. cs%CVMix_tidal_scheme.eq.simmons).or. &
554  (uppercase(tidal_energy_type(1:4)).eq.'ER03' .and. cs%CVMix_tidal_scheme.eq.schmittner) ) )then
555  call mom_error(fatal, "tidal_mixing_init: Tidal energy file type ("//&
556  trim(tidal_energy_type)//") is incompatible with CVMix tidal "//&
557  " mixing scheme: "//trim(cvmix_tidal_scheme_str) )
558  endif
559  cvmix_tidal_scheme_str = lowercase(cvmix_tidal_scheme_str)
560 
561  ! Set up CVMix
562  call cvmix_init_tidal(cvmix_tidal_params_user = cs%CVMix_tidal_params, &
563  mix_scheme = cvmix_tidal_scheme_str, &
564  efficiency = cs%Mu_itides, &
565  vertical_decay_scale = cs%int_tide_decay_scale*us%Z_to_m, &
566  max_coefficient = cs%tidal_max_coef, &
567  local_mixing_frac = cs%Gamma_itides, &
568  depth_cutoff = cs%min_zbot_itides*us%Z_to_m)
569 
570  call read_tidal_energy(g, us, tidal_energy_type, tidal_energy_file, cs)
571 
572  !call closeParameterBlock(param_file)
573 
574  endif ! CVMix on
575 
576  ! Register Diagnostics fields
577 
578  if (cs%Int_tide_dissipation .or. cs%Lee_wave_dissipation .or. &
579  cs%Lowmode_itidal_dissipation) then
580 
581  cs%id_Kd_itidal = register_diag_field('ocean_model','Kd_itides',diag%axesTi,time, &
582  'Internal Tide Driven Diffusivity', 'm2 s-1', conversion=us%Z2_T_to_m2_s)
583 
584  if (cs%use_CVMix_tidal) then
585  cs%id_N2_int = register_diag_field('ocean_model','N2_int',diag%axesTi,time, &
586  'Bouyancy frequency squared, at interfaces', 's-2')
587  !> TODO: add units
588  cs%id_Simmons_coeff = register_diag_field('ocean_model','Simmons_coeff',diag%axesT1,time, &
589  'time-invariant portion of the tidal mixing coefficient using the Simmons', '')
590  cs%id_Schmittner_coeff = register_diag_field('ocean_model','Schmittner_coeff',diag%axesTL,time, &
591  'time-invariant portion of the tidal mixing coefficient using the Schmittner', '')
592  cs%id_tidal_qe_md = register_diag_field('ocean_model','tidal_qe_md',diag%axesTL,time, &
593  'input tidal energy dissipated locally interpolated to model vertical coordinates', '')
594  cs%id_vert_dep = register_diag_field('ocean_model','vert_dep',diag%axesTi,time, &
595  'vertical deposition function needed for Simmons et al tidal mixing', '')
596 
597  else
598  cs%id_TKE_itidal = register_diag_field('ocean_model','TKE_itidal',diag%axesT1,time, &
599  'Internal Tide Driven Turbulent Kinetic Energy', 'W m-2', conversion=(us%Z_to_m**3*us%s_to_T**3))
600  cs%id_Nb = register_diag_field('ocean_model','Nb',diag%axesT1,time, &
601  'Bottom Buoyancy Frequency', 's-1', conversion=us%s_to_T)
602 
603  cs%id_Kd_lowmode = register_diag_field('ocean_model','Kd_lowmode',diag%axesTi,time, &
604  'Internal Tide Driven Diffusivity (from propagating low modes)', &
605  'm2 s-1', conversion=us%Z2_T_to_m2_s)
606 
607  cs%id_Fl_itidal = register_diag_field('ocean_model','Fl_itides',diag%axesTi,time, &
608  'Vertical flux of tidal turbulent dissipation', &
609  'm3 s-3', conversion=(us%Z_to_m**3*us%s_to_T**3))
610 
611  cs%id_Fl_lowmode = register_diag_field('ocean_model','Fl_lowmode',diag%axesTi,time, &
612  'Vertical flux of tidal turbulent dissipation (from propagating low modes)', &
613  'm3 s-3', conversion=(us%Z_to_m**3*us%s_to_T**3))
614 
615  cs%id_Polzin_decay_scale = register_diag_field('ocean_model','Polzin_decay_scale',diag%axesT1,time, &
616  'Vertical decay scale for the tidal turbulent dissipation with Polzin scheme', &
617  'm', conversion=us%Z_to_m)
618 
619  cs%id_Polzin_decay_scale_scaled = register_diag_field('ocean_model', &
620  'Polzin_decay_scale_scaled', diag%axesT1, time, &
621  'Vertical decay scale for the tidal turbulent dissipation with Polzin scheme, '// &
622  'scaled by N2_bot/N2_meanz', 'm', conversion=us%Z_to_m)
623 
624  cs%id_N2_bot = register_diag_field('ocean_model','N2_b',diag%axesT1,time, &
625  'Bottom Buoyancy frequency squared', 's-2', conversion=us%s_to_T**2)
626 
627  cs%id_N2_meanz = register_diag_field('ocean_model','N2_meanz', diag%axesT1, time, &
628  'Buoyancy frequency squared averaged over the water column', 's-2', conversion=us%s_to_T**2)
629 
630  cs%id_Kd_Itidal_Work = register_diag_field('ocean_model','Kd_Itidal_Work',diag%axesTL,time, &
631  'Work done by Internal Tide Diapycnal Mixing', 'W m-2', conversion=(us%Z_to_m**3*us%s_to_T**3))
632 
633  cs%id_Kd_Niku_Work = register_diag_field('ocean_model','Kd_Nikurashin_Work',diag%axesTL,time, &
634  'Work done by Nikurashin Lee Wave Drag Scheme', 'W m-2', conversion=(us%Z_to_m**3*us%s_to_T**3))
635 
636  cs%id_Kd_Lowmode_Work = register_diag_field('ocean_model','Kd_Lowmode_Work',diag%axesTL,time, &
637  'Work done by Internal Tide Diapycnal Mixing (low modes)', &
638  'W m-2', conversion=(us%Z_to_m**3*us%s_to_T**3))
639 
640  if (cs%Lee_wave_dissipation) then
641  cs%id_TKE_leewave = register_diag_field('ocean_model','TKE_leewave',diag%axesT1,time, &
642  'Lee wave Driven Turbulent Kinetic Energy', 'W m-2', conversion=(us%Z_to_m**3*us%s_to_T**3))
643  cs%id_Kd_Niku = register_diag_field('ocean_model','Kd_Nikurashin',diag%axesTi,time, &
644  'Lee Wave Driven Diffusivity', 'm2 s-1', conversion=us%Z2_T_to_m2_s)
645  endif
646  endif ! S%use_CVMix_tidal
647  endif
648 
649 end function tidal_mixing_init
650 
651 
652 !> Depending on whether or not CVMix is active, calls the associated subroutine to compute internal
653 !! tidal dissipation and to add the effect of internal-tide-driven mixing to the layer or interface
654 !! diffusivities.
655 subroutine calculate_tidal_mixing(h, N2_bot, j, TKE_to_Kd, max_TKE, G, GV, US, CS, &
656  N2_lay, N2_int, Kd_lay, Kd_int, Kd_max, Kv)
657  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
658  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure
659  type(unit_scale_type), intent(in) :: us !< A dimensional unit scaling type
660  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
661  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
662  real, dimension(SZI_(G)), intent(in) :: n2_bot !< The near-bottom squared buoyancy
663  !! frequency [T-2 ~> s-2].
664  real, dimension(SZI_(G),SZK_(G)), intent(in) :: n2_lay !< The squared buoyancy frequency of the
665  !! layers [T-2 ~> s-2].
666  real, dimension(SZI_(G),SZK_(G)+1), intent(in) :: n2_int !< The squared buoyancy frequency at the
667  !! interfaces [T-2 ~> s-2].
668  integer, intent(in) :: j !< The j-index to work on
669  real, dimension(SZI_(G),SZK_(G)), intent(in) :: tke_to_kd !< The conversion rate between the TKE
670  !! dissipated within a layer and the
671  !! diapycnal diffusivity within that layer,
672  !! usually (~Rho_0 / (G_Earth * dRho_lay))
673  !! [Z2 T-1 / Z3 T-3 = T2 Z-1 ~> s2 m-1]
674  real, dimension(SZI_(G),SZK_(G)), intent(in) :: max_tke !< The energy required to for a layer to entrain
675  !! to its maximum realizable thickness [Z3 T-3 ~> m3 s-3]
676  type(tidal_mixing_cs), pointer :: cs !< The control structure for this module
677  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
678  intent(inout) :: kd_lay !< The diapycnal diffusvity in layers [Z2 T-1 ~> m2 s-1].
679  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1), &
680  optional, intent(inout) :: kd_int !< The diapycnal diffusvity at interfaces,
681  !! [Z2 T-1 ~> m2 s-1].
682  real, intent(in) :: kd_max !< The maximum increment for diapycnal
683  !! diffusivity due to TKE-based processes,
684  !! [Z2 T-1 ~> m2 s-1].
685  !! Set this to a negative value to have no limit.
686  real, dimension(:,:,:), pointer :: kv !< The "slow" vertical viscosity at each interface
687  !! (not layer!) [Z2 T-1 ~> m2 s-1].
688 
689  if (cs%Int_tide_dissipation .or. cs%Lee_wave_dissipation .or. cs%Lowmode_itidal_dissipation) then
690  if (cs%use_CVMix_tidal) then
691  call calculate_cvmix_tidal(h, j, g, gv, us, cs, n2_int, kd_lay, kv)
692  else
693  call add_int_tide_diffusivity(h, n2_bot, j, tke_to_kd, max_tke, &
694  g, gv, us, cs, n2_lay, kd_lay, kd_int, kd_max)
695  endif
696  endif
697 end subroutine calculate_tidal_mixing
698 
699 
700 !> Calls the CVMix routines to compute tidal dissipation and to add the effect of internal-tide-driven
701 !! mixing to the interface diffusivities.
702 subroutine calculate_cvmix_tidal(h, j, G, GV, US, CS, N2_int, Kd_lay, Kv)
703  integer, intent(in) :: j !< The j-index to work on
704  type(ocean_grid_type), intent(in) :: G !< Grid structure.
705  type(verticalgrid_type), intent(in) :: GV !< ocean vertical grid structure
706  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
707  type(tidal_mixing_cs), pointer :: CS !< This module's control structure.
708  real, dimension(SZI_(G),SZK_(G)+1), intent(in) :: N2_int !< The squared buoyancy
709  !! frequency at the interfaces [T-2 ~> s-2].
710  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
711  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2].
712  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
713  intent(inout) :: Kd_lay!< The diapycnal diffusivities in the layers [Z2 T-1 ~> m2 s-1].
714  real, dimension(:,:,:), pointer :: Kv !< The "slow" vertical viscosity at each interface
715  !! (not layer!) [Z2 T-1 ~> m2 s-1].
716  ! Local variables
717  real, dimension(SZK_(G)+1) :: Kd_tidal ! tidal diffusivity [m2 s-1]
718  real, dimension(SZK_(G)+1) :: Kv_tidal ! tidal viscosity [m2 s-1]
719  real, dimension(SZK_(G)+1) :: vert_dep ! vertical deposition
720  real, dimension(SZK_(G)+1) :: iFaceHeight ! Height of interfaces [m]
721  real, dimension(SZK_(G)+1) :: SchmittnerSocn
722  real, dimension(SZK_(G)) :: cellHeight ! Height of cell centers [m]
723  real, dimension(SZK_(G)) :: tidal_qe_md ! Tidal dissipation energy interpolated from 3d input
724  ! to model coordinates
725  real, dimension(SZK_(G)+1) :: N2_int_i ! De-scaled interface buoyancy frequency [s-2]
726  real, dimension(SZK_(G)) :: Schmittner_coeff
727  real, dimension(SZK_(G)) :: h_m ! Cell thickness [m]
728  real, allocatable, dimension(:,:) :: exp_hab_zetar
729 
730  integer :: i, k, is, ie
731  real :: dh, hcorr, Simmons_coeff
732  real, parameter :: rho_fw = 1000.0 ! fresh water density [kg/m^3]
733  ! TODO: when coupled, get this from CESM (SHR_CONST_RHOFW)
734  real :: h_neglect, h_neglect_edge
735  type(tidal_mixing_diags), pointer :: dd => null()
736 
737  is = g%isc ; ie = g%iec
738  dd => cs%dd
739 
740  select case (cs%CVMix_tidal_scheme)
741  case (simmons)
742  do i=is,ie
743 
744  if (g%mask2dT(i,j)<1) cycle
745 
746  ifaceheight = 0.0 ! BBL is all relative to the surface
747  hcorr = 0.0
748  do k=1,g%ke
749  ! cell center and cell bottom in meters (negative values in the ocean)
750  dh = h(i,j,k) * gv%H_to_m ! Nominal thickness to use for increment, rescaled to m for use by CVMix.
751  dh = dh + hcorr ! Take away the accumulated error (could temporarily make dh<0)
752  hcorr = min( dh - cs%min_thickness, 0. ) ! If inflating then hcorr<0
753  dh = max( dh, cs%min_thickness ) ! Limit increment dh>=min_thickness
754  cellheight(k) = ifaceheight(k) - 0.5 * dh
755  ifaceheight(k+1) = ifaceheight(k) - dh
756  enddo
757 
758  call cvmix_compute_simmons_invariant( nlev = g%ke, &
759  energy_flux = cs%tidal_qe_2d(i,j), &
760  rho = rho_fw, &
761  simmonscoeff = simmons_coeff, &
762  vertdep = vert_dep, &
763  zw = ifaceheight, &
764  zt = cellheight, &
765  cvmix_tidal_params_user = cs%CVMix_tidal_params)
766 
767  ! Since we pass tidal_qe_2d=(CS%Gamma_itides)*tidal_energy_flux_2d, and not tidal_energy_flux_2d in
768  ! above subroutine call, we divide Simmons_coeff by CS%Gamma_itides as a corrective step:
769  ! TODO: (CS%Gamma_itides)*tidal_energy_flux_2d is unnecessary, directly use tidal_energy_flux_2d
770  simmons_coeff = simmons_coeff / cs%Gamma_itides
771 
772 
773  ! XXX: Temporary de-scaling of N2_int(i,:) into a temporary variable
774  do k = 1,g%ke+1
775  n2_int_i(k) = us%s_to_T**2 * n2_int(i,k)
776  enddo
777 
778  call cvmix_coeffs_tidal( mdiff_out = kv_tidal, &
779  tdiff_out = kd_tidal, &
780  nsqr = n2_int_i, &
781  oceandepth = -ifaceheight(g%ke+1),&
782  simmonscoeff = simmons_coeff, &
783  vert_dep = vert_dep, &
784  nlev = g%ke, &
785  max_nlev = g%ke, &
786  cvmix_params = cs%CVMix_glb_params, &
787  cvmix_tidal_params_user = cs%CVMix_tidal_params)
788 
789  ! Update diffusivity
790  do k=1,g%ke
791  kd_lay(i,j,k) = kd_lay(i,j,k) + 0.5 * us%m2_s_to_Z2_T * (kd_tidal(k) + kd_tidal(k+1))
792  enddo
793 
794  ! Update viscosity with the proper unit conversion.
795  if (associated(kv)) then
796  do k=1,g%ke+1
797  kv(i,j,k) = kv(i,j,k) + us%m2_s_to_Z2_T * kv_tidal(k) ! Rescale from m2 s-1 to Z2 T-1.
798  enddo
799  endif
800 
801  ! diagnostics
802  if (associated(dd%Kd_itidal)) then
803  dd%Kd_itidal(i,j,:) = us%m2_s_to_Z2_T*kd_tidal(:)
804  endif
805  if (associated(dd%N2_int)) then
806  dd%N2_int(i,j,:) = n2_int(i,:)
807  endif
808  if (associated(dd%Simmons_coeff_2d)) then
809  dd%Simmons_coeff_2d(i,j) = simmons_coeff
810  endif
811  if (associated(dd%vert_dep_3d)) then
812  dd%vert_dep_3d(i,j,:) = vert_dep(:)
813  endif
814 
815  enddo ! i=is,ie
816 
817  case (schmittner)
818 
819  ! TODO: correct exp_hab_zetar shapes in CVMix_compute_Schmittner_invariant
820  ! and CVMix_compute_SchmittnerCoeff low subroutines
821 
822  allocate(exp_hab_zetar(g%ke+1,g%ke+1))
823  if (gv%Boussinesq) then
824  h_neglect = gv%m_to_H*1.0e-30 ; h_neglect_edge = gv%m_to_H*1.0e-10
825  else
826  h_neglect = gv%kg_m2_to_H*1.0e-30 ; h_neglect_edge = gv%kg_m2_to_H*1.0e-10
827  endif
828 
829 
830  do i=is,ie
831 
832  if (g%mask2dT(i,j)<1) cycle
833 
834  ifaceheight = 0.0 ! BBL is all relative to the surface
835  hcorr = 0.0
836  do k=1,g%ke
837  h_m(k) = h(i,j,k)*gv%H_to_m ! Rescale thicknesses to m for use by CVmix.
838  ! cell center and cell bottom in meters (negative values in the ocean)
839  dh = h_m(k) + hcorr ! Nominal thickness less the accumulated error (could temporarily make dh<0)
840  hcorr = min( dh - cs%min_thickness, 0. ) ! If inflating then hcorr<0
841  dh = max( dh, cs%min_thickness ) ! Limit increment dh>=min_thickness
842  cellheight(k) = ifaceheight(k) - 0.5 * dh
843  ifaceheight(k+1) = ifaceheight(k) - dh
844  enddo
845 
846  schmittnersocn = 0.0 ! TODO: compute this
847 
848  ! form the time-invariant part of Schmittner coefficient term
849  call cvmix_compute_schmittner_invariant(nlev = g%ke, &
850  vertdep = vert_dep, &
851  efficiency = cs%Mu_itides, &
852  rho = rho_fw, &
853  exp_hab_zetar = exp_hab_zetar, &
854  zw = ifaceheight, &
855  cvmix_tidal_params_user = cs%CVMix_tidal_params)
856  !TODO: in above call, there is no need to pass efficiency, since it gets
857  ! passed via CVMix_init_tidal and stored in CVMix_tidal_params. Change
858  ! CVMix API to prevent this redundancy.
859 
860  ! remap from input z coordinate to model coordinate:
861  tidal_qe_md = 0.0
862  call remapping_core_h(cs%remap_cs, size(cs%h_src), cs%h_src, cs%tidal_qe_3d_in(i,j,:), &
863  g%ke, h_m, tidal_qe_md)
864 
865  ! form the Schmittner coefficient that is based on 3D q*E, which is formed from
866  ! summing q_i*TidalConstituent_i over the number of constituents.
867  call cvmix_compute_schmittnercoeff( nlev = g%ke, &
868  energy_flux = tidal_qe_md(:), &
869  rho = rho_fw, &
870  schmittnercoeff = schmittner_coeff, &
871  exp_hab_zetar = exp_hab_zetar, &
872  cvmix_tidal_params_user = cs%CVMix_tidal_params)
873 
874  ! XXX: Temporary de-scaling of N2_int(i,:) into a temporary variable
875  do k = 1,g%ke+1
876  n2_int_i(k) = us%s_to_T**2 * n2_int(i,k)
877  enddo
878 
879  call cvmix_coeffs_tidal_schmittner( mdiff_out = kv_tidal, &
880  tdiff_out = kd_tidal, &
881  nsqr = n2_int_i, &
882  oceandepth = -ifaceheight(g%ke+1), &
883  vert_dep = vert_dep, &
884  nlev = g%ke, &
885  max_nlev = g%ke, &
886  schmittnercoeff = schmittner_coeff, &
887  schmittnersouthernocean = schmittnersocn, &
888  cvmix_params = cs%CVMix_glb_params, &
889  cvmix_tidal_params_user = cs%CVMix_tidal_params)
890 
891  ! Update diffusivity
892  do k=1,g%ke
893  kd_lay(i,j,k) = kd_lay(i,j,k) + 0.5 * us%m2_s_to_Z2_T * (kd_tidal(k) + kd_tidal(k+1))
894  enddo
895 
896  ! Update viscosity
897  if (associated(kv)) then
898  do k=1,g%ke+1
899  kv(i,j,k) = kv(i,j,k) + us%m2_s_to_Z2_T * kv_tidal(k) ! Rescale from m2 s-1 to Z2 T-1.
900  enddo
901  endif
902 
903  ! diagnostics
904  if (associated(dd%Kd_itidal)) then
905  dd%Kd_itidal(i,j,:) = us%m2_s_to_Z2_T*kd_tidal(:)
906  endif
907  if (associated(dd%N2_int)) then
908  dd%N2_int(i,j,:) = n2_int(i,:)
909  endif
910  if (associated(dd%Schmittner_coeff_3d)) then
911  dd%Schmittner_coeff_3d(i,j,:) = schmittner_coeff(:)
912  endif
913  if (associated(dd%tidal_qe_md)) then
914  dd%tidal_qe_md(i,j,:) = tidal_qe_md(:)
915  endif
916  if (associated(dd%vert_dep_3d)) then
917  dd%vert_dep_3d(i,j,:) = vert_dep(:)
918  endif
919  enddo ! i=is,ie
920 
921  deallocate(exp_hab_zetar)
922 
923  case default
924  call mom_error(fatal, "tidal_mixing_init: Unrecognized setting "// &
925  "#define CVMIX_TIDAL_SCHEME found in input file.")
926  end select
927 
928 end subroutine calculate_cvmix_tidal
929 
930 
931 !> This subroutine adds the effect of internal-tide-driven mixing to the layer diffusivities.
932 !! The mechanisms considered are (1) local dissipation of internal waves generated by the
933 !! barotropic flow ("itidal"), (2) local dissipation of internal waves generated by the propagating
934 !! low modes (rays) of the internal tide ("lowmode"), and (3) local dissipation of internal lee waves.
935 !! Will eventually need to add diffusivity due to other wave-breaking processes (e.g. Bottom friction,
936 !! Froude-number-depending breaking, PSI, etc.).
937 subroutine add_int_tide_diffusivity(h, N2_bot, j, TKE_to_Kd, max_TKE, G, GV, US, CS, &
938  N2_lay, Kd_lay, Kd_int, Kd_max)
939  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
940  type(verticalgrid_type), intent(in) :: GV !< The ocean's vertical grid structure
941  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
942  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
943  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2]
944  real, dimension(SZI_(G)), intent(in) :: N2_bot !< The near-bottom squared buoyancy frequency
945  !! frequency [T-2 ~> s-2].
946  real, dimension(SZI_(G),SZK_(G)), intent(in) :: N2_lay !< The squared buoyancy frequency of the
947  !! layers [T-2 ~> s-2].
948  integer, intent(in) :: j !< The j-index to work on
949  real, dimension(SZI_(G),SZK_(G)), intent(in) :: TKE_to_Kd !< The conversion rate between the TKE
950  !! dissipated within a layer and the
951  !! diapycnal diffusivity within that layer,
952  !! usually (~Rho_0 / (G_Earth * dRho_lay))
953  !! [Z2 T-1 / Z3 T-3 = T2 Z-1 ~> s2 m-1]
954  real, dimension(SZI_(G),SZK_(G)), intent(in) :: max_TKE !< The energy required to for a layer to entrain
955  !! to its maximum realizable thickness [Z3 T-3 ~> m3 s-3]
956  type(tidal_mixing_cs), pointer :: CS !< The control structure for this module
957  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
958  intent(inout) :: Kd_lay !< The diapycnal diffusvity in layers [Z2 T-1 ~> m2 s-1].
959  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1), &
960  optional, intent(inout) :: Kd_int !< The diapycnal diffusvity at interfaces
961  !! [Z2 T-1 ~> m2 s-1].
962  real, intent(in) :: Kd_max !< The maximum increment for diapycnal
963  !! diffusivity due to TKE-based processes
964  !! [Z2 T-1 ~> m2 s-1].
965  !! Set this to a negative value to have no limit.
966 
967  ! local
968 
969  real, dimension(SZI_(G)) :: &
970  htot, & ! total thickness above or below a layer, or the
971  ! integrated thickness in the BBL [Z ~> m].
972  htot_wkb, & ! WKB scaled distance from top to bottom [Z ~> m].
973  tke_itidal_bot, & ! internal tide TKE at ocean bottom [Z3 T-3 ~> m3 s-3]
974  tke_niku_bot, & ! lee-wave TKE at ocean bottom [Z3 T-3 ~> m3 s-3]
975  tke_lowmode_bot, & ! internal tide TKE at ocean bottom lost from all remote low modes [Z3 T-3 ~> m3 s-3] (BDM)
976  inv_int, & ! inverse of TKE decay for int tide over the depth of the ocean [nondim]
977  inv_int_lee, & ! inverse of TKE decay for lee waves over the depth of the ocean [nondim]
978  inv_int_low, & ! inverse of TKE decay for low modes over the depth of the ocean [nondim] (BDM)
979  z0_polzin, & ! TKE decay scale in Polzin formulation [Z ~> m].
980  z0_polzin_scaled, & ! TKE decay scale in Polzin formulation [Z ~> m].
981  ! multiplied by N2_bot/N2_meanz to be coherent with the WKB scaled z
982  ! z*=int(N2/N2_bot) * N2_bot/N2_meanz = int(N2/N2_meanz)
983  ! z0_Polzin_scaled = z0_Polzin * N2_bot/N2_meanz
984  n2_meanz, & ! vertically averaged squared buoyancy frequency [T-2] for WKB scaling
985  tke_itidal_rem, & ! remaining internal tide TKE (from barotropic source) [Z3 T-3 ~> m3 s-3]
986  tke_niku_rem, & ! remaining lee-wave TKE [Z3 T-3 ~> m3 s-3]
987  tke_lowmode_rem, & ! remaining internal tide TKE (from propagating low mode source) [Z3 T-3 ~> m3 s-3] (BDM)
988  tke_frac_top, & ! fraction of bottom TKE that should appear at top of a layer [nondim]
989  tke_frac_top_lee, & ! fraction of bottom TKE that should appear at top of a layer [nondim]
990  tke_frac_top_lowmode, &
991  ! fraction of bottom TKE that should appear at top of a layer [nondim] (BDM)
992  z_from_bot, & ! distance from bottom [Z ~> m].
993  z_from_bot_wkb ! WKB scaled distance from bottom [Z ~> m].
994 
995  real :: I_rho0 ! 1 / RHO0 [m3 kg-1]
996  real :: Kd_add ! diffusivity to add in a layer [Z2 T-1 ~> m2 s-1].
997  real :: TKE_itide_lay ! internal tide TKE imparted to a layer (from barotropic) [Z3 T-3 ~> m3 s-3]
998  real :: TKE_Niku_lay ! lee-wave TKE imparted to a layer [Z3 T-3 ~> m3 s-3]
999  real :: TKE_lowmode_lay ! internal tide TKE imparted to a layer (from low mode) [Z3 T-3 ~> m3 s-3] (BDM)
1000  real :: frac_used ! fraction of TKE that can be used in a layer [nondim]
1001  real :: Izeta ! inverse of TKE decay scale [Z-1 ~> m-1].
1002  real :: Izeta_lee ! inverse of TKE decay scale for lee waves [Z-1 ~> m-1].
1003  real :: z0Ps_num ! The numerator of the unlimited z0_Polzin_scaled [Z T-3 ~> m s-3].
1004  real :: z0Ps_denom ! The denominator of the unlimited z0_Polzin_scaled [T-3 ~> s-3].
1005  real :: z0_psl ! temporary variable [Z ~> m].
1006  real :: TKE_lowmode_tot ! TKE from all low modes [kg Z3 m-3 T-3 ~> W m-2] (BDM)
1007 
1008  logical :: use_Polzin, use_Simmons
1009  character(len=160) :: mesg ! The text of an error message
1010  integer :: i, k, is, ie, nz
1011  integer :: a, fr, m
1012  type(tidal_mixing_diags), pointer :: dd => null()
1013 
1014  is = g%isc ; ie = g%iec ; nz = g%ke
1015  dd => cs%dd
1016 
1017  if (.not.(cs%Int_tide_dissipation .or. cs%Lee_wave_dissipation)) return
1018 
1019  do i=is,ie ; htot(i) = 0.0 ; inv_int(i) = 0.0 ; inv_int_lee(i) = 0.0 ; inv_int_low(i) = 0.0 ;enddo
1020  do k=1,nz ; do i=is,ie
1021  htot(i) = htot(i) + gv%H_to_Z*h(i,j,k)
1022  enddo ; enddo
1023 
1024  i_rho0 = 1.0/gv%Rho0
1025 
1026  use_polzin = ((cs%Int_tide_dissipation .and. (cs%int_tide_profile == polzin_09)) .or. &
1027  (cs%lee_wave_dissipation .and. (cs%lee_wave_profile == polzin_09)) .or. &
1028  (cs%Lowmode_itidal_dissipation .and. (cs%int_tide_profile == polzin_09)))
1029  use_simmons = ((cs%Int_tide_dissipation .and. (cs%int_tide_profile == stlaurent_02)) .or. &
1030  (cs%lee_wave_dissipation .and. (cs%lee_wave_profile == stlaurent_02)) .or. &
1031  (cs%Lowmode_itidal_dissipation .and. (cs%int_tide_profile == stlaurent_02)))
1032 
1033  ! Calculate parameters for vertical structure of dissipation
1034  ! Simmons:
1035  if ( use_simmons ) then
1036  izeta = 1.0 / max(cs%Int_tide_decay_scale, gv%H_subroundoff*gv%H_to_Z)
1037  izeta_lee = 1.0 / max(cs%Int_tide_decay_scale*cs%Decay_scale_factor_lee, &
1038  gv%H_subroundoff*gv%H_to_Z)
1039  do i=is,ie
1040  cs%Nb(i,j) = sqrt(n2_bot(i))
1041  if (associated(dd%N2_bot)) dd%N2_bot(i,j) = n2_bot(i)
1042  if ( cs%Int_tide_dissipation ) then
1043  if (izeta*htot(i) > 1.0e-14) then ! L'Hospital's version of Adcroft's reciprocal rule.
1044  inv_int(i) = 1.0 / (1.0 - exp(-izeta*htot(i)))
1045  endif
1046  endif
1047  if ( cs%Lee_wave_dissipation ) then
1048  if (izeta_lee*htot(i) > 1.0e-14) then ! L'Hospital's version of Adcroft's reciprocal rule.
1049  inv_int_lee(i) = 1.0 / (1.0 - exp(-izeta_lee*htot(i)))
1050  endif
1051  endif
1052  if ( cs%Lowmode_itidal_dissipation) then
1053  if (izeta*htot(i) > 1.0e-14) then ! L'Hospital's version of Adcroft's reciprocal rule.
1054  inv_int_low(i) = 1.0 / (1.0 - exp(-izeta*htot(i)))
1055  endif
1056  endif
1057  z_from_bot(i) = gv%H_to_Z*h(i,j,nz)
1058  enddo
1059  endif ! Simmons
1060 
1061  ! Polzin:
1062  if ( use_polzin ) then
1063  ! WKB scaling of the vertical coordinate
1064  do i=is,ie ; n2_meanz(i) = 0.0 ; enddo
1065  do k=1,nz ; do i=is,ie
1066  n2_meanz(i) = n2_meanz(i) + n2_lay(i,k) * gv%H_to_Z * h(i,j,k)
1067  enddo ; enddo
1068  do i=is,ie
1069  n2_meanz(i) = n2_meanz(i) / (htot(i) + gv%H_subroundoff*gv%H_to_Z)
1070  if (associated(dd%N2_meanz)) dd%N2_meanz(i,j) = n2_meanz(i)
1071  enddo
1072 
1073  ! WKB scaled z*(z=H) z* at the surface using the modified Polzin WKB scaling
1074  do i=is,ie ; htot_wkb(i) = htot(i) ; enddo
1075 ! do i=is,ie ; htot_WKB(i) = 0.0 ; enddo
1076 ! do k=1,nz ; do i=is,ie
1077 ! htot_WKB(i) = htot_WKB(i) + GV%H_to_Z*h(i,j,k) * N2_lay(i,k) / N2_meanz(i)
1078 ! enddo ; enddo
1079  ! htot_WKB(i) = htot(i) ! Nearly equivalent and simpler
1080 
1081  do i=is,ie
1082  cs%Nb(i,j) = sqrt(n2_bot(i))
1083  if (cs%answers_2018) then
1084  if ((cs%tideamp(i,j) > 0.0) .and. &
1085  (cs%kappa_itides**2 * cs%h2(i,j) * cs%Nb(i,j)**3 > 1.0e-14*us%T_to_s**3) ) then
1086  z0_polzin(i) = cs%Polzin_decay_scale_factor * cs%Nu_Polzin * &
1087  cs%Nbotref_Polzin**2 * cs%tideamp(i,j) / &
1088  ( cs%kappa_itides**2 * cs%h2(i,j) * cs%Nb(i,j)**3 )
1089  if (z0_polzin(i) < cs%Polzin_min_decay_scale) &
1090  z0_polzin(i) = cs%Polzin_min_decay_scale
1091  if (n2_meanz(i) > 1.0e-14*us%T_to_s**2 ) then
1092  z0_polzin_scaled(i) = z0_polzin(i)*cs%Nb(i,j)**2 / n2_meanz(i)
1093  else
1094  z0_polzin_scaled(i) = cs%Polzin_decay_scale_max_factor * htot(i)
1095  endif
1096  if (z0_polzin_scaled(i) > (cs%Polzin_decay_scale_max_factor * htot(i)) ) &
1097  z0_polzin_scaled(i) = cs%Polzin_decay_scale_max_factor * htot(i)
1098  else
1099  z0_polzin(i) = cs%Polzin_decay_scale_max_factor * htot(i)
1100  z0_polzin_scaled(i) = cs%Polzin_decay_scale_max_factor * htot(i)
1101  endif
1102  else
1103  z0ps_num = (cs%Polzin_decay_scale_factor * cs%Nu_Polzin * cs%Nbotref_Polzin**2) * cs%tideamp(i,j)
1104  z0ps_denom = ( cs%kappa_itides**2 * cs%h2(i,j) * cs%Nb(i,j) * n2_meanz(i) )
1105  if ((cs%tideamp(i,j) > 0.0) .and. &
1106  (z0ps_num < z0ps_denom * cs%Polzin_decay_scale_max_factor * htot(i))) then
1107  z0_polzin_scaled(i) = z0ps_num / z0ps_denom
1108 
1109  if (abs(n2_meanz(i) * z0_polzin_scaled(i)) < &
1110  cs%Nb(i,j)**2 * (cs%Polzin_decay_scale_max_factor * htot(i))) then
1111  z0_polzin(i) = z0_polzin_scaled(i) * (n2_meanz(i) / cs%Nb(i,j)**2)
1112  else
1113  z0_polzin(i) = cs%Polzin_decay_scale_max_factor * htot(i)
1114  endif
1115  else
1116  z0_polzin(i) = cs%Polzin_decay_scale_max_factor * htot(i)
1117  z0_polzin_scaled(i) = cs%Polzin_decay_scale_max_factor * htot(i)
1118  endif
1119  endif
1120 
1121  if (associated(dd%Polzin_decay_scale)) &
1122  dd%Polzin_decay_scale(i,j) = z0_polzin(i)
1123  if (associated(dd%Polzin_decay_scale_scaled)) &
1124  dd%Polzin_decay_scale_scaled(i,j) = z0_polzin_scaled(i)
1125  if (associated(dd%N2_bot)) dd%N2_bot(i,j) = cs%Nb(i,j)*cs%Nb(i,j)
1126 
1127  if (cs%answers_2018) then
1128  ! These expressions use dimensional constants to avoid NaN values.
1129  if ( cs%Int_tide_dissipation .and. (cs%int_tide_profile == polzin_09) ) then
1130  if (htot_wkb(i) > 1.0e-14*us%m_to_Z) &
1131  inv_int(i) = ( z0_polzin_scaled(i) / htot_wkb(i) ) + 1.0
1132  endif
1133  if ( cs%lee_wave_dissipation .and. (cs%lee_wave_profile == polzin_09) ) then
1134  if (htot_wkb(i) > 1.0e-14*us%m_to_Z) &
1135  inv_int_lee(i) = ( z0_polzin_scaled(i)*cs%Decay_scale_factor_lee / htot_wkb(i) ) + 1.0
1136  endif
1137  if ( cs%Lowmode_itidal_dissipation .and. (cs%int_tide_profile == polzin_09) ) then
1138  if (htot_wkb(i) > 1.0e-14*us%m_to_Z) &
1139  inv_int_low(i) = ( z0_polzin_scaled(i) / htot_wkb(i) ) + 1.0
1140  endif
1141  else
1142  ! These expressions give values of Inv_int < 10^14 using a variant of Adcroft's reciprocal rule.
1143  inv_int(i) = 0.0 ; inv_int_lee(i) = 0.0 ; inv_int_low(i) = 0.0
1144  if ( cs%Int_tide_dissipation .and. (cs%int_tide_profile == polzin_09) ) then
1145  if (z0_polzin_scaled(i) < 1.0e14 * htot_wkb(i)) &
1146  inv_int(i) = ( z0_polzin_scaled(i) / htot_wkb(i) ) + 1.0
1147  endif
1148  if ( cs%lee_wave_dissipation .and. (cs%lee_wave_profile == polzin_09) ) then
1149  if (z0_polzin_scaled(i) < 1.0e14 * htot_wkb(i)) &
1150  inv_int_lee(i) = ( z0_polzin_scaled(i)*cs%Decay_scale_factor_lee / htot_wkb(i) ) + 1.0
1151  endif
1152  if ( cs%Lowmode_itidal_dissipation .and. (cs%int_tide_profile == polzin_09) ) then
1153  if (z0_polzin_scaled(i) < 1.0e14 * htot_wkb(i)) &
1154  inv_int_low(i) = ( z0_polzin_scaled(i) / htot_wkb(i) ) + 1.0
1155  endif
1156  endif
1157 
1158  z_from_bot(i) = gv%H_to_Z*h(i,j,nz)
1159  ! Use the new formulation for WKB scaling. N2 is referenced to its vertical mean.
1160  if (cs%answers_2018) then
1161  if (n2_meanz(i) > 1.0e-14*us%T_to_s**2 ) then
1162  z_from_bot_wkb(i) = gv%H_to_Z*h(i,j,nz) * n2_lay(i,nz) / n2_meanz(i)
1163  else ; z_from_bot_wkb(i) = 0 ; endif
1164  else
1165  if (gv%H_to_Z*h(i,j,nz) * n2_lay(i,nz) < n2_meanz(i) * (1.0e14 * htot_wkb(i))) then
1166  z_from_bot_wkb(i) = gv%H_to_Z*h(i,j,nz) * n2_lay(i,nz) / n2_meanz(i)
1167  else ; z_from_bot_wkb(i) = 0 ; endif
1168  endif
1169  enddo
1170  endif ! Polzin
1171 
1172  ! Calculate/get dissipation values at bottom
1173  ! Both Polzin and Simmons:
1174  do i=is,ie
1175  ! Dissipation of locally trapped internal tide (non-propagating high modes)
1176  tke_itidal_bot(i) = min(cs%TKE_itidal(i,j)*cs%Nb(i,j), cs%TKE_itide_max)
1177  if (associated(dd%TKE_itidal_used)) &
1178  dd%TKE_itidal_used(i,j) = tke_itidal_bot(i)
1179  tke_itidal_bot(i) = (i_rho0 * cs%Mu_itides * cs%Gamma_itides) * tke_itidal_bot(i)
1180  ! Dissipation of locally trapped lee waves
1181  tke_niku_bot(i) = 0.0
1182  if (cs%Lee_wave_dissipation) then
1183  tke_niku_bot(i) = (i_rho0 * cs%Mu_itides * cs%Gamma_lee) * cs%TKE_Niku(i,j)
1184  endif
1185  ! Dissipation of propagating internal tide (baroclinic low modes; rays) (BDM)
1186  tke_lowmode_tot = 0.0
1187  tke_lowmode_bot(i) = 0.0
1188  if (cs%Lowmode_itidal_dissipation) then
1189  ! get loss rate due to wave drag on low modes (already multiplied by q)
1190 
1191  ! TODO: uncomment the following call and fix it
1192  !call get_lowmode_loss(i,j,G,CS%int_tide_CSp,"WaveDrag",TKE_lowmode_tot)
1193  write (mesg,*) "========", __file__, __line__
1194  call mom_error(fatal,trim(mesg)//": this block not supported yet. (aa)")
1195 
1196  tke_lowmode_bot(i) = cs%Mu_itides * i_rho0 * tke_lowmode_tot
1197  endif
1198  ! Vertical energy flux at bottom
1199  tke_itidal_rem(i) = inv_int(i) * tke_itidal_bot(i)
1200  tke_niku_rem(i) = inv_int_lee(i) * tke_niku_bot(i)
1201  tke_lowmode_rem(i) = inv_int_low(i) * tke_lowmode_bot(i)
1202 
1203  if (associated(dd%Fl_itidal)) dd%Fl_itidal(i,j,nz) = tke_itidal_rem(i) !why is this here? BDM
1204  enddo
1205 
1206  ! Estimate the work that would be done by mixing in each layer.
1207  ! Simmons:
1208  if ( use_simmons ) then
1209  do k=nz-1,2,-1 ; do i=is,ie
1210  if (max_tke(i,k) <= 0.0) cycle
1211  z_from_bot(i) = z_from_bot(i) + gv%H_to_Z*h(i,j,k)
1212 
1213  ! Fraction of bottom flux predicted to reach top of this layer
1214  tke_frac_top(i) = inv_int(i) * exp(-izeta * z_from_bot(i))
1215  tke_frac_top_lee(i) = inv_int_lee(i) * exp(-izeta_lee * z_from_bot(i))
1216  tke_frac_top_lowmode(i) = inv_int_low(i) * exp(-izeta * z_from_bot(i))
1217 
1218  ! Actual influx at bottom of layer minus predicted outflux at top of layer to give
1219  ! predicted power expended
1220  tke_itide_lay = tke_itidal_rem(i) - tke_itidal_bot(i) * tke_frac_top(i)
1221  tke_niku_lay = tke_niku_rem(i) - tke_niku_bot(i) * tke_frac_top_lee(i)
1222  tke_lowmode_lay = tke_lowmode_rem(i) - tke_lowmode_bot(i)* tke_frac_top_lowmode(i)
1223 
1224  ! Actual power expended may be less than predicted if stratification is weak; adjust
1225  if (tke_itide_lay + tke_niku_lay + tke_lowmode_lay > (max_tke(i,k))) then
1226  frac_used = (max_tke(i,k)) / (tke_itide_lay + tke_niku_lay + tke_lowmode_lay)
1227  tke_itide_lay = frac_used * tke_itide_lay
1228  tke_niku_lay = frac_used * tke_niku_lay
1229  tke_lowmode_lay = frac_used * tke_lowmode_lay
1230  endif
1231 
1232  ! Calculate vertical flux available to bottom of layer above
1233  tke_itidal_rem(i) = tke_itidal_rem(i) - tke_itide_lay
1234  tke_niku_rem(i) = tke_niku_rem(i) - tke_niku_lay
1235  tke_lowmode_rem(i) = tke_lowmode_rem(i) - tke_lowmode_lay
1236 
1237  ! Convert power to diffusivity
1238  kd_add = tke_to_kd(i,k) * (tke_itide_lay + tke_niku_lay + tke_lowmode_lay)
1239 
1240  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1241  kd_lay(i,j,k) = kd_lay(i,j,k) + kd_add
1242 
1243  if (present(kd_int)) then
1244  kd_int(i,j,k) = kd_int(i,j,k) + 0.5 * kd_add
1245  kd_int(i,j,k+1) = kd_int(i,j,k+1) + 0.5 * kd_add
1246  endif
1247 
1248  ! diagnostics
1249  if (associated(dd%Kd_itidal)) then
1250  ! If at layers, dd%Kd_itidal is just TKE_to_Kd(i,k) * TKE_itide_lay
1251  ! The following sets the interface diagnostics.
1252  kd_add = tke_to_kd(i,k) * tke_itide_lay
1253  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1254  if (k>1) dd%Kd_itidal(i,j,k) = dd%Kd_itidal(i,j,k) + 0.5*kd_add
1255  if (k<nz) dd%Kd_itidal(i,j,k+1) = dd%Kd_itidal(i,j,k+1) + 0.5*kd_add
1256  endif
1257  if (associated(dd%Kd_Itidal_work)) &
1258  dd%Kd_itidal_work(i,j,k) = gv%Rho0 * tke_itide_lay
1259  if (associated(dd%Fl_itidal)) dd%Fl_itidal(i,j,k) = tke_itidal_rem(i)
1260 
1261  if (associated(dd%Kd_Niku)) then
1262  ! If at layers, dd%Kd_Niku(i,j,K) is just TKE_to_Kd(i,k) * TKE_Niku_lay
1263  ! The following sets the interface diagnostics.
1264  kd_add = tke_to_kd(i,k) * tke_niku_lay
1265  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1266  if (k>1) dd%Kd_Niku(i,j,k) = dd%Kd_Niku(i,j,k) + 0.5*kd_add
1267  if (k<nz) dd%Kd_Niku(i,j,k+1) = dd%Kd_Niku(i,j,k+1) + 0.5*kd_add
1268  endif
1269 ! if (associated(dd%Kd_Niku)) dd%Kd_Niku(i,j,K) = TKE_to_Kd(i,k) * TKE_Niku_lay
1270  if (associated(dd%Kd_Niku_work)) &
1271  dd%Kd_Niku_work(i,j,k) = gv%Rho0 * tke_niku_lay
1272 
1273  if (associated(dd%Kd_lowmode)) then
1274  ! If at layers, dd%Kd_lowmode is just TKE_to_Kd(i,k) * TKE_lowmode_lay
1275  ! The following sets the interface diagnostics.
1276  kd_add = tke_to_kd(i,k) * tke_lowmode_lay
1277  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1278  if (k>1) dd%Kd_lowmode(i,j,k) = dd%Kd_lowmode(i,j,k) + 0.5*kd_add
1279  if (k<nz) dd%Kd_lowmode(i,j,k+1) = dd%Kd_lowmode(i,j,k+1) + 0.5*kd_add
1280  endif
1281  if (associated(dd%Kd_lowmode_work)) &
1282  dd%Kd_lowmode_work(i,j,k) = gv%Rho0 * tke_lowmode_lay
1283  if (associated(dd%Fl_lowmode)) dd%Fl_lowmode(i,j,k) = tke_lowmode_rem(i)
1284 
1285  enddo ; enddo
1286  endif ! Simmons
1287 
1288  ! Polzin:
1289  if ( use_polzin ) then
1290  do k=nz-1,2,-1 ; do i=is,ie
1291  if (max_tke(i,k) <= 0.0) cycle
1292  z_from_bot(i) = z_from_bot(i) + gv%H_to_Z*h(i,j,k)
1293  if (n2_meanz(i) > 1.0e-14*us%T_to_s**2 ) then
1294  z_from_bot_wkb(i) = z_from_bot_wkb(i) &
1295  + gv%H_to_Z * h(i,j,k) * n2_lay(i,k) / n2_meanz(i)
1296  else ; z_from_bot_wkb(i) = 0 ; endif
1297 
1298  ! Fraction of bottom flux predicted to reach top of this layer
1299  tke_frac_top(i) = ( inv_int(i) * z0_polzin_scaled(i) ) / &
1300  ( z0_polzin_scaled(i) + z_from_bot_wkb(i) )
1301  z0_psl = z0_polzin_scaled(i)*cs%Decay_scale_factor_lee
1302  tke_frac_top_lee(i) = (inv_int_lee(i) * z0_psl) / (z0_psl + z_from_bot_wkb(i))
1303  tke_frac_top_lowmode(i) = ( inv_int_low(i) * z0_polzin_scaled(i) ) / &
1304  ( z0_polzin_scaled(i) + z_from_bot_wkb(i) )
1305 
1306  ! Actual influx at bottom of layer minus predicted outflux at top of layer to give
1307  ! predicted power expended
1308  tke_itide_lay = tke_itidal_rem(i) - tke_itidal_bot(i) *tke_frac_top(i)
1309  tke_niku_lay = tke_niku_rem(i) - tke_niku_bot(i) * tke_frac_top_lee(i)
1310  tke_lowmode_lay = tke_lowmode_rem(i) - tke_lowmode_bot(i)*tke_frac_top_lowmode(i)
1311 
1312  ! Actual power expended may be less than predicted if stratification is weak; adjust
1313  if (tke_itide_lay + tke_niku_lay + tke_lowmode_lay > (max_tke(i,k))) then
1314  frac_used = (max_tke(i,k)) / (tke_itide_lay + tke_niku_lay + tke_lowmode_lay)
1315  tke_itide_lay = frac_used * tke_itide_lay
1316  tke_niku_lay = frac_used * tke_niku_lay
1317  tke_lowmode_lay = frac_used * tke_lowmode_lay
1318  endif
1319 
1320  ! Calculate vertical flux available to bottom of layer above
1321  tke_itidal_rem(i) = tke_itidal_rem(i) - tke_itide_lay
1322  tke_niku_rem(i) = tke_niku_rem(i) - tke_niku_lay
1323  tke_lowmode_rem(i) = tke_lowmode_rem(i) - tke_lowmode_lay
1324 
1325  ! Convert power to diffusivity
1326  kd_add = tke_to_kd(i,k) * (tke_itide_lay + tke_niku_lay + tke_lowmode_lay)
1327 
1328  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1329  kd_lay(i,j,k) = kd_lay(i,j,k) + kd_add
1330 
1331  if (present(kd_int)) then
1332  kd_int(i,j,k) = kd_int(i,j,k) + 0.5 * kd_add
1333  kd_int(i,j,k+1) = kd_int(i,j,k+1) + 0.5 * kd_add
1334  endif
1335 
1336  ! diagnostics
1337  if (associated(dd%Kd_itidal)) then
1338  ! If at layers, this is just dd%Kd_itidal(i,j,K) = TKE_to_Kd(i,k) * TKE_itide_lay
1339  ! The following sets the interface diagnostics.
1340  kd_add = tke_to_kd(i,k) * tke_itide_lay
1341  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1342  if (k>1) dd%Kd_itidal(i,j,k) = dd%Kd_itidal(i,j,k) + 0.5*kd_add
1343  if (k<nz) dd%Kd_itidal(i,j,k+1) = dd%Kd_itidal(i,j,k+1) + 0.5*kd_add
1344  endif
1345  if (associated(dd%Kd_Itidal_work)) &
1346  dd%Kd_itidal_work(i,j,k) = gv%Rho0 * tke_itide_lay
1347  if (associated(dd%Fl_itidal)) dd%Fl_itidal(i,j,k) = tke_itidal_rem(i)
1348 
1349  if (associated(dd%Kd_Niku)) then
1350  ! If at layers, this is just dd%Kd_Niku(i,j,K) = TKE_to_Kd(i,k) * TKE_Niku_lay
1351  ! The following sets the interface diagnostics.
1352  kd_add = tke_to_kd(i,k) * tke_niku_lay
1353  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1354  if (k>1) dd%Kd_Niku(i,j,k) = dd%Kd_Niku(i,j,k) + 0.5*kd_add
1355  if (k<nz) dd%Kd_Niku(i,j,k+1) = dd%Kd_Niku(i,j,k+1) + 0.5*kd_add
1356  endif
1357  ! if (associated(dd%Kd_Niku)) dd%Kd_Niku(i,j,K) = TKE_to_Kd(i,k) * TKE_Niku_lay
1358  if (associated(dd%Kd_Niku_work)) dd%Kd_Niku_work(i,j,k) = gv%Rho0 * tke_niku_lay
1359 
1360  if (associated(dd%Kd_lowmode)) then
1361  ! If at layers, dd%Kd_lowmode is just TKE_to_Kd(i,k) * TKE_lowmode_lay
1362  ! The following sets the interface diagnostics.
1363  kd_add = tke_to_kd(i,k) * tke_lowmode_lay
1364  if (kd_max >= 0.0) kd_add = min(kd_add, kd_max)
1365  if (k>1) dd%Kd_lowmode(i,j,k) = dd%Kd_lowmode(i,j,k) + 0.5*kd_add
1366  if (k<nz) dd%Kd_lowmode(i,j,k+1) = dd%Kd_lowmode(i,j,k+1) + 0.5*kd_add
1367  endif
1368  if (associated(dd%Kd_lowmode_work)) &
1369  dd%Kd_lowmode_work(i,j,k) = gv%Rho0 * tke_lowmode_lay
1370  if (associated(dd%Fl_lowmode)) dd%Fl_lowmode(i,j,k) = tke_lowmode_rem(i)
1371 
1372  enddo ; enddo
1373  endif ! Polzin
1374 
1375 end subroutine add_int_tide_diffusivity
1376 
1377 !> Sets up diagnostics arrays for tidal mixing.
1378 subroutine setup_tidal_diagnostics(G,CS)
1379  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
1380  type(tidal_mixing_cs), pointer :: cs !< The control structure for this module
1381 
1382  ! local
1383  integer :: isd, ied, jsd, jed, nz
1384  type(tidal_mixing_diags), pointer :: dd => null()
1385 
1386  isd = g%isd; ied = g%ied; jsd = g%jsd; jed = g%jed; nz = g%ke
1387  dd => cs%dd
1388 
1389  if ((cs%id_Kd_itidal > 0) .or. (cs%id_Kd_Itidal_work > 0)) then
1390  allocate(dd%Kd_itidal(isd:ied,jsd:jed,nz+1)) ; dd%Kd_itidal(:,:,:) = 0.0
1391  endif
1392  if ((cs%id_Kd_lowmode > 0) .or. (cs%id_Kd_lowmode_work > 0)) then
1393  allocate(dd%Kd_lowmode(isd:ied,jsd:jed,nz+1)) ; dd%Kd_lowmode(:,:,:) = 0.0
1394  endif
1395  if ( (cs%id_Fl_itidal > 0) ) then
1396  allocate(dd%Fl_itidal(isd:ied,jsd:jed,nz+1)) ; dd%Fl_itidal(:,:,:) = 0.0
1397  endif
1398  if ( (cs%id_Fl_lowmode > 0) ) then
1399  allocate(dd%Fl_lowmode(isd:ied,jsd:jed,nz+1)) ; dd%Fl_lowmode(:,:,:) = 0.0
1400  endif
1401  if ( (cs%id_Polzin_decay_scale > 0) ) then
1402  allocate(dd%Polzin_decay_scale(isd:ied,jsd:jed))
1403  dd%Polzin_decay_scale(:,:) = 0.0
1404  endif
1405  if ( (cs%id_N2_bot > 0) ) then
1406  allocate(dd%N2_bot(isd:ied,jsd:jed)) ; dd%N2_bot(:,:) = 0.0
1407  endif
1408  if ( (cs%id_N2_meanz > 0) ) then
1409  allocate(dd%N2_meanz(isd:ied,jsd:jed)) ; dd%N2_meanz(:,:) = 0.0
1410  endif
1411  if ( (cs%id_Polzin_decay_scale_scaled > 0) ) then
1412  allocate(dd%Polzin_decay_scale_scaled(isd:ied,jsd:jed))
1413  dd%Polzin_decay_scale_scaled(:,:) = 0.0
1414  endif
1415  if ((cs%id_Kd_Niku > 0) .or. (cs%id_Kd_Niku_work > 0)) then
1416  allocate(dd%Kd_Niku(isd:ied,jsd:jed,nz+1)) ; dd%Kd_Niku(:,:,:) = 0.0
1417  endif
1418  if (cs%id_Kd_Niku_work > 0) then
1419  allocate(dd%Kd_Niku_work(isd:ied,jsd:jed,nz)) ; dd%Kd_Niku_work(:,:,:) = 0.0
1420  endif
1421  if (cs%id_Kd_Itidal_work > 0) then
1422  allocate(dd%Kd_Itidal_work(isd:ied,jsd:jed,nz))
1423  dd%Kd_Itidal_work(:,:,:) = 0.0
1424  endif
1425  if (cs%id_Kd_Lowmode_Work > 0) then
1426  allocate(dd%Kd_Lowmode_Work(isd:ied,jsd:jed,nz))
1427  dd%Kd_Lowmode_Work(:,:,:) = 0.0
1428  endif
1429  if (cs%id_TKE_itidal > 0) then
1430  allocate(dd%TKE_Itidal_used(isd:ied,jsd:jed)) ; dd%TKE_Itidal_used(:,:) = 0.
1431  endif
1432  ! additional diags for CVMix
1433  if (cs%id_N2_int > 0) then
1434  allocate(dd%N2_int(isd:ied,jsd:jed,nz+1)) ; dd%N2_int(:,:,:) = 0.0
1435  endif
1436  if (cs%id_Simmons_coeff > 0) then
1437  if (cs%CVMix_tidal_scheme .ne. simmons) then
1438  call mom_error(fatal, "setup_tidal_diagnostics: Simmons_coeff diagnostics is available "//&
1439  "only when CVMix_tidal_scheme is Simmons")
1440  endif
1441  allocate(dd%Simmons_coeff_2d(isd:ied,jsd:jed)) ; dd%Simmons_coeff_2d(:,:) = 0.0
1442  endif
1443  if (cs%id_vert_dep > 0) then
1444  allocate(dd%vert_dep_3d(isd:ied,jsd:jed,nz+1)) ; dd%vert_dep_3d(:,:,:) = 0.0
1445  endif
1446  if (cs%id_Schmittner_coeff > 0) then
1447  if (cs%CVMix_tidal_scheme .ne. schmittner) then
1448  call mom_error(fatal, "setup_tidal_diagnostics: Schmittner_coeff diagnostics is available "//&
1449  "only when CVMix_tidal_scheme is Schmittner.")
1450  endif
1451  allocate(dd%Schmittner_coeff_3d(isd:ied,jsd:jed,nz)) ; dd%Schmittner_coeff_3d(:,:,:) = 0.0
1452  endif
1453  if (cs%id_tidal_qe_md > 0) then
1454  if (cs%CVMix_tidal_scheme .ne. schmittner) then
1455  call mom_error(fatal, "setup_tidal_diagnostics: tidal_qe_md diagnostics is available "//&
1456  "only when CVMix_tidal_scheme is Schmittner.")
1457  endif
1458  allocate(dd%tidal_qe_md(isd:ied,jsd:jed,nz)) ; dd%tidal_qe_md(:,:,:) = 0.0
1459  endif
1460 end subroutine setup_tidal_diagnostics
1461 
1462 !> This subroutine offers up diagnostics of the tidal mixing.
1463 subroutine post_tidal_diagnostics(G, GV, h ,CS)
1464  type(ocean_grid_type), intent(in) :: g !< The ocean's grid structure
1465  type(verticalgrid_type), intent(in) :: gv !< The ocean's vertical grid structure.
1466  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), &
1467  intent(in) :: h !< Layer thicknesses [H ~> m or kg m-2].
1468  type(tidal_mixing_cs), pointer :: cs !< The control structure for this module
1469 
1470  ! local
1471  type(tidal_mixing_diags), pointer :: dd => null()
1472 
1473  dd => cs%dd
1474 
1475  if (cs%Int_tide_dissipation .or. cs%Lee_wave_dissipation .or. cs%Lowmode_itidal_dissipation) then
1476  if (cs%id_TKE_itidal > 0) call post_data(cs%id_TKE_itidal, dd%TKE_itidal_used, cs%diag)
1477  if (cs%id_TKE_leewave > 0) call post_data(cs%id_TKE_leewave, cs%TKE_Niku, cs%diag)
1478  if (cs%id_Nb > 0) call post_data(cs%id_Nb, cs%Nb, cs%diag)
1479  if (cs%id_N2_bot > 0) call post_data(cs%id_N2_bot, dd%N2_bot, cs%diag)
1480  if (cs%id_N2_meanz > 0) call post_data(cs%id_N2_meanz,dd%N2_meanz,cs%diag)
1481 
1482  if (cs%id_Fl_itidal > 0) call post_data(cs%id_Fl_itidal, dd%Fl_itidal, cs%diag)
1483  if (cs%id_Kd_itidal > 0) call post_data(cs%id_Kd_itidal, dd%Kd_itidal, cs%diag)
1484  if (cs%id_Kd_Niku > 0) call post_data(cs%id_Kd_Niku, dd%Kd_Niku, cs%diag)
1485  if (cs%id_Kd_lowmode> 0) call post_data(cs%id_Kd_lowmode, dd%Kd_lowmode, cs%diag)
1486  if (cs%id_Fl_lowmode> 0) call post_data(cs%id_Fl_lowmode, dd%Fl_lowmode, cs%diag)
1487 
1488  if (cs%id_N2_int> 0) call post_data(cs%id_N2_int, dd%N2_int, cs%diag)
1489  if (cs%id_vert_dep> 0) call post_data(cs%id_vert_dep, dd%vert_dep_3d, cs%diag)
1490  if (cs%id_Simmons_coeff> 0) call post_data(cs%id_Simmons_coeff, dd%Simmons_coeff_2d, cs%diag)
1491  if (cs%id_Schmittner_coeff> 0) call post_data(cs%id_Schmittner_coeff, dd%Schmittner_coeff_3d, cs%diag)
1492  if (cs%id_tidal_qe_md> 0) call post_data(cs%id_tidal_qe_md, dd%tidal_qe_md, cs%diag)
1493 
1494  if (cs%id_Kd_Itidal_Work > 0) &
1495  call post_data(cs%id_Kd_Itidal_Work, dd%Kd_Itidal_Work, cs%diag)
1496  if (cs%id_Kd_Niku_Work > 0) call post_data(cs%id_Kd_Niku_Work, dd%Kd_Niku_Work, cs%diag)
1497  if (cs%id_Kd_Lowmode_Work > 0) &
1498  call post_data(cs%id_Kd_Lowmode_Work, dd%Kd_Lowmode_Work, cs%diag)
1499 
1500  if (cs%id_Polzin_decay_scale > 0 ) &
1501  call post_data(cs%id_Polzin_decay_scale, dd%Polzin_decay_scale, cs%diag)
1502  if (cs%id_Polzin_decay_scale_scaled > 0 ) &
1503  call post_data(cs%id_Polzin_decay_scale_scaled, dd%Polzin_decay_scale_scaled, cs%diag)
1504  endif
1505 
1506  if (associated(dd%Kd_itidal)) deallocate(dd%Kd_itidal)
1507  if (associated(dd%Kd_lowmode)) deallocate(dd%Kd_lowmode)
1508  if (associated(dd%Fl_itidal)) deallocate(dd%Fl_itidal)
1509  if (associated(dd%Fl_lowmode)) deallocate(dd%Fl_lowmode)
1510  if (associated(dd%Polzin_decay_scale)) deallocate(dd%Polzin_decay_scale)
1511  if (associated(dd%Polzin_decay_scale_scaled)) deallocate(dd%Polzin_decay_scale_scaled)
1512  if (associated(dd%N2_bot)) deallocate(dd%N2_bot)
1513  if (associated(dd%N2_meanz)) deallocate(dd%N2_meanz)
1514  if (associated(dd%Kd_Niku)) deallocate(dd%Kd_Niku)
1515  if (associated(dd%Kd_Niku_work)) deallocate(dd%Kd_Niku_work)
1516  if (associated(dd%Kd_Itidal_Work)) deallocate(dd%Kd_Itidal_Work)
1517  if (associated(dd%Kd_Lowmode_Work)) deallocate(dd%Kd_Lowmode_Work)
1518  if (associated(dd%TKE_itidal_used)) deallocate(dd%TKE_itidal_used)
1519  if (associated(dd%N2_int)) deallocate(dd%N2_int)
1520  if (associated(dd%vert_dep_3d)) deallocate(dd%vert_dep_3d)
1521  if (associated(dd%Simmons_coeff_2d)) deallocate(dd%Simmons_coeff_2d)
1522  if (associated(dd%Schmittner_coeff_3d)) deallocate(dd%Schmittner_coeff_3d)
1523  if (associated(dd%tidal_qe_md)) deallocate(dd%tidal_qe_md)
1524 
1525 end subroutine post_tidal_diagnostics
1526 
1527 ! TODO: move this subroutine to MOM_internal_tide_input module (?)
1528 !> This subroutine read tidal energy inputs from a file.
1529 subroutine read_tidal_energy(G, US, tidal_energy_type, tidal_energy_file, CS)
1530  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1531  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
1532  character(len=20), intent(in) :: tidal_energy_type !< The type of tidal energy inputs to read
1533  character(len=200), intent(in) :: tidal_energy_file !< The file from which to read tidalinputs
1534  type(tidal_mixing_cs), pointer :: CS !< The control structure for this module
1535  ! local
1536  integer :: i, j, isd, ied, jsd, jed, nz
1537  real, allocatable, dimension(:,:) :: tidal_energy_flux_2d ! input tidal energy flux at T-grid points [W m-2]
1538 
1539  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed ; nz = g%ke
1540 
1541  select case (uppercase(tidal_energy_type(1:4)))
1542  case ('JAYN') ! Jayne 2009
1543  if (.not. allocated(cs%tidal_qe_2d)) allocate(cs%tidal_qe_2d(isd:ied,jsd:jed))
1544  allocate(tidal_energy_flux_2d(isd:ied,jsd:jed))
1545  call mom_read_data(tidal_energy_file,'wave_dissipation',tidal_energy_flux_2d, g%domain)
1546  do j=g%jsc,g%jec ; do i=g%isc,g%iec
1547  cs%tidal_qe_2d(i,j) = cs%Gamma_itides * tidal_energy_flux_2d(i,j)
1548  enddo ; enddo
1549  deallocate(tidal_energy_flux_2d)
1550  case ('ER03') ! Egbert & Ray 2003
1551  call read_tidal_constituents(g, us, tidal_energy_file, cs)
1552  case default
1553  call mom_error(fatal, "read_tidal_energy: Unknown tidal energy file type.")
1554  end select
1555 
1556 end subroutine read_tidal_energy
1557 
1558 !> This subroutine reads tidal input energy from a file by constituent.
1559 subroutine read_tidal_constituents(G, US, tidal_energy_file, CS)
1560  type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
1561  type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
1562  character(len=200), intent(in) :: tidal_energy_file !< The file from which to read tidal energy inputs
1563  type(tidal_mixing_cs), pointer :: CS !< The control structure for this module
1564 
1565  ! local variables
1566  real, parameter :: C1_3 = 1.0/3.0
1567  real, dimension(SZI_(G),SZJ_(G)) :: &
1568  tidal_qk1, & ! qk1 coefficient used in Schmittner & Egbert
1569  tidal_qo1 ! qo1 coefficient used in Schmittner & Egbert
1570  real, allocatable, dimension(:) :: &
1571  z_t, & ! depth from surface to midpoint of input layer [Z]
1572  z_w ! depth from surface to top of input layer [Z]
1573  real, allocatable, dimension(:,:,:) :: &
1574  tc_m2, & ! input lunar semidiurnal tidal energy flux [W/m^2]
1575  tc_s2, & ! input solar semidiurnal tidal energy flux [W/m^2]
1576  tc_k1, & ! input lunar diurnal tidal energy flux [W/m^2]
1577  tc_o1 ! input lunar diurnal tidal energy flux [W/m^2]
1578  integer, dimension(4) :: nz_in
1579  integer :: k, is, ie, js, je, isd, ied, jsd, jed, i, j
1580 
1581  is = g%isc ; ie = g%iec ; js = g%jsc ; je = g%jec
1582  isd = g%isd ; ied = g%ied ; jsd = g%jsd ; jed = g%jed
1583 
1584  ! get number of input levels:
1585  call field_size(tidal_energy_file, 'z_t', nz_in)
1586 
1587  ! allocate local variables
1588  allocate(z_t(nz_in(1)), z_w(nz_in(1)) )
1589  allocate(tc_m2(isd:ied,jsd:jed,nz_in(1)), &
1590  tc_s2(isd:ied,jsd:jed,nz_in(1)), &
1591  tc_k1(isd:ied,jsd:jed,nz_in(1)), &
1592  tc_o1(isd:ied,jsd:jed,nz_in(1)) )
1593 
1594  ! allocate CS variables associated with 3d tidal energy dissipation
1595  if (.not. allocated(cs%tidal_qe_3d_in)) allocate(cs%tidal_qe_3d_in(isd:ied,jsd:jed,nz_in(1)))
1596  if (.not. allocated(cs%h_src)) allocate(cs%h_src(nz_in(1)))
1597 
1598  ! read in tidal constituents
1599  call mom_read_data(tidal_energy_file, 'M2', tc_m2, g%domain)
1600  call mom_read_data(tidal_energy_file, 'S2', tc_s2, g%domain)
1601  call mom_read_data(tidal_energy_file, 'K1', tc_k1, g%domain)
1602  call mom_read_data(tidal_energy_file, 'O1', tc_o1, g%domain)
1603  ! Note the hard-coded assumption that z_t and z_w in the file are in centimeters.
1604  call mom_read_data(tidal_energy_file, 'z_t', z_t, scale=100.0*us%m_to_Z)
1605  call mom_read_data(tidal_energy_file, 'z_w', z_w, scale=100.0*us%m_to_Z)
1606 
1607  do j=js,je ; do i=is,ie
1608  if (abs(g%geoLatT(i,j)) < 30.0) then
1609  tidal_qk1(i,j) = c1_3
1610  tidal_qo1(i,j) = c1_3
1611  else
1612  tidal_qk1(i,j) = 1.0
1613  tidal_qo1(i,j) = 1.0
1614  endif
1615  enddo ; enddo
1616 
1617  cs%tidal_qe_3d_in(:,:,:) = 0.0
1618  do k=1,nz_in(1)
1619  ! Store the input cell thickness in m for use with CVmix.
1620  cs%h_src(k) = us%Z_to_m*(z_t(k)-z_w(k))*2.0
1621  ! form tidal_qe_3d_in from weighted tidal constituents
1622  do j=js,je ; do i=is,ie
1623  if ((z_t(k) <= g%bathyT(i,j)) .and. (z_w(k) > cs%tidal_diss_lim_tc)) &
1624  cs%tidal_qe_3d_in(i,j,k) = c1_3*tc_m2(i,j,k) + c1_3*tc_s2(i,j,k) + &
1625  tidal_qk1(i,j)*tc_k1(i,j,k) + tidal_qo1(i,j)*tc_o1(i,j,k)
1626  enddo ; enddo
1627  enddo
1628 
1629  !open(unit=1905,file="out_1905.txt",access="APPEND")
1630  !do j=G%jsd,G%jed
1631  ! do i=isd,ied
1632  ! if ( i+G%idg_offset .eq. 90 .and. j+G%jdg_offset .eq. 126) then
1633  ! write(1905,*) "-------------------------------------------"
1634  ! do k=50,nz_in(1)
1635  ! write(1905,*) i,j,k
1636  ! write(1905,*) CS%tidal_qe_3d_in(i,j,k), tc_m2(i,j,k)
1637  ! write(1905,*) z_t(k), G%bathyT(i,j), z_w(k),CS%tidal_diss_lim_tc
1638  ! end do
1639  ! endif
1640  ! enddo
1641  !enddo
1642  !close(1905)
1643 
1644  ! test if qE is positive
1645  if (any(cs%tidal_qe_3d_in<0.0)) then
1646  call mom_error(fatal, "read_tidal_constituents: Negative tidal_qe_3d_in terms.")
1647  endif
1648 
1649  !! collapse 3D q*E to 2D q*E
1650  !CS%tidal_qe_2d(:,:) = 0.0
1651  !do k=1,nz_in(1) ; do j=js,je ; do i=is,ie
1652  ! if (z_t(k) <= G%bathyT(i,j)) &
1653  ! CS%tidal_qe_2d(i,j) = CS%tidal_qe_2d(i,j) + CS%tidal_qe_3d_in(i,j,k)
1654  !enddo ; enddo ; enddo
1655 
1656  ! initialize input remapping:
1657  call initialize_remapping(cs%remap_cs, remapping_scheme="PLM", &
1658  boundary_extrapolation=.false., check_remapping=cs%debug)
1659 
1660  deallocate(tc_m2)
1661  deallocate(tc_s2)
1662  deallocate(tc_k1)
1663  deallocate(tc_o1)
1664  deallocate(z_t)
1665  deallocate(z_w)
1666 
1667 end subroutine read_tidal_constituents
1668 
1669 !> Clear pointers and deallocate memory
1670 subroutine tidal_mixing_end(CS)
1671  type(tidal_mixing_cs), pointer :: cs !< This module's control structure, which
1672  !! will be deallocated in this routine.
1673 
1674  if (.not.associated(cs)) return
1675 
1676  !TODO deallocate all the dynamically allocated members here ...
1677  if (allocated(cs%tidal_qe_2d)) deallocate(cs%tidal_qe_2d)
1678  if (allocated(cs%tidal_qe_3d_in)) deallocate(cs%tidal_qe_3d_in)
1679  if (allocated(cs%h_src)) deallocate(cs%h_src)
1680  deallocate(cs%dd)
1681  deallocate(cs)
1682 
1683 end subroutine tidal_mixing_end
1684 
1685 end module mom_tidal_mixing
mom_verticalgrid
Provides a transparent vertical ocean grid type and supporting routines.
Definition: MOM_verticalGrid.F90:2
mom_file_parser::log_version
An overloaded interface to log version information about modules.
Definition: MOM_file_parser.F90:109
mom_diag_mediator
The subroutines here provide convenient wrappers to the fms diag_manager interfaces with additional d...
Definition: MOM_diag_mediator.F90:3
mom_variables::thermo_var_ptrs
Pointers to an assortment of thermodynamic fields that may be available, including potential temperat...
Definition: MOM_variables.F90:82
mom_string_functions
Handy functions for manipulating strings.
Definition: MOM_string_functions.F90:2
mom_eos
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
mom_remapping::remapping_cs
Container for remapping parameters.
Definition: MOM_remapping.F90:22
mom_file_parser::param_file_type
A structure that can be parsed to read and document run-time parameters.
Definition: MOM_file_parser.F90:54
mom_file_parser::get_param
An overloaded interface to read and log the values of various types of parameters.
Definition: MOM_file_parser.F90:102
mom_io
This module contains I/O framework code.
Definition: MOM_io.F90:2
mom_unit_scaling::unit_scale_type
Describes various unit conversion factors.
Definition: MOM_unit_scaling.F90:14
mom_remapping
Provides column-wise vertical remapping functions.
Definition: MOM_remapping.F90:2
mom_diag_mediator::post_data
Make a diagnostic available for averaging or output.
Definition: MOM_diag_mediator.F90:70
mom_verticalgrid::verticalgrid_type
Describes the vertical ocean grid, including unit conversion factors.
Definition: MOM_verticalGrid.F90:24
mom_variables
Provides transparent structures with groups of MOM6 variables and supporting routines.
Definition: MOM_variables.F90:2
mom_tidal_mixing
Interface to vertical tidal mixing schemes including CVMix tidal mixing.
Definition: MOM_tidal_mixing.F90:2
mom_io::mom_read_data
Read a data field from a file.
Definition: MOM_io.F90:74
mom_file_parser
The MOM6 facility to parse input files for runtime parameters.
Definition: MOM_file_parser.F90:2
mom_grid
Provides the ocean grid type.
Definition: MOM_grid.F90:2
mom_unit_scaling
Provides a transparent unit rescaling type to facilitate dimensional consistency testing.
Definition: MOM_unit_scaling.F90:2
mom_debugging
Provides checksumming functions for debugging.
Definition: MOM_debugging.F90:7
mom_variables::p3d
A structure for creating arrays of pointers to 3D arrays.
Definition: MOM_variables.F90:28
mom_tidal_mixing::tidal_mixing_diags
Containers for tidal mixing diagnostics.
Definition: MOM_tidal_mixing.F90:43
mom_file_parser::log_param
An overloaded interface to log the values of various types of parameters.
Definition: MOM_file_parser.F90:96
mom_tidal_mixing::tidal_mixing_cs
Control structure with parameters for the tidal mixing module.
Definition: MOM_tidal_mixing.F90:71
mom_error_handler
Routines for error handling and I/O management.
Definition: MOM_error_handler.F90:2
mom_grid::ocean_grid_type
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:25
mom_diag_mediator::diag_ctrl
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Definition: MOM_diag_mediator.F90:239
mom_eos::calculate_density
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:60