Skip to content

Commit

Permalink
Add vertical background viscosity into visc%Kv_slow
Browse files Browse the repository at this point in the history
  • Loading branch information
gustavo-marques committed Apr 3, 2018
1 parent a2498a1 commit c1acec8
Show file tree
Hide file tree
Showing 4 changed files with 36 additions and 30 deletions.
56 changes: 31 additions & 25 deletions src/parameterizations/vertical/MOM_bkgnd_mixing.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module MOM_bkgnd_mixing
use MOM_verticalGrid, only : verticalGrid_type
use MOM_file_parser, only : get_param, log_version, param_file_type
use cvmix_background, only : cvmix_init_bkgnd, cvmix_coeffs_bkgnd
use MOM_variables, only : vertvisc_type
use MOM_intrinsic_functions, only : invcosh

implicit none ; private
Expand Down Expand Up @@ -302,23 +303,26 @@ end subroutine sfc_bkgnd_mixing


!> Calculates the vertical background diffusivities/viscosities
subroutine calculate_bkgnd_mixing(h, tv, N2_lay, Kd, j, G, GV, CS)
subroutine calculate_bkgnd_mixing(h, tv, N2_lay, Kd, visc, j, G, GV, CS)

type(ocean_grid_type), intent(in) :: G !< Grid structure.
type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure.
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thickness, in m or kg m-2.
type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamics structure.
type(ocean_grid_type), intent(in) :: G !< Grid structure.
type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure.
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(in) :: h !< Layer thickness, in m or kg m-2.
type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamics structure.
real, dimension(SZI_(G),SZK_(G)), intent(in) :: N2_lay!< squared buoyancy frequency associated
!! with layers (1/s2)
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: Kd !< Diapycnal diffusivity of each layer (m2/sec).
integer, intent(in) :: j
type(bkgnd_mixing_cs), pointer :: CS !< The control structure returned by
!! a previous call to bkgnd_mixing_init.
!! with layers (1/s2)
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: Kd !< Diapycnal diffusivity of each layer (m2/sec).
type(vertvisc_type), intent(inout) :: visc!< Structure containing vertical viscosities,
!! bottom boundary layer properies, and related
!! fields.
integer, intent(in) :: j !< Meridional grid indice.
type(bkgnd_mixing_cs), pointer :: CS !< The control structure returned by
!! a previous call to bkgnd_mixing_init.

! local variables
real, dimension(SZI_(G), SZK_(G)+1) :: depth_2d !< distance from surface of an interface (m)
real, dimension(SZI_(G), SZK_(G)+1) :: depth_2d !< distance from surface of an interface (m)
real, dimension(SZI_(G)) :: &
depth !< distance from surface of an interface (meter)
depth !< distance from surface of an interface (meter)
real :: depth_c !< depth of the center of a layer (meter)
real :: I_Hmix !< inverse of fixed mixed layer thickness (1/m)
real :: I_2Omega !< 1/(2 Omega) (sec)
Expand Down Expand Up @@ -359,15 +363,11 @@ subroutine calculate_bkgnd_mixing(h, tv, N2_lay, Kd, j, G, GV, CS)
nlev=nz, &
max_nlev=nz)

do k=1,nz
! Update Kd
do k=1,nz
Kd(i,j,k) = Kd(i,j,k) + 0.5*(CS%kd_bkgnd(i,j,K) + CS%kd_bkgnd(i,j,K+1))
! ######## CHECK ###############
! GMM, we could update Kv here?????
! Kv(i,j,k) = Kv(i,j,k) + 0.5*(CS%bkgnd_mixing_csp%kv_bkgnd(i,j,K) + &
! CS%bkgnd_mixing_csp%kv_bkgnd(i,j,K+1))
enddo
enddo
enddo ! i loop

elseif ((.not. CS%Bryan_Lewis_diffusivity) .and. (.not.CS%bulkmixedlayer) .and. &
(CS%Kd/= CS%Kdml)) then
Expand Down Expand Up @@ -401,17 +401,23 @@ subroutine calculate_bkgnd_mixing(h, tv, N2_lay, Kd, j, G, GV, CS)
enddo ; enddo
endif

