Skip to content

Commit

Permalink
Frequency-dependent internal wave drag
Browse files Browse the repository at this point in the history
Minor performance optimization. Also, this commit allows the filters
to be activated without the frequency-dependent drag being activated.
  • Loading branch information
c2xu committed Feb 16, 2025
1 parent 3439a85 commit 99916d3
Show file tree
Hide file tree
Showing 2 changed files with 40 additions and 26 deletions.
44 changes: 29 additions & 15 deletions src/core/MOM_barotropic.F90
Original file line number Diff line number Diff line change
Expand Up @@ -609,9 +609,9 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
! spacing [H L ~> m2 or kg m-1].
real, dimension(:,:,:), pointer :: ufilt, vfilt
! Filtered velocities from the output of streaming filters [L T-1 ~> m s-1]
real, dimension(SZIBW_(CS),SZJW_(CS)) :: Drag_u
real, dimension(SZIB_(G),SZJ_(G)) :: Drag_u
! The zonal acceleration due to frequency-dependent drag [L T-2 ~> m s-2]
real, dimension(SZIW_(CS),SZJBW_(CS)) :: Drag_v
real, dimension(SZI_(G),SZJB_(G)) :: Drag_v
! The meridional acceleration due to frequency-dependent drag [L T-2 ~> m s-2]
real, target, dimension(SZIW_(CS),SZJW_(CS)) :: &
eta, & ! The barotropic free surface height anomaly or column mass
Expand Down Expand Up @@ -1433,9 +1433,12 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
! Compute instantaneous tidal velocities and apply frequency-dependent drag.
! Note that the filtered velocities are only updated during the current predictor step,
! and are calculated using the barotropic velocity from the previous correction step.
if (CS%use_filter) then
call Filt_accum(ubt(G%IsdB:G%IedB,G%jsd:G%jed), ufilt, CS%Time, US, CS%Filt_CS_u)
call Filt_accum(vbt(G%isd:G%ied,G%JsdB:G%JedB), vfilt, CS%Time, US, CS%Filt_CS_v)
endif

if (CS%use_filter .and. CS%linear_freq_drag) then
call Filt_accum(ubt, ufilt, CS%Time, US, CS%Filt_CS_u)
call Filt_accum(vbt, vfilt, CS%Time, US, CS%Filt_CS_v)
call wave_drag_calc(ufilt, vfilt, Drag_u, Drag_v, G, CS%Drag_CS)
!$OMP do
do j=js,je ; do I=is-1,ie
Expand All @@ -1461,8 +1464,6 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
Drag_v(i,J) = 0.0
endif
enddo ; enddo
else
Drag_u(:,:) = 0.0 ; Drag_v(:,:) = 0.0
endif

if ((Isq > is-1) .or. (Jsq > js-1)) then
Expand Down Expand Up @@ -2090,12 +2091,12 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv-1,iev+1
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * &
((Cor_v(i,J) + PFv(i,J)) - (vbt(i,J)*Rayleigh_v(i,J) + Drag_v(i,J)))
((Cor_v(i,J) + PFv(i,J)) - vbt(i,J)*Rayleigh_v(i,J))
enddo ; enddo
else
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv-1,iev+1
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * (Cor_v(i,J) + PFv(i,J) - Drag_v(i,J))
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * (Cor_v(i,J) + PFv(i,J))
enddo ; enddo
endif

Expand Down Expand Up @@ -2168,13 +2169,13 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
!$OMP do schedule(static)
do j=jsv,jev ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * &
((Cor_u(I,j) + PFu(I,j)) - (ubt(I,j)*Rayleigh_u(I,j) + Drag_u(I,j)))
((Cor_u(I,j) + PFu(I,j)) - ubt(I,j)*Rayleigh_u(I,j))
enddo ; enddo
!$OMP end do nowait
else
!$OMP do schedule(static)
do j=jsv,jev ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * (Cor_u(I,j) + PFu(I,j) - Drag_u(I,j))
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * (Cor_u(I,j) + PFu(I,j))
enddo ; enddo
!$OMP end do nowait
endif
Expand Down Expand Up @@ -2245,12 +2246,12 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
!$OMP do schedule(static)
do j=jsv-1,jev+1 ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * &
((Cor_u(I,j) + PFu(I,j)) - (ubt(I,j)*Rayleigh_u(I,j) + Drag_u(I,j)))
((Cor_u(I,j) + PFu(I,j)) - ubt(I,j)*Rayleigh_u(I,j))
enddo ; enddo
else
!$OMP do schedule(static)
do j=jsv-1,jev+1 ; do I=isv-1,iev
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * (Cor_u(I,j) + PFu(I,j) - Drag_u(I,j))
u_accel_bt(I,j) = u_accel_bt(I,j) + wt_accel(n) * (Cor_u(I,j) + PFu(I,j))
enddo ; enddo
endif

