Skip to content

Commit

Permalink
Changed use_QG_Leith to use_QG_Leith_visc. Removed commented lines fr…
Browse files Browse the repository at this point in the history
…om calc_QG_Leith_viscosity.
  • Loading branch information
sdbachman committed Nov 1, 2018
1 parent e0baaea commit 52667e9
Show file tree
Hide file tree
Showing 2 changed files with 10 additions and 101 deletions.
26 changes: 10 additions & 16 deletions src/parameterizations/lateral/MOM_hor_visc.F90
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ module MOM_hor_visc
logical :: use_beta_in_Leith !< If true, includes the beta term in the Leith viscosity
logical :: Leith_Ah !< If true, use a biharmonic form of 2D Leith
!! nonlinear eddy viscosity. AH is the background.
logical :: use_QG_Leith !< If true, use QG Leith nonlinear eddy viscosity.
logical :: use_QG_Leith_visc !< If true, use QG Leith nonlinear eddy viscosity.
!! KH is the background value.
logical :: bound_Coriolis !< If true & SMAGORINSKY_AH is used, the biharmonic
!! viscosity is modified to include a term that
Expand Down Expand Up @@ -322,13 +322,6 @@ subroutine horizontal_viscosity(u, v, h, diffu, diffv, MEKE, VarMix, G, GV, CS,
legacy_bound = (CS%Smagorinsky_Kh .or. CS%Leith_Kh) .and. &
(CS%bound_Kh .and. .not.CS%better_bound_Kh)

! Coefficient for modified Leith
if (CS%Modified_Leith) then
mod_Leith = 1.0
else
mod_Leith = 0.0
endif

! Toggle whether to use a Laplacian viscosity derived from MEKE
use_MEKE_Ku = associated(MEKE%Ku)

Expand Down Expand Up @@ -621,8 +614,9 @@ subroutine horizontal_viscosity(u, v, h, diffu, diffv, MEKE, VarMix, G, GV, CS,
enddo ; enddo
endif ! CS%use_beta_in_Leith

if (CS%use_QG_Leith) then
call calc_QG_Leith_viscosity(VarMix, G, GV, h, k, vort_xy_dx, vort_xy_dy)
if (CS%use_QG_Leith_visc) then
call calc_QG_Leith_viscosity(VarMix, G, GV, h, k, vort_xy_dx, vort_xy_dy, &
grad_div_mag_h, grad_div_mag_q)
endif

do j=Jsq-1,Jeq+2 ; do i=Isq-1,Ieq+2
Expand Down Expand Up @@ -1115,7 +1109,7 @@ subroutine hor_visc_init(Time, G, param_file, diag, CS)
! cases where the corresponding parameters are not read.
CS%bound_Kh = .false. ; CS%better_bound_Kh = .false. ; CS%Smagorinsky_Kh = .false. ; CS%Leith_Kh = .false.
CS%bound_Ah = .false. ; CS%better_bound_Ah = .false. ; CS%Smagorinsky_Ah = .false. ; CS%Leith_Ah = .false.
CS%use_QG_Leith = .false.
CS%use_QG_Leith_visc = .false.
CS%bound_Coriolis = .false.
CS%Modified_Leith = .false.
CS%anisotropic = .false.
Expand Down Expand Up @@ -1170,17 +1164,17 @@ subroutine hor_visc_init(Time, G, param_file, diag, CS)
"The nondimensional Laplacian Leith constant, \n"//&
"often set to 1.0", units="nondim", default=0.0, &
fail_if_missing = CS%Leith_Kh)
call get_param(param_file, mdl, "USE_QG_LEITH", CS%use_QG_Leith, &
call get_param(param_file, mdl, "USE_QG_LEITH_VISC", CS%use_QG_Leith_visc, &
"If true, use QG Leith nonlinear eddy viscosity.", &
default=.false.)
if (CS%use_QG_Leith .and. .not. CS%Leith_Kh) call MOM_error(FATAL, &
if (CS%use_QG_Leith_visc .and. .not. CS%Leith_Kh) call MOM_error(FATAL, &
"MOM_lateral_mixing_coeffs.F90, VarMix_init:"//&
"LEITH_KH must be True when USE_QG_LEITH=True.")
"LEITH_KH must be True when USE_QG_LEITH_VISC=True.")
endif
if (CS%Leith_Kh .or. CS%Leith_Ah .or. get_all) then
call get_param(param_file, mdl, "USE_BETA_IN_LEITH", CS%use_beta_in_Leith, &
"If true, include the beta term in the QG Leith nonlinear eddy viscosity.", &
default=CS%use_QG_Leith)
"If true, include the beta term in the Leith nonlinear eddy viscosity.", &
default=CS%Leith_Kh)
call get_param(param_file, mdl, "MODIFIED_LEITH", CS%modified_Leith, &
"If true, add a term to Leith viscosity which is \n"//&
"proportional to the gradient of divergence.", &
Expand Down
85 changes: 0 additions & 85 deletions src/parameterizations/lateral/MOM_lateral_mixing_coeffs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -780,67 +780,6 @@ subroutine calc_QG_Leith_viscosity(CS, G, GV, h, k, vort_xy_dx, vort_xy_dy)
is = G%isc ; ie = G%iec ; js = G%jsc ; je = G%jec
Isq = G%IscB ; Ieq = G%IecB ; Jsq = G%JscB ; Jeq = G%JecB

! ! Divergence
! do j=Jsq-1,Jeq+2 ; do i=Isq-1,Ieq+2
! div_xx(i,j) = 0.5*((G%dyCu(I,j) * u(I,j,k) * (h(i+1,j,k)+h(i,j,k)) - &
! G%dyCu(I-1,j) * u(I-1,j,k) * (h(i-1,j,k)+h(i,j,k)) ) + &
! (G%dxCv(i,J) * v(i,J,k) * (h(i,j,k)+h(i,j+1,k)) - &
! G%dxCv(i,J-1)*v(i,J-1,k)*(h(i,j,k)+h(i,j-1,k))))*G%IareaT(i,j)/ &
! (h(i,j,k) + GV%H_subroundoff)
! enddo ; enddo
!
! ! Divergence gradient
! do j=Jsq-1,Jeq+2 ; do I=is-2,Ieq+1
! div_xx_dx(I,j) = G%IdxCu(I,j)*(div_xx(i+1,j) - div_xx(i,j))
! enddo ; enddo
!
! do J=js-2,Jeq+1 ; do i=Isq-1,Ieq+2
! div_xx_dy(i,J) = G%IdyCv(i,J)*(div_xx(i,j+1) - div_xx(i,j))
! enddo ; enddo
!
! ! Components for the vertical vorticity
! ! Note this a simple re-calculation of shearing components using the same discretization.
! ! We will consider using a circulation based calculation of vorticity later.
! ! Also note this will need OBC boundary conditions re-applied...
! do J=js-2,Jeq+1 ; do I=is-2,Ieq+1
! DY_dxBu = G%dyBu(I,J) * G%IdxBu(I,J)
! dvdx(I,J) = DY_dxBu * (v(i+1,J,k) * G%IdyCv(i+1,J) - v(i,J,k) * G%IdyCv(i,J))
! DX_dyBu = G%dxBu(I,J) * G%IdyBu(I,J)
! dudy(I,J) = DX_dyBu * (u(I,j+1,k) * G%IdxCu(I,j+1) - u(I,j,k) * G%IdxCu(I,j))
! enddo ; enddo
!
! ! Vorticity
! if (CS%no_slip) then
! do J=js-2,Jeq+1 ; do I=is-2,Ieq+1
! vort_xy(I,J) = (2.0-G%mask2dBu(I,J)) * ( dvdx(I,J) - dudy(I,J) )
! enddo ; enddo
! else
! do J=js-2,Jeq+1 ; do I=is-2,Ieq+1
! vort_xy(I,J) = G%mask2dBu(I,J) * ( dvdx(I,J) - dudy(I,J) )
! enddo ; enddo
! endif
!
! ! Vorticity gradient
! do J=js-2,Jeq+1 ; do i=is-1,Ieq+1
! DY_dxBu = G%dyBu(I,J) * G%IdxBu(I,J)
! vort_xy_dx(i,J) = DY_dxBu * (vort_xy(I,J) * G%IdyCu(I,j) - vort_xy(I-1,J) * G%IdyCu(I-1,j))
! enddo ; enddo
!
! do j=js-1,Jeq+1 ; do I=is-2,Ieq+1
! DX_dyBu = G%dxBu(I,J) * G%IdyBu(I,J)
! vort_xy_dy(I,j) = DX_dyBu * (vort_xy(I,J) * G%IdxCv(i,J) - vort_xy(I,J-1) * G%IdxCv(i,J-1))
! enddo ; enddo
!
! ! Add in beta for the Leith viscosity
! if (CS%use_beta_in_Leith) then
! do J=js-2,Jeq+1 ; do i=is-1,Ieq+1
! vort_xy_dx(i,J) = vort_xy_dx(i,J) + 0.5 * ( G%dF_dx(i,j) + G%dF_dx(i,j+1) )
! enddo ; enddo
! do j=js-1,Jeq+1 ; do I=is-2,Ieq+1
! vort_xy_dy(I,j) = vort_xy_dy(I,j) + 0.5 * ( G%dF_dy(i,j) + G%dF_dy(i+1,j) )
! enddo ; enddo
! endif
!
! Add in stretching term for the QG Leith vsicosity
! if (CS%use_QG_Leith) then
do j=js-1,Jeq+1 ; do I=is-2,Ieq+1
Expand Down Expand Up @@ -879,31 +818,7 @@ subroutine calc_QG_Leith_viscosity(CS, G, GV, h, k, vort_xy_dx, vort_xy_dy)
+ ( h_at_v(i,J-1) * dslopey_dz(i,J-1) + h_at_v(i+1,J) * dslopey_dz(i+1,J) ) ) / &
( ( h_at_v(i,J) + h_at_v(i+1,J-1) ) + ( h_at_v(i,J-1) + h_at_v(i+1,J) ) )
enddo ; enddo
! endif

! mod_Leith = 0.; if (CS%modified_Leith) mod_Leith = 1.0

! ! h-point viscosities
! do j=Jsq,Jeq+1 ; do i=Isq,Ieq+1
! vert_vort_mag = sqrt( &
! 0.5*((vort_xy_dx(i,J-1)*vort_xy_dx(i,J-1) + vort_xy_dx(i,J)*vort_xy_dx(i,J)) + &
! (vort_xy_dy(I-1,j)*vort_xy_dy(I-1,j) + vort_xy_dy(I,j)*vort_xy_dy(I,j))) + &
! mod_Leith*0.5*((div_xx_dx(I,j)*div_xx_dx(I,j) + div_xx_dx(I-1,j)*div_xx_dx(I-1,j)) + &
! (div_xx_dy(i,J)*div_xx_dy(i,J) + div_xx_dy(i,J-1)*div_xx_dy(i,J-1))))
! if (CS%Leith_Kh) Leith_Kh_h(i,j) = CS%Laplac3_const_xx(i,j) * vert_vort_mag
! if (CS%Leith_Ah) Leith_Ah_h(i,j) = CS%biharm5_const_xx(i,j) * vert_vort_mag
! enddo ; enddo

! ! q-point viscosities
! do J=js-1,Jeq ; do I=is-1,Ieq
! vert_vort_mag = sqrt( &
! 0.5*((vort_xy_dx(i,J)*vort_xy_dx(i,J) + vort_xy_dx(i+1,J)*vort_xy_dx(i+1,J)) + &
! (vort_xy_dy(I,j)*vort_xy_dy(I,j) + vort_xy_dy(I,j+1)*vort_xy_dy(I,j+1))) + &
! mod_Leith*0.5*((div_xx_dx(I,j)*div_xx_dx(I,j) + div_xx_dx(I,j+1)*div_xx_dx(I,j+1)) + &
! (div_xx_dy(i,J)*div_xx_dy(i,J) + div_xx_dy(i+1,J)*div_xx_dy(i+1,J))))
! if (CS%Leith_Kh) Leith_Kh_q(I,J) = CS%Laplac3_const_xy(I,J) * vert_vort_mag
! if (CS%Leith_Ah) Leith_Ah_q(I,J) = CS%biharm5_const_xx(I,J) * vert_vort_mag
! enddo ; enddo

end subroutine calc_QG_Leith_viscosity

Expand Down

0 comments on commit 52667e9

Please sign in to comment.