Skip to content

Commit

Permalink
+Pass timestep to step_forward_MEKE in units of [T]
Browse files Browse the repository at this point in the history
  Pass timestep to step_forward_MEKE and calc_slope_functions in units of [T].
All answers are bitwise identical, but the units of arguments to two public
subroutines have rescaled dimensions.
  • Loading branch information
Hallberg-NOAA committed Oct 8, 2019
1 parent 5312d99 commit e55ad23
Show file tree
Hide file tree
Showing 3 changed files with 14 additions and 17 deletions.
10 changes: 5 additions & 5 deletions src/core/MOM.F90
Original file line number Diff line number Diff line change
Expand Up @@ -922,7 +922,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
call enable_averaging(dt_thermo, Time_local+real_to_time(dt_thermo-dt), CS%diag)
call cpu_clock_begin(id_clock_thick_diff)
if (associated(CS%VarMix)) &
call calc_slope_functions(h, CS%tv, dt, G, GV, US, CS%VarMix)
call calc_slope_functions(h, CS%tv, US%s_to_T*dt, G, GV, US, CS%VarMix)
call thickness_diffuse(h, CS%uhtr, CS%vhtr, CS%tv, US%s_to_T*dt_thermo, G, GV, US, &
CS%MEKE, CS%VarMix, CS%CDp, CS%thickness_diffuse_CSp)
call cpu_clock_end(id_clock_thick_diff)
Expand Down Expand Up @@ -995,7 +995,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
if (CS%debug) call hchksum(h,"Pre-thickness_diffuse h", G%HI, haloshift=0, scale=GV%H_to_m)

if (associated(CS%VarMix)) &
call calc_slope_functions(h, CS%tv, dt, G, GV, US, CS%VarMix)
call calc_slope_functions(h, CS%tv, US%s_to_T*dt, G, GV, US, CS%VarMix)
call thickness_diffuse(h, CS%uhtr, CS%vhtr, CS%tv, US%s_to_T*dt, G, GV, US, &
CS%MEKE, CS%VarMix, CS%CDp, CS%thickness_diffuse_CSp)

Expand Down Expand Up @@ -1029,7 +1029,7 @@ subroutine step_MOM_dynamics(forces, p_surf_begin, p_surf_end, dt, dt_thermo, &
call diag_update_remap_grids(CS%diag)

if (CS%useMEKE) call step_forward_MEKE(CS%MEKE, h, CS%VarMix%SN_u, CS%VarMix%SN_v, &
CS%visc, dt, G, GV, US, CS%MEKE_CSp, CS%uhtr, CS%vhtr)
CS%visc, US%s_to_T*dt, G, GV, US, CS%MEKE_CSp, CS%uhtr, CS%vhtr)
call disable_averaging(CS%diag)

! Advance the dynamics time by dt.
Expand Down Expand Up @@ -1403,7 +1403,7 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
if (associated(CS%VarMix)) then
call pass_var(CS%h, G%Domain)
call calc_resoln_function(CS%h, CS%tv, G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, REAL(dt_offline), G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, US%s_to_T*REAL(dt_offline), G, GV, US, CS%VarMix)
endif
call tracer_hordiff(CS%h, REAL(dt_offline), CS%MEKE, CS%VarMix, G, GV, US, &
CS%tracer_diff_CSp, CS%tracer_Reg, CS%tv)
Expand All @@ -1428,7 +1428,7 @@ subroutine step_offline(forces, fluxes, sfc_state, Time_start, time_interval, CS
if (associated(CS%VarMix)) then
call pass_var(CS%h, G%Domain)
call calc_resoln_function(CS%h, CS%tv, G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, REAL(dt_offline), G, GV, US, CS%VarMix)
call calc_slope_functions(CS%h, CS%tv, US%s_to_T*REAL(dt_offline), G, GV, US, CS%VarMix)
endif
call tracer_hordiff(CS%h, REAL(dt_offline), CS%MEKE, CS%VarMix, G, GV, US, &
CS%tracer_diff_CSp, CS%tracer_Reg, CS%tv)
Expand Down
13 changes: 5 additions & 8 deletions src/parameterizations/lateral/MOM_MEKE.F90
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@ module MOM_MEKE

!> Integrates forward-in-time the MEKE eddy energy equation.
!! See \ref section_MEKE_equations.
subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, hv)
subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt_in_T, G, GV, US, CS, hu, hv)
type(MEKE_type), pointer :: MEKE !< MEKE data.
type(ocean_grid_type), intent(inout) :: G !< Ocean grid.
type(verticalGrid_type), intent(in) :: GV !< Ocean vertical grid structure.
Expand All @@ -106,7 +106,7 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
real, dimension(SZIB_(G),SZJ_(G)), intent(in) :: SN_u !< Eady growth rate at u-points [T-1 ~> s-1].
real, dimension(SZI_(G),SZJB_(G)), intent(in) :: SN_v !< Eady growth rate at v-points [T-1 ~> s-1].
type(vertvisc_type), intent(in) :: visc !< The vertical viscosity type.
real, intent(in) :: dt !< Model(baroclinic) time-step [s].
real, intent(in) :: dt_in_T !< Model(baroclinic) time-step [T ~> s].
type(MEKE_CS), pointer :: CS !< MEKE control structure.
real, dimension(SZIB_(G),SZJ_(G),SZK_(G)), intent(in) :: hu !< Accumlated zonal mass flux [H L2 ~> m3 or kg].
real, dimension(SZI_(G),SZJB_(G),SZK_(G)), intent(in) :: hv !< Accumlated meridional mass flux [H L2 ~> m3 or kg]
Expand All @@ -117,9 +117,6 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
I_mass, & ! The inverse of mass [R-1 Z-1 ~> m2 kg-1].
src, & ! The sum of all MEKE sources [L2 T-3 ~> W kg-1] (= m2 s-3).
MEKE_decay, & ! A diagnostic of the MEKE decay timescale [T-1 ~> s-1].
! MEKE_GM_src, & ! The MEKE source from thickness mixing [m2 s-3].
! MEKE_mom_src, & ! The MEKE source from momentum [m2 s-3].
! MEKE_GME_snk, & ! The MEKE sink from GME backscatter [m2 s-3].
drag_rate_visc, & ! Near-bottom velocity contribution to bottom dratg [L T-1 ~> m s-1]
drag_rate, & ! The MEKE spindown timescale due to bottom drag [T-1 ~> s-1].
drag_rate_J15, & ! The MEKE spindown timescale due to bottom drag with the Jansen 2015 scheme.
Expand Down Expand Up @@ -193,7 +190,7 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
call uvchksum("MEKE h[uv]", hu, hv, G%HI, haloshift=1, scale=GV%H_to_m)
endif

