MOM6
MOM_cvmix_shear.F90
Go to the documentation of this file.
1 !> Interface to CVMix interior shear schemes
3 
4 ! This file is part of MOM6. See LICENSE.md for the license.
5 
6 !---------------------------------------------------
7 ! module MOM_cvmix_shear
8 ! Author: Brandon Reichl
9 ! Date: Aug 31, 2016
10 ! Purpose: Interface to CVMix interior shear schemes
11 ! Further information to be added at a later time.
12 !---------------------------------------------------
13 
14 use mom_diag_mediator, only : post_data, register_diag_field, safe_alloc_ptr
15 use mom_diag_mediator, only : diag_ctrl, time_type
16 use mom_error_handler, only : mom_error, is_root_pe, fatal, warning, note
18 use mom_grid, only : ocean_grid_type
22 use cvmix_shear, only : cvmix_init_shear, cvmix_coeffs_shear
24 implicit none ; private
25 
26 #include <MOM_memory.h>
27 
29 
30 !> Control structure including parameters for CVMix interior shear schemes.
31 type, public :: cvmix_shear_cs
32  logical :: use_lmd94, use_pp81 !< Flags for various schemes
33  real :: ri_zero !< LMD94 critical Richardson number
34  real :: nu_zero !< LMD94 maximum interior diffusivity
35  real :: kpp_exp !<
36  real, allocatable, dimension(:,:,:) :: n2 !< Squared Brunt-Vaisala frequency (1/s2)
37  real, allocatable, dimension(:,:,:) :: s2 !< Squared shear frequency (1/s2)
38  character(10) :: mix_scheme !< Mixing scheme name (string)
39 end type cvmix_shear_cs
40 
41 character(len=40) :: mdl = "MOM_CVMix_shear" !< This module's name.
42 
43 contains
44 
45 !> Subroutine for calculating (internal) diffusivity
46 subroutine calculate_cvmix_shear(u_H, v_H, h, tv, KH, &
47  KM, G, GV, CS )
48  type(ocean_grid_type), intent(in) :: G !< Grid structure.
49  type(verticalgrid_type), intent(in) :: GV !< Vertical grid structure.
50  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: u_H !< Initial zonal velocity on T points, in m s-1.
51  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: v_H !< Initial meridional velocity on T points, in m s-1.
52  real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thickness, in m or kg m-2.
53  type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamics structure.
54  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1), intent(out) :: KH !< The vertical viscosity at each interface
55  !! (not layer!) in m2 s-1.
56  real, dimension(SZI_(G),SZJ_(G),SZK_(G)+1), intent(out) :: KM !< The vertical viscosity at each interface
57  !! (not layer!) in m2 s-1.
58  type(cvmix_shear_cs), pointer :: CS !< The control structure returned by a previous call to
59  !! CVMix_shear_init.
60  ! Local variables
61  integer :: i, j, k, kk, km1
62  real :: gorho
63  real :: pref, DU, DV, DRHO, DZ, N2, S2
64  real, dimension(2*(G%ke)) :: pres_1d, temp_1d, salt_1d, rho_1d
65  real, dimension(G%ke+1) :: Ri_Grad !< Gradient Richardson number
66 
67  ! some constants
68  gorho = gv%g_Earth / gv%Rho0
69 
70  do j = g%jsc, g%jec
71  do i = g%isc, g%iec
72 
73  ! skip calling for land points
74  if (g%mask2dT(i,j)==0.) cycle
75 
76  ! Richardson number computed for each cell in a column.
77  pref = 0.
78  ri_grad(:)=1.e8 !Initialize w/ large Richardson value
79  do k=1,g%ke
80  ! pressure, temp, and saln for EOS
81  ! kk+1 = k fields
82  ! kk+2 = km1 fields
83  km1 = max(1, k-1)
84  kk = 2*(k-1)
85  pres_1d(kk+1) = pref
86  pres_1d(kk+2) = pref
87  temp_1d(kk+1) = tv%T(i,j,k)
88  temp_1d(kk+2) = tv%T(i,j,km1)
89  salt_1d(kk+1) = tv%S(i,j,k)
90  salt_1d(kk+2) = tv%S(i,j,km1)
91 
92  ! pRef is pressure at interface between k and km1.
93  ! iterate pRef for next pass through k-loop.
94  pref = pref + gv%H_to_Pa * h(i,j,k)
95 
96  enddo ! k-loop finishes
97 
98  ! compute in-situ density
99  call calculate_density(temp_1d, salt_1d, pres_1d, rho_1d, 1, 2*g%ke, tv%EQN_OF_STATE)
100 
101  ! N2 (can be negative) on interface
102  do k = 1, g%ke
103  km1 = max(1, k-1)
104  kk = 2*(k-1)
105  du = (u_h(i,j,k))-(u_h(i,j,km1))
106  dv = (v_h(i,j,k))-(v_h(i,j,km1))
107  drho = (gorho * (rho_1d(kk+1) - rho_1d(kk+2)) )
108  dz = ((0.5*(h(i,j,km1) + h(i,j,k))+gv%H_subroundoff)*gv%H_to_m)
109  n2 = drho/dz
110  s2 = (du*du+dv*dv)/(dz*dz)
111  ri_grad(k) = max(0.,n2)/max(s2,1.e-16)
112  enddo
113 
114  ! Call to CVMix wrapper for computing interior mixing coefficients.
115  call cvmix_coeffs_shear(mdiff_out=km(i,j,:), &
116  tdiff_out=kh(i,j,:), &
117  rich=ri_grad, &
118  nlev=g%ke, &
119  max_nlev=g%ke)
120  enddo
121  enddo
122 
123 end subroutine calculate_cvmix_shear
124 
125 
126 !> Initialized the cvmix internal shear mixing routine.
127 !! \note *This is where we test to make sure multiple internal shear
128 !! mixing routines (including JHL) are not enabled at the same time.
129 !! (returns) cvmix_shear_init - True if module is to be used, False otherwise
130 logical function cvmix_shear_init(Time, G, GV, param_file, diag, CS)
131  type(time_type), intent(in) :: Time !< The current time.
132  type(ocean_grid_type), intent(in) :: G !< Grid structure.
133  type(verticalgrid_type), intent(in) :: GV !< Vertical grid structure.
134  type(param_file_type), intent(in) :: param_file !< Run-time parameter file handle
135  type(diag_ctrl), target, intent(inout) :: diag !< Diagnostics control structure.
136  type(cvmix_shear_cs), pointer :: CS !< This module's control structure.
137  ! Local variables
138  integer :: NumberTrue=0
139  logical :: use_JHL
140 ! This include declares and sets the variable "version".
141 #include "version_variable.h"
142 
143  if (associated(cs)) then
144  call mom_error(warning, "cvmix_shear_init called with an associated "// &
145  "control structure.")
146  return
147  endif
148  allocate(cs)
149 
150 ! Set default, read and log parameters
151  call log_version(param_file, mdl, version, &
152  "Parameterization of shear-driven turbulence via CVMix (various options)")
153  call get_param(param_file, mdl, "USE_LMD94", cs%use_LMD94, &
154  "If true, use the Large-McWilliams-Doney (JGR 1994) \n"//&
155  "shear mixing parameterization.", default=.false.)
156  if (cs%use_LMD94) then
157  numbertrue=numbertrue + 1
158  cs%Mix_Scheme='KPP'
159  endif
160  call get_param(param_file, mdl, "USE_PP81", cs%use_PP81, &
161  "If true, use the Pacanowski and Philander (JPO 1981) \n"//&
162  "shear mixing parameterization.", default=.false.)
163  if (cs%use_PP81) then
164  numbertrue = numbertrue + 1
165  cs%Mix_Scheme='PP'
166  endif
167  use_jhl=kappa_shear_is_used(param_file)
168  if (use_jhl) numbertrue = numbertrue + 1
169  ! After testing for interior schemes, make sure only 0 or 1 are enabled.
170  ! Otherwise, warn user and kill job.
171  if ((numbertrue).gt.1) then
172  call mom_error(fatal, 'MOM_cvmix_shear_init: '// &
173  'Multiple shear driven internal mixing schemes selected,'//&
174  ' please disable all but one scheme to proceed.')
175  endif
176  cvmix_shear_init=(cs%use_PP81.or.cs%use_LMD94)
177 
178 ! Forego remainder of initialization if not using this scheme
179  if (.not. cvmix_shear_init) return
180  call get_param(param_file, mdl, "NU_ZERO", cs%Nu_Zero, &
181  "Leading coefficient in KPP shear mixing.", &
182  units="nondim", default=5.e-3)
183  call get_param(param_file, mdl, "RI_ZERO", cs%Ri_Zero, &
184  "Critical Richardson for KPP shear mixing,"// &
185  " NOTE this the internal mixing and this is"// &
186  " not for setting the boundary layer depth." &
187  ,units="nondim", default=0.7)
188  call get_param(param_file, mdl, "KPP_EXP", cs%KPP_exp, &
189  "Exponent of unitless factor of diffusivities,"// &
190  " for KPP internal shear mixing scheme." &
191  ,units="nondim", default=3.0)
192  call cvmix_init_shear(mix_scheme=cs%mix_scheme, &
193  kpp_nu_zero=cs%Nu_Zero, &
194  kpp_ri_zero=cs%Ri_zero, &
195  kpp_exp=cs%KPP_exp)
196  ! Allocation and initialization
197  allocate( cs%N2( szi_(g), szj_(g), szk_(g)+1 ) );cs%N2(:,:,:) = 0.
198  allocate( cs%S2( szi_(g), szj_(g), szk_(g)+1 ) );cs%S2(:,:,:) = 0.
199 
200 end function cvmix_shear_init
201 
202 !> Reads the parameters "LMD94" and "PP81" and returns state.
203 !! This function allows other modules to know whether this parameterization will
204 !! be used without needing to duplicate the log entry.
205 logical function cvmix_shear_is_used(param_file)
206  type(param_file_type), intent(in) :: param_file !< Run-time parameter files handle.
207  ! Local variables
208  logical :: LMD94, PP81
209  call get_param(param_file, mdl, "USE_LMD94", lmd94, &
210  default=.false., do_not_log = .true.)
211  call get_param(param_file, mdl, "Use_PP81", pp81, &
212  default=.false., do_not_log = .true.)
213  cvmix_shear_is_used = (lmd94 .or. pp81)
214 end function cvmix_shear_is_used
215 
216 end module mom_cvmix_shear
Control structure including parameters for CVMix interior shear schemes.
Interface to CVMix interior shear schemes.
Ocean grid type. See mom_grid for details.
Definition: MOM_grid.F90:19
The following data type a list of diagnostic fields an their variants, as well as variables that cont...
Calculates density of sea water from T, S and P.
Definition: MOM_EOS.F90:45
subroutine, public calculate_cvmix_shear(u_H, v_H, h, tv, KH, KM, G, GV, CS)
Subroutine for calculating (internal) diffusivity.
Provides the ocean grid type.
Definition: MOM_grid.F90:2
logical function, public cvmix_shear_init(Time, G, GV, param_file, diag, CS)
Initialized the cvmix internal shear mixing routine.
logical function, public is_root_pe()
Provides subroutines for quantities specific to the equation of state.
Definition: MOM_EOS.F90:2
character(len=40) mdl
This module&#39;s name.
logical function, public cvmix_shear_is_used(param_file)
Reads the parameters "LMD94" and "PP81" and returns state. This function allows other modules to know...
The thermo_var_ptrs structure contains pointers to an assortment of thermodynamic fields that may be ...
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)
logical function, public kappa_shear_is_used(param_file)
A control structure for the equation of state.
Definition: MOM_EOS.F90:55