Expand Down Expand Up @@ -2334,13 +2335,13 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv,iev
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * &
((Cor_v(i,J) + PFv(i,J)) - (vbt(i,J)*Rayleigh_v(i,J) + Drag_v(i,J)))
((Cor_v(i,J) + PFv(i,J)) - vbt(i,J)*Rayleigh_v(i,J))
enddo ; enddo
!$OMP end do nowait
else
!$OMP do schedule(static)
do J=jsv-1,jev ; do i=isv,iev
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * (Cor_v(i,J) + PFv(i,J) - Drag_v(i,J))
v_accel_bt(i,J) = v_accel_bt(i,J) + wt_accel(n) * (Cor_v(i,J) + PFv(i,J))
enddo ; enddo
!$OMP end do nowait
endif
Expand Down Expand Up @@ -2645,6 +2646,17 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
enddo ; enddo
endif

if (CS%use_filter .and. CS%linear_freq_drag) then ! Apply frequency-dependent drag
!$OMP do
do j=js,je ; do I=is-1,ie
u_accel_bt(I,j) = u_accel_bt(I,j) - Drag_u(I,j)
enddo ; enddo
!$OMP do
do J=js-1,je ; do i=is,ie
v_accel_bt(i,J) = v_accel_bt(i,J) - Drag_v(i,J)
enddo ; enddo
endif


if (id_clock_calc_post > 0) call cpu_clock_end(id_clock_calc_post)
if (id_clock_pass_post > 0) call cpu_clock_begin(id_clock_pass_post)
Expand Down Expand Up @@ -5011,10 +5023,12 @@ subroutine barotropic_init(u, v, h, eta, Time, G, GV, US, param_file, diag, CS,
endif ! CS%linear_wave_drag

! Initialize streaming band-pass filters and frequency-dependent drag
if (CS%use_filter .and. CS%linear_freq_drag) then
if (CS%use_filter) then
call Filt_init(param_file, US, CS%Filt_CS_u, restart_CS)
call Filt_init(param_file, US, CS%Filt_CS_v, restart_CS)
endif

if (CS%use_filter .and. CS%linear_freq_drag) then
if (.not.CS%linear_wave_drag .and. len_trim(wave_drag_file) > 0) then
inputdir = "." ; call get_param(param_file, mdl, "INPUTDIR", inputdir)
wave_drag_file = trim(slasher(inputdir))//trim(wave_drag_file)
Expand Down
22 changes: 11 additions & 11 deletions src/parameterizations/lateral/MOM_wave_drag.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,9 @@ module MOM_wave_drag

!> Control structure for the MOM_wave_drag module
type, public :: wave_drag_CS ; private
integer :: nf !< Number of filters to be used in the simulation
!>@{ Spatially varying, frequency-dependent drag coefficients [H T-1 ~> m s-1]
real, allocatable, dimension(:,:,:) :: coef_u, coef_v
!>@}
integer :: nf !< Number of filters to be used in the simulation
real, allocatable, dimension(:,:,:) :: coef_u !< frequency-dependent drag coefficients [H T-1 ~> m s-1]
real, allocatable, dimension(:,:,:) :: coef_v !< frequency-dependent drag coefficients [H T-1 ~> m s-1]
end type wave_drag_CS

contains
Expand Down Expand Up @@ -92,13 +91,14 @@ end subroutine wave_drag_init
subroutine wave_drag_calc(u, v, drag_u, drag_v, G, CS)
type(ocean_grid_type), intent(in) :: G !< The ocean's grid structure
type(wave_drag_CS), intent(in) :: CS !< Control structure of MOM_wave_drag
!>@{ Tidal velocities from the output of streaming band-pass filters [L T-1 ~> m s-1]
real, dimension(:,:,:), pointer, intent(in) :: u, v
!>@}
!>@{ Sum of products of tidal velocities and scaled frequency-dependent drag [L2 T-2 ~> m2 s-2]
real, dimension(G%IsdB:G%IedB,G%jsd:G%jed), intent(out) :: drag_u
real, dimension(G%isd:G%ied,G%JsdB:G%JedB), intent(out) :: drag_v
!>@}
real, dimension(:,:,:), pointer, intent(in) :: u !< Zonal velocity from the output of
!! streaming band-pass filters [L T-1 ~> m s-1]
real, dimension(:,:,:), pointer, intent(in) :: v !< Meridional velocity from the output of
!! streaming band-pass filters [L T-1 ~> m s-1]
real, dimension(G%IsdB:G%IedB,G%jsd:G%jed), intent(out) :: drag_u !< Sum of products of filtered velocities
!! and scaled frequency-dependent drag [L2 T-2 ~> m2 s-2]
real, dimension(G%isd:G%ied,G%JsdB:G%JedB), intent(out) :: drag_v !< Sum of products of filtered velocities
!! and scaled frequency-dependent drag [L2 T-2 ~> m2 s-2]

! Local variables
integer :: is, ie, js, je, i, j, k
Expand Down

0 comments on commit 99916d3

Please sign in to comment.