sdt = US%s_to_T*dt*CS%MEKE_dtScale ! Scaled dt to use for time-stepping
sdt = dt_in_T*CS%MEKE_dtScale ! Scaled dt to use for time-stepping
Rho0 = GV%Rho0
mass_neglect = GV%H_to_RZ * GV%H_subroundoff
cdrag2 = CS%cdrag**2
Expand Down Expand Up @@ -459,8 +456,8 @@ subroutine step_forward_MEKE(MEKE, h, SN_u, SN_v, visc, dt, G, GV, US, CS, hu, h
enddo ; enddo
if (CS%MEKE_advection_factor>0.) then
!### I think that for dimensional consistency, this should be:
! advFac = GV%H_to_RZ * CS%MEKE_advection_factor / (US%s_to_T*dt)
advFac = US%kg_m3_to_R*GV%H_to_Z * CS%MEKE_advection_factor / (US%s_to_T*dt)
! advFac = GV%H_to_RZ * CS%MEKE_advection_factor / sdt
advFac = US%kg_m3_to_R*GV%H_to_Z * CS%MEKE_advection_factor / dt_in_T
!$OMP parallel do default(shared)
do j=js,je ; do I=is-1,ie
! Here the units of the quantities added to MEKE_uflux and MEKE_vflux are [m L4 T-3].
Expand Down
8 changes: 4 additions & 4 deletions src/parameterizations/lateral/MOM_lateral_mixing_coeffs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -395,27 +395,27 @@ end subroutine calc_resoln_function

!> Calculates and stores functions of isopycnal slopes, e.g. Sx, Sy, S*N, mostly used in the Visbeck et al.
!! style scaling of diffusivity
subroutine calc_slope_functions(h, tv, dt, G, GV, US, CS)
subroutine calc_slope_functions(h, tv, dt_in_T, G, GV, US, CS)
type(ocean_grid_type), intent(inout) :: G !< Ocean grid structure
type(verticalGrid_type), intent(in) :: GV !< Vertical grid structure
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
real, dimension(SZI_(G),SZJ_(G),SZK_(G)), intent(inout) :: h !< Layer thickness [H ~> m or kg m-2]
type(thermo_var_ptrs), intent(in) :: tv !< Thermodynamic variables
real, intent(in) :: dt !< Time increment [s]
real, intent(in) :: dt_in_T !< Time increment [T ~> s]
type(VarMix_CS), pointer :: CS !< Variable mixing coefficients
! Local variables
real, dimension(SZI_(G), SZJ_(G), SZK_(G)+1) :: &
e ! The interface heights relative to mean sea level [Z ~> m].
real, dimension(SZIB_(G), SZJ_(G), SZK_(G)+1) :: N2_u ! Square of Brunt-Vaisala freq at u-points [T-2 ~> s-2]
real, dimension(SZI_(G), SZJB_(G), SZK_(G)+1) :: N2_v ! Square of Brunt-Vaisala freq at v-points [s-2]
real, dimension(SZI_(G), SZJB_(G), SZK_(G)+1) :: N2_v ! Square of Brunt-Vaisala freq at v-points [T-2 ~> s-2]

if (.not. associated(CS)) call MOM_error(FATAL, "MOM_lateral_mixing_coeffs.F90, calc_slope_functions:"//&
"Module must be initialized before it is used.")

if (CS%calculate_Eady_growth_rate) then
call find_eta(h, tv, G, GV, US, e, halo_size=2)
if (CS%use_stored_slopes) then
call calc_isoneutral_slopes(G, GV, US, h, e, tv, US%s_to_T*dt*CS%kappa_smooth, &
call calc_isoneutral_slopes(G, GV, US, h, e, tv, dt_in_T*CS%kappa_smooth, &
CS%slope_x, CS%slope_y, N2_u, N2_v, 1)
call calc_Visbeck_coeffs(h, CS%slope_x, CS%slope_y, N2_u, N2_v, G, GV, US, CS)
! call calc_slope_functions_using_just_e(h, G, CS, e, .false.)
Expand Down

0 comments on commit e55ad23

Please sign in to comment.