Skip to content

Commit

Permalink
Removed parameter KPP_BEFORE_KAPPA_SHEAR since always true.
Browse files Browse the repository at this point in the history
Removed parameter KPP_BEFORE_KAPPA_SHEAR since always true.
This cleans up some awkward code related to removing, then
adding back, the shear mixing diffusivity.

MOM6 implementation of KPP always matches the boundary
layer diffusivity to a zero value of the interior
diffusivity, even if there is a nonzero interior diffusivity.
The reason for this approach is that matching to a nonzero
interior diffusivity can produce some very spurious results.
Because MOM6 always matches to zero interior diffusivity,
we can remove the code related to earlier implementations where
we matched to a non-zero interior value.  Removing this code
cleans up some logic nicely.
  • Loading branch information
StephenGriffies committed Sep 2, 2015
1 parent 81e8071 commit bf1d55f
Showing 1 changed file with 6 additions and 31 deletions.
37 changes: 6 additions & 31 deletions src/parameterizations/vertical/MOM_diabatic_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -163,16 +163,11 @@ module MOM_diabatic_driver
! applied to tracers, especially in massless layers
! near the bottom, in m2 s-1.

logical :: useKPP ! If true, use [CVmix] KPP diffusivities and non-local
! transport.
logical :: salt_reject_below_ML ! It true, add salt below mixed layer (layer mode only)
logical :: useKPP ! use CVmix/KPP diffusivities and non-local transport
logical :: salt_reject_below_ML ! If true, add salt below mixed layer (layer mode only)
logical :: KPPisPassive ! If true, KPP is in passive mode, not changing answers.
logical :: useConvection ! If true, calculate large diffusivities when column
! is statically unstable.
logical :: matchKPPwithoutKappaShear ! If true, KPP is matched to interior diffusivities
! that do NOT include kappa-shear diffusivity.
! Generally run with this option false.

logical :: debug ! If true, write verbose checksums for debugging purposes.
logical :: debugConservation ! If true, monitor conservation and extrema.
type(diag_ctrl), pointer :: diag ! structure used to regulate timing of diagnostic output
Expand Down Expand Up @@ -513,32 +508,23 @@ subroutine diabatic(u, v, h, tv, fluxes, visc, ADp, CDp, dt, G, CS)
if (CS%useKPP) then
call cpu_clock_begin(id_clock_kpp)
! KPP needs the surface buoyancy flux but does not update state variables.
! We could make this call higher up to avoid a repeat unpacking of the surface fluxes. ????
! We could make this call higher up to avoid a repeat unpacking of the surface fluxes.
! Sets: CS%KPP_buoy_flux, CS%KPP_temp_flux, CS%KPP_salt_flux
! NOTE: CS%KPP_buoy_flux, CS%KPP_temp_flux, CS%KPP_salt_flux are returned as rates (i.e. stuff per second)
! unlike other instances where the fluxes are integrated in time over a time-step.
call calculateBuoyancyFlux2d(G, fluxes, CS%optics, h, tv%T, tv%S, tv, &
CS%KPP_buoy_flux, CS%KPP_temp_flux, CS%KPP_salt_flux)
! The KPP scheme calculates the boundary layer diffusivities and non-local transport.
! If have KPP matching to interior, then KPP must be last contribution to Kd.
! But generally MOM does not insist on matching KPP boundary layer diffusivities to
! the interior, as that matching can be problematic.
! The KPP scheme calculates boundary layer diffusivities and non-local transport.
! MOM6 implementation of KPP matches the boundary layer to zero interior diffusivity,
! since the matching to nonzero interior diffusivity can be problematic.
! Changes: Kd_int. Sets: KPP_NLTheat, KPP_NLTscalar

!$OMP parallel default(none) shared(is,ie,js,je,nz,Kd_salt,Kd_int,visc,CS,Kd_heat)
if (associated(visc%Kd_turb) .and. CS%matchKPPwithoutKappaShear) then
!$OMP do
do k=1,nz+1 ; do j=js,je ; do i=is,ie
Kd_salt(i,j,k) = Kd_int(i,j,k) - visc%Kd_turb(i,j,k) ! Temporarily remove part due to Kappa-shear smg: clean this up!
Kd_heat(i,j,k) = Kd_int(i,j,k) - visc%Kd_turb(i,j,k) ! Temporarily remove part due to Kappa-shear smg: clean thus up!
enddo ; enddo ; enddo
else
!$OMP do
do k=1,nz+1 ; do j=js,je ; do i=is,ie
Kd_salt(i,j,k) = Kd_int(i,j,k)
Kd_heat(i,j,k) = Kd_int(i,j,k)
enddo ; enddo ; enddo
endif
if (associated(visc%Kd_extra_S)) then
!$OMP do
do k=1,nz+1 ; do j=js,je ; do i=is,ie
Expand All @@ -558,13 +544,6 @@ subroutine diabatic(u, v, h, tv, fluxes, visc, ADp, CDp, dt, G, CS)
!$OMP parallel default(none) shared(is,ie,js,je,nz,Kd_salt,Kd_int,visc,CS,Kd_heat)

if (.not. CS%KPPisPassive) then
if (associated(visc%Kd_turb) .and. CS%matchKPPwithoutKappaShear) then
!$OMP do
do k=1,nz+1 ; do j=js,je ; do i=is,ie
Kd_salt(i,j,k) = ( Kd_salt(i,j,k) + visc%Kd_turb(i,j,k) ) ! Put back part due to Kappa-shear smg: clean this up!
Kd_heat(i,j,k) = ( Kd_heat(i,j,k) + visc%Kd_turb(i,j,k) ) ! Put back part due to Kappa-shear smg: clean this up!
enddo ; enddo ; enddo
endif
!$OMP do
do k=1,nz+1 ; do j=js,je ; do i=is,ie
Kd_int(i,j,k) = min( Kd_salt(i,j,k), Kd_heat(i,j,k) )
Expand Down Expand Up @@ -1559,10 +1538,6 @@ subroutine diabatic_driver_init(Time, G, param_file, useALEalgorithm, diag, &
allocate( CS%KPP_buoy_flux(isd:ied,jsd:jed,nz+1) ) ; CS%KPP_buoy_flux(:,:,:) = 0.
allocate( CS%KPP_temp_flux(isd:ied,jsd:jed) ) ; CS%KPP_temp_flux(:,:) = 0.
allocate( CS%KPP_salt_flux(isd:ied,jsd:jed) ) ; CS%KPP_salt_flux(:,:) = 0.
if (CS%use_kappa_shear) &
call get_param(param_file, mod, "KPP_BEFORE_KAPPA_SHEAR", CS%matchKPPwithoutKappaShear, &
"If true, KPP matches interior diffusivity that EXCLUDES any\n"// &
"diffusivity from kappa-shear.", default=.true.)
endif

call get_param(param_file, mod, "SALT_REJECT_BELOW_ML", CS%salt_reject_below_ML, &
Expand Down

0 comments on commit bf1d55f

Please sign in to comment.