Skip to content

Commit a164f63

Browse files
c2xuTheresa Morrison
authored andcommitted
Streaming filter (NOAA-GFDL#675)
In the MOM_streaming_filter module, a system of two coupled ODEs is configured as a streaming band-pass filter that takes the broadband model output as the input and returns the filtered signal at a user specified tidal frequency as the output. It is capable of detecting the instantaneous tidal signals while the model is running, and can be used to impose frequency-dependent wave drag or to de-tide model output. An example of filtering the M2 and K1 barotropic velocities is provided in the MOM_barotropic module. Added runtime flags for the M2 and K1 filters. Simplified the code by removing the control structure of the linked list, and now each filter has its own control structure. Using hor_index_type argument to avoid calculation in halo regions.
1 parent a5e66eb commit a164f63

File tree

2 files changed

+189
-0
lines changed

2 files changed

+189
-0
lines changed

src/core/MOM_barotropic.F90

Lines changed: 70 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,8 @@ module MOM_barotropic
2626
use MOM_restart, only : query_initialized, MOM_restart_CS
2727
use MOM_self_attr_load, only : scalar_SAL_sensitivity
2828
use MOM_self_attr_load, only : SAL_CS
29+
use MOM_streaming_filter, only : Filt_register, Filt_accum, Filter_CS
30+
use MOM_tidal_forcing, only : tidal_frequency
2931
use MOM_time_manager, only : time_type, real_to_time, operator(+), operator(-)
3032
use MOM_unit_scaling, only : unit_scale_type
3133
use MOM_variables, only : BT_cont_type, alloc_bt_cont_type
@@ -248,6 +250,10 @@ module MOM_barotropic
248250
logical :: linearized_BT_PV !< If true, the PV and interface thicknesses used
249251
!! in the barotropic Coriolis calculation is time
250252
!! invariant and linearized.
253+
logical :: use_filter_m2 !< If true, apply streaming band-pass filter for detecting
254+
!! instantaneous tidal signals.
255+
logical :: use_filter_k1 !< If true, apply streaming band-pass filter for detecting
256+
!! instantaneous tidal signals.
251257
logical :: use_wide_halos !< If true, use wide halos and march in during the
252258
!! barotropic time stepping for efficiency.
253259
logical :: clip_velocity !< If true, limit any velocity components that are
@@ -291,6 +297,10 @@ module MOM_barotropic
291297
type(hor_index_type), pointer :: debug_BT_HI => NULL() !< debugging copy of horizontal index_type
292298
type(SAL_CS), pointer :: SAL_CSp => NULL() !< Control structure for SAL
293299
type(harmonic_analysis_CS), pointer :: HA_CSp => NULL() !< Control structure for harmonic analysis
300+
type(Filter_CS) :: Filt_CS_um2, & !< Control structures for the M2 streaming filter
301+
Filt_CS_vm2, & !< Control structures for the M2 streaming filter
302+
Filt_CS_uk1, & !< Control structures for the K1 streaming filter
303+
Filt_CS_vk1 !< Control structures for the K1 streaming filter
294304
logical :: module_is_initialized = .false. !< If true, module has been initialized
295305

296306
integer :: isdw !< The lower i-memory limit for the wide halo arrays.
@@ -598,6 +608,8 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
598608
DCor_v, & ! An averaged total thickness at v points [H ~> m or kg m-2].
599609
Datv ! Basin depth at v-velocity grid points times the x-grid
600610
! spacing [H L ~> m2 or kg m-1].
611+
real, dimension(:,:), pointer :: um2, uk1, vm2, vk1
612+
! M2 and K1 velocities from the output of streaming filters [m s-1]
601613
real, target, dimension(SZIW_(CS),SZJW_(CS)) :: &
602614
eta, & ! The barotropic free surface height anomaly or column mass
603615
! anomaly [H ~> m or kg m-2]
@@ -1586,6 +1598,17 @@ subroutine btstep(U_in, V_in, eta_in, dt, bc_accel_u, bc_accel_v, forces, pbce,
15861598
endif ; enddo ; enddo
15871599
endif
15881600

1601+
! Here is an example of how the filter equations are time stepped to determine the M2 and K1 velocities.
1602+
! The filters are initialized and registered in subroutine barotropic_init.
1603+
if (CS%use_filter_m2) then
1604+
call Filt_accum(ubt, um2, CS%Time, US, CS%Filt_CS_um2)
1605+
call Filt_accum(vbt, vm2, CS%Time, US, CS%Filt_CS_vm2)
1606+
endif
1607+
if (CS%use_filter_k1) then
1608+
call Filt_accum(ubt, uk1, CS%Time, US, CS%Filt_CS_uk1)
1609+
call Filt_accum(vbt, vk1, CS%Time, US, CS%Filt_CS_vk1)
1610+
endif
1611+
15891612
! Zero out the arrays for various time-averaged quantities.
15901613
if (find_etaav) then
15911614
!$OMP do
@@ -5247,6 +5270,8 @@ subroutine register_barotropic_restarts(HI, GV, US, param_file, CS, restart_CS)
52475270
type(vardesc) :: vd(3)
52485271
character(len=40) :: mdl = "MOM_barotropic" ! This module's name.
52495272
integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
5273+
real :: am2, ak1 !< Bandwidth parameters of the M2 and K1 streaming filters [nondim]
5274+
real :: om2, ok1 !< Target frequencies of the M2 and K1 streaming filters [T-1 ~> s-1]
52505275

52515276
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed
52525277
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB
@@ -5259,6 +5284,33 @@ subroutine register_barotropic_restarts(HI, GV, US, param_file, CS, restart_CS)
52595284
"sum(u dh_dt) while also correcting for truncation errors.", &
52605285
default=.false., do_not_log=.true.)
52615286

5287+
call get_param(param_file, mdl, "STREAMING_FILTER_M2", CS%use_filter_m2, &
5288+
"If true, turn on streaming band-pass filter for detecting "//&
5289+
"instantaneous tidal signals.", default=.false.)
5290+
call get_param(param_file, mdl, "STREAMING_FILTER_K1", CS%use_filter_k1, &
5291+
"If true, turn on streaming band-pass filter for detecting "//&
5292+
"instantaneous tidal signals.", default=.false.)
5293+
call get_param(param_file, mdl, "FILTER_ALPHA_M2", am2, &
5294+
"Bandwidth parameter of the streaming filter targeting the M2 frequency. "//&
5295+
"Must be positive. To turn off filtering, set FILTER_ALPHA_M2 <= 0.0.", &
5296+
default=0.0, units="nondim", do_not_log=.not.CS%use_filter_m2)
5297+
call get_param(param_file, mdl, "FILTER_ALPHA_K1", ak1, &
5298+
"Bandwidth parameter of the streaming filter targeting the K1 frequency. "//&
5299+
"Must be positive. To turn off filtering, set FILTER_ALPHA_K1 <= 0.0.", &
5300+
default=0.0, units="nondim", do_not_log=.not.CS%use_filter_k1)
5301+
call get_param(param_file, mdl, "TIDE_M2_FREQ", om2, &
5302+
"Frequency of the M2 tidal constituent. "//&
5303+
"This is only used if TIDES and TIDE_M2"// &
5304+
" are true, or if OBC_TIDE_N_CONSTITUENTS > 0 and M2"// &
5305+
" is in OBC_TIDE_CONSTITUENTS.", units="s-1", default=tidal_frequency("M2"), &
5306+
scale=US%T_to_s, do_not_log=.true.)
5307+
call get_param(param_file, mdl, "TIDE_K1_FREQ", ok1, &
5308+
"Frequency of the K1 tidal constituent. "//&
5309+
"This is only used if TIDES and TIDE_K1"// &
5310+
" are true, or if OBC_TIDE_N_CONSTITUENTS > 0 and K1"// &
5311+
" is in OBC_TIDE_CONSTITUENTS.", units="s-1", default=tidal_frequency("K1"), &
5312+
scale=US%T_to_s, do_not_log=.true.)
5313+
52625314
ALLOC_(CS%ubtav(IsdB:IedB,jsd:jed)) ; CS%ubtav(:,:) = 0.0
52635315
ALLOC_(CS%vbtav(isd:ied,JsdB:JedB)) ; CS%vbtav(:,:) = 0.0
52645316
if (CS%gradual_BT_ICs) then
@@ -5287,6 +5339,24 @@ subroutine register_barotropic_restarts(HI, GV, US, param_file, CS, restart_CS)
52875339
call register_restart_field(CS%dtbt, "DTBT", .false., restart_CS, &
52885340
longname="Barotropic timestep", units="seconds", conversion=US%T_to_s)
52895341

5342+
! Initialize and register streaming filters
5343+
if (CS%use_filter_m2) then
5344+
if (am2 > 0.0 .and. om2 > 0.0) then
5345+
call Filt_register(am2, om2, 'u', HI, CS%Filt_CS_um2)
5346+
call Filt_register(am2, om2, 'v', HI, CS%Filt_CS_vm2)
5347+
else
5348+
CS%use_filter_m2 = .false.
5349+
endif
5350+
endif
5351+
if (CS%use_filter_k1) then
5352+
if (ak1 > 0.0 .and. ok1 > 0.0) then
5353+
call Filt_register(ak1, ok1, 'u', HI, CS%Filt_CS_uk1)
5354+
call Filt_register(ak1, ok1, 'v', HI, CS%Filt_CS_vk1)
5355+
else
5356+
CS%use_filter_k1 = .false.
5357+
endif
5358+
endif
5359+
52905360
end subroutine register_barotropic_restarts
52915361

52925362
!> \namespace mom_barotropic
Lines changed: 119 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,119 @@
1+
!> Streaming band-pass filter for detecting the instantaneous tidal signals in the simulation
2+
module MOM_streaming_filter
3+
4+
use MOM_error_handler, only : MOM_mesg, MOM_error, FATAL
5+
use MOM_hor_index, only : hor_index_type
6+
use MOM_time_manager, only : time_type, time_type_to_real
7+
use MOM_unit_scaling, only : unit_scale_type
8+
9+
implicit none ; private
10+
11+
public Filt_register, Filt_accum
12+
13+
#include <MOM_memory.h>
14+
15+
!> The control structure for storing the filter infomation of a particular field
16+
type, public :: Filter_CS ; private
17+
real :: a, & !< Parameter that determines the bandwidth [nondim]
18+
om, & !< Target frequency of the filter [T-1 ~> s-1]
19+
old_time = -1.0 !< The time of the previous accumulating step [T ~> s]
20+
real, allocatable, dimension(:,:) :: s1, & !< Dummy variable [A]
21+
u1 !< Filtered data [A]
22+
!>@{ Lower and upper bounds of input data
23+
integer :: is, ie, js, je
24+
!>@}
25+
end type Filter_CS
26+
27+
contains
28+
29+
!> This subroutine registers each of the fields to be filtered.
30+
subroutine Filt_register(a, om, grid, HI, CS)
31+
real, intent(in) :: a !< Parameter that determines the bandwidth [nondim]
32+
real, intent(in) :: om !< Target frequency of the filter [T-1 ~> s-1]
33+
character(len=*), intent(in) :: grid !< Horizontal grid location: h, u, or v
34+
type(hor_index_type), intent(in) :: HI !< Horizontal index type structure
35+
type(Filter_CS), intent(out) :: CS !< Control structure for the current field
36+
37+
! Local variables
38+
integer :: isd, ied, jsd, jed, IsdB, IedB, JsdB, JedB
39+
40+
if (a <= 0.0) call MOM_error(FATAL, "MOM_streaming_filter: bandwidth <= 0")
41+
if (om <= 0.0) call MOM_error(FATAL, "MOM_streaming_filter: target frequency <= 0")
42+
43+
CS%a = a
44+
CS%om = om
45+
46+
isd = HI%isd ; ied = HI%ied ; jsd = HI%jsd ; jed = HI%jed
47+
IsdB = HI%IsdB ; IedB = HI%IedB ; JsdB = HI%JsdB ; JedB = HI%JedB
48+
49+
select case (trim(grid))
50+
case ('h')
51+
allocate(CS%s1(isd:ied,jsd:jed)) ; CS%s1(:,:) = 0.0
52+
allocate(CS%u1(isd:ied,jsd:jed)) ; CS%u1(:,:) = 0.0
53+
CS%is = isd ; CS%ie = ied ; CS%js = jsd ; CS%je = jed
54+
case ('u')
55+
allocate(CS%s1(IsdB:IedB,jsd:jed)) ; CS%s1(:,:) = 0.0
56+
allocate(CS%u1(IsdB:IedB,jsd:jed)) ; CS%u1(:,:) = 0.0
57+
CS%is = IsdB ; CS%ie = IedB ; CS%js = jsd ; CS%je = jed
58+
case ('v')
59+
allocate(CS%s1(isd:ied,JsdB:JedB)) ; CS%s1(:,:) = 0.0
60+
allocate(CS%u1(isd:ied,JsdB:JedB)) ; CS%u1(:,:) = 0.0
61+
CS%is = isd ; CS%ie = ied ; CS%js = JsdB ; CS%je = JedB
62+
case default
63+
call MOM_error(FATAL, "MOM_streaming_filter: horizontal grid not supported")
64+
end select
65+
66+
end subroutine Filt_register
67+
68+
!> This subroutine timesteps the filter equations. It takes model output u at the current time step as the input,
69+
!! and returns tidal signal u1 as the output, which is the solution of a set of two ODEs (the filter equations).
70+
subroutine Filt_accum(u, u1, Time, US, CS)
71+
real, dimension(:,:), pointer, intent(out) :: u1 !< Output of the filter [A]
72+
type(time_type), intent(in) :: Time !< The current model time
73+
type(unit_scale_type), intent(in) :: US !< A dimensional unit scaling type
74+
type(Filter_CS), target, intent(inout) :: CS !< Control structure of the MOM_streaming_filter module
75+
real, dimension(CS%is:CS%ie,CS%js:CS%je), intent(in) :: u !< Input into the filter [A]
76+
77+
! Local variables
78+
real :: now, & !< The current model time [T ~> s]
79+
dt, & !< Time step size for the filter equations [T ~> s]
80+
c1, c2 !< Coefficients for the filter equations [nondim]
81+
integer :: i, j, is, ie, js, je
82+
83+
now = US%s_to_T * time_type_to_real(Time)
84+
is = CS%is ; ie = CS%ie ; js = CS%js ; je = CS%je
85+
86+
! Initialize u1
87+
if (CS%old_time < 0.0) then
88+
CS%old_time = now
89+
CS%u1(:,:) = u(:,:)
90+
endif
91+
92+
dt = now - CS%old_time
93+
CS%old_time = now
94+
95+
! Timestepping
96+
c1 = CS%om * dt
97+
c2 = 1.0 - CS%a * c1
98+
99+
do j=js,je ; do i=is,ie
100+
CS%s1(i,j) = c1 * CS%u1(i,j) + CS%s1(i,j)
101+
CS%u1(i,j) = -c1 * (CS%s1(i,j) - CS%a * u(i,j)) + c2 * CS%u1(i,j)
102+
enddo; enddo
103+
u1 => CS%u1
104+
105+
end subroutine Filt_accum
106+
107+
!> \namespace streaming_filter
108+
!!
109+
!! This module detects instantaneous tidal signals in the model output using a set of coupled ODEs (the filter
110+
!! equations), given the target frequency (om) and the bandwidth parameter (a) of the filter. At each timestep,
111+
!! the filter takes model output (u) as the input and returns a time series consisting of sinusoidal motions (u1)
112+
!! near its target frequency. The filtered tidal signals can be used to parameterize frequency-dependent drag, or
113+
!! to detide the model output. See Xu & Zaron (2024) for detail.
114+
!!
115+
!! Reference: Xu, C., & Zaron, E. D. (2024). Detecting instantaneous tidal signals in ocean models utilizing
116+
!! streaming band-pass filters. Journal of Advances in Modeling Earth Systems. Under review.
117+
118+
end module MOM_streaming_filter
119+

0 commit comments

Comments
 (0)