! Update CS%kd_bkgnd
! GMM, we could update CS%kv_bkgnd here?????
! Update CS%kd_bkgnd and CS%kv_bkgnd for diagnostic purposes
if (.not. CS%Bryan_Lewis_diffusivity) then
do i=is,ie
CS%kd_bkgnd(i,j,1) = 0.0
CS%kd_bkgnd(i,j,nz+1) = 0.0
CS%kd_bkgnd(i,j,1) = 0.0; CS%kv_bkgnd(i,j,1) = 0.0
CS%kd_bkgnd(i,j,nz+1) = 0.0; CS%kv_bkgnd(i,j,nz+1) = 0.0
do k=2,nz
! Update CS%kd_bkgnd
CS%kd_bkgnd(i,j,k) = CS%kd_bkgnd(i,j,k) + 0.5*(Kd(i,j,K-1) + Kd(i,j,K))
! ######## CHECK ###############
! GMM, we could update CS%kv_bkgnd here?????
CS%kv_bkgnd(i,j,k) = CS%kd_bkgnd(i,j,k) * CS%prandtl_bkgnd
enddo
enddo
endif

! Update visc%Kv_slow, if associated
if (associated(visc%Kv_slow)) then
do i=is,ie
do k=1,nz+1
visc%Kv_slow(i,j,k) = visc%Kv_slow(i,j,k) + CS%kv_bkgnd(i,j,k)
enddo
enddo
endif
Expand Down
4 changes: 2 additions & 2 deletions src/parameterizations/vertical/MOM_diabatic_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -677,8 +677,8 @@ subroutine diabatic(u, v, h, tv, Hml, fluxes, visc, ADp, CDp, dt, Time_end, G, G

!!!!!!!! GMM, the following needs to be checked !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
do k=1,nz ; do j=js,je ; do i=is,ie
Kd_int(i,j,k) = Kd_int(i,j,k) + CS%cvmix_conv_csp%kd_conv_3d(i,j,k)
visc%Kv_slow(i,j,k) = visc%Kv_slow(i,j,k) + CS%cvmix_conv_csp%kv_conv_3d(i,j,k)
Kd_int(i,j,k) = Kd_int(i,j,k) + CS%cvmix_conv_csp%kd_conv(i,j,k)
visc%Kv_slow(i,j,k) = visc%Kv_slow(i,j,k) + CS%cvmix_conv_csp%kv_conv(i,j,k)
enddo ; enddo ; enddo
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!

Expand Down
2 changes: 1 addition & 1 deletion src/parameterizations/vertical/MOM_set_diffusivity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -505,7 +505,7 @@ subroutine set_diffusivity(u, v, h, u_h, v_h, tv, fluxes, optics, visc, dt, &
endif

! add background mixing
call calculate_bkgnd_mixing(h, tv, N2_lay, Kd, j, G, GV, CS%bkgnd_mixing_csp)
call calculate_bkgnd_mixing(h, tv, N2_lay, Kd, visc, j, G, GV, CS%bkgnd_mixing_csp)

! GMM, the following will go into the MOM_cvmix_double_diffusion module
if (CS%double_diffusion) then
Expand Down
4 changes: 2 additions & 2 deletions src/parameterizations/vertical/MOM_set_viscosity.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1823,8 +1823,8 @@ subroutine set_visc_register_restarts(HI, GV, param_file, visc, restart_CS)
vd = var_desc("Kv_shear","m2 s-1","Shear-driven turbulent viscosity at interfaces", &
hor_grid='h', z_grid='i')
call register_restart_field(visc%Kv_shear, vd, .false., restart_CS)
vd = var_desc("Kv_slow","m2 s-1","Vertical turbulent viscosity at interfaces due to slow" &
" processes", hor_grid='h', z_grid='i')
vd = var_desc("Kv_slow","m2 s-1","Vertical turbulent viscosity at interfaces due \n" // &
" to slow processes", hor_grid='h', z_grid='i')
call register_restart_field(visc%Kv_slow, vd, .false., restart_CS)

endif
Expand Down

0 comments on commit c1acec8

Please sign in to comment.