diff --git a/libraries/dsp/verify_pfb/hdllib.cfg b/libraries/dsp/verify_pfb/hdllib.cfg
index 360e737099233e58ef501d7a528865febd9c98cd..66bab97861d9fda3ffde307fe8c3488c1245e710 100644
--- a/libraries/dsp/verify_pfb/hdllib.cfg
+++ b/libraries/dsp/verify_pfb/hdllib.cfg
@@ -11,10 +11,12 @@ hdl_lib_technology =
 synth_files = 
 
 test_bench_files = 
-    tb_verify_pfb_wg.vhd 
+    tb_verify_pfb_response.vhd
+    tb_verify_pfb_wg.vhd
     tb_tb_verify_pfb_wg.vhd
-    
+
 regression_test_vhdl = 
+    tb_verify_pfb_response.vhd
     tb_verify_pfb_wg.vhd
 
 [modelsim_project_file]
diff --git a/libraries/dsp/verify_pfb/tb_verify_pfb_response.vhd b/libraries/dsp/verify_pfb/tb_verify_pfb_response.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..942cc3387c287bf89363d0797c9fb24a6a7b8f10
--- /dev/null
+++ b/libraries/dsp/verify_pfb/tb_verify_pfb_response.vhd
@@ -0,0 +1,493 @@
+-------------------------------------------------------------------------------
+--
+-- Copyright 2020
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+--     http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+--
+-------------------------------------------------------------------------------
+
+-------------------------------------------------------------------------------
+--
+-- Author: E. Kooistra
+-- Purpose: Test bench to investigate the impulse response of the poly phase filterbank (PFB).
+--          The main goal is to verify the order of the FIR coefficients.
+-- Description:
+--   . Use g_sel_pfb to select the APERTIF wpfb_unit_dev.vhd or LOFAR1 pfb2_unit.vhd as
+--     device under test (DUT).
+--   . The FIR coefficients are flipped per tap, so per set of N_fft = 1024 values. This is
+--     because the FIR coefficients are applied as a filter per FFT input (so using
+--     convolution), and not as a window function (using plain multiply).
+--
+-- Usage:
+--   > as 3 default, or as 12 for details
+--   manually add ref_coefs_arr, flip_coefs_arr, read_coefs_arr in case they are missing
+--   > run -all
+--   view PFIR coefficients via fil_re_scope in Wave Window in decimal radix and analogue format
+--
+
+LIBRARY ieee, common_lib, dp_lib, filter_lib, rTwoSDF_lib, fft_lib, wpfb_lib;
+LIBRARY pfs_lib, pft2_lib, pfb2_lib;
+USE IEEE.std_logic_1164.ALL;
+USE IEEE.numeric_std.ALL;
+USE IEEE.std_logic_textio.ALL;
+USE IEEE.math_real.ALL;
+USE std.textio.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE common_lib.tb_common_pkg.ALL;
+USE common_lib.tb_common_mem_pkg.ALL;
+USE dp_lib.dp_stream_pkg.ALL;
+-- APERTIF WPFB:
+USE filter_lib.fil_pkg.ALL; 
+USE rTwoSDF_lib.rTwoSDFPkg.ALL;
+USE fft_lib.fft_pkg.ALL;
+USE fft_lib.tb_fft_pkg.ALL;
+USE wpfb_lib.wpfb_pkg.ALL;
+-- LOFAR1 PFB2:
+USE pfs_lib.pfs_pkg.ALL;
+USE pft2_lib.pft_pkg.ALL;
+
+ENTITY tb_verify_pfb_response IS
+  GENERIC (
+    g_tb_index        : NATURAL := 0;   -- use g_tb_index to identify and separate print_str() loggings from multi tb 
+    -- PFB
+    g_sel_pfb         : STRING := "WPFB";  -- "WPFB" for APERTIF PFB, "PFB2" for LOFAR1 PBF
+    --g_sel_pfb         : STRING := "PFB2";
+
+    -- LOFAR2 WPFB
+    g_fil_coefs_file_prefix : STRING := "data/Coeffs16384Kaiser-quant_1wb";                     -- PFIR coefficients file access
+    --g_fil_coefs_file_prefix : STRING := "data/run_pfir_coeff_m_bypass_16taps_1024points_16b_1wb";   -- bypass PFIR
+    --g_fil_coefs_file_prefix : STRING := "data/run_pfir_coeff_m_fircls1_16taps_1024points_16b_1wb";   -- g_fil_coef_dat_w = 16 bit
+
+    -- LOFAR1 PFB2
+    g_pfir_coefs_file   : STRING := c_pfs_coefs_file  -- PFB2 "data/pfs_coefsbuf_1024.hex" = Coeffs16384Kaiser-quant.dat default from pfs_pkg.vhd
+
+  );
+END ENTITY tb_verify_pfb_response;
+
+ARCHITECTURE tb OF tb_verify_pfb_response IS
+
+  CONSTANT c_mm_clk_period      : TIME := 1 ns;
+  CONSTANT c_dp_clk_period      : TIME := 10 ns;
+
+  CONSTANT c_nof_wb_streams     : NATURAL := 1;
+  CONSTANT c_nof_blk_per_sync   : NATURAL := 20;
+  CONSTANT c_pfs_bypass         : BOOLEAN := g_fil_coefs_file_prefix = "data/run_pfir_coeff_m_bypass_16taps_1024points_16b_1wb";
+
+  CONSTANT c_fil_coefs_dat_file : STRING := g_fil_coefs_file_prefix(1 TO g_fil_coefs_file_prefix'LENGTH - 4) & ".dat";  -- strip _1wb
+
+  -- WPFB
+  -- type t_wpfb is record  
+  --   -- General parameters for the wideband poly phase filter
+  --   wb_factor         : natural;        -- = default 4, wideband factor
+  --   nof_points        : natural;        -- = 1024, N point FFT (Also the number of subbands for the filter part)
+  --   nof_chan          : natural;        -- = default 0, defines the number of channels (=time-multiplexed input signals): nof channels = 2**nof_chan
+  --   nof_wb_streams    : natural;        -- = 1, the number of parallel wideband streams. The filter coefficients are shared on every wb-stream. 
+  --   
+  --   -- Parameters for the poly phase filter
+  --   nof_taps          : natural;        -- = 16, the number of FIR taps per subband
+  --   fil_backoff_w     : natural;        -- = 0, number of bits for input backoff to avoid output overflow
+  --   fil_in_dat_w      : natural;        -- = 8, number of input bits
+  --   fil_out_dat_w     : natural;        -- = 16, number of output bits
+  --   coef_dat_w        : natural;        -- = 16, data width of the FIR coefficients
+  --                                     
+  --   -- Parameters for the FFT         
+  --   use_reorder       : boolean;        -- = false for bit-reversed output, true for normal output
+  --   use_fft_shift     : boolean;        -- = false for [0, pos, neg] bin frequencies order, true for [neg, 0, pos] bin frequencies order in case of complex input
+  --   use_separate      : boolean;        -- = false for complex input, true for two real inputs
+  --   fft_in_dat_w      : natural;        -- = 16, number of input bits
+  --   fft_out_dat_w     : natural;        -- = 13, number of output bits
+  --   fft_out_gain_w    : natural;        -- = 0, output gain factor applied after the last stage output, before requantization to out_dat_w
+  --   stage_dat_w       : natural;        -- = 18, number of bits that are used inter-stage
+  --   guard_w           : natural;        -- = 2
+  --   guard_enable      : boolean;        -- = true
+  --
+  --   -- Parameters for the statistics
+  --   stat_data_w       : positive;       -- = 56
+  --   stat_data_sz      : positive;       -- = 2
+  --   nof_blk_per_sync  : natural;        -- = 800000, number of FFT output blocks per sync interval
+  --
+  --   -- Pipeline parameters for both poly phase filter and FFT. These are heritaged from the filter and fft libraries.  
+  --   pft_pipeline      : t_fft_pipeline;     -- Pipeline settings for the pipelined FFT
+  --   fft_pipeline      : t_fft_pipeline;     -- Pipeline settings for the parallel FFT
+  --   fil_pipeline      : t_fil_ppf_pipeline; -- Pipeline settings for the filter units 
+  -- end record;
+
+  --constant c_wpfb_lofar2_subbands_dts_18b : t_wpfb := (1, 1024, 0, 6,
+  --                                                     16, 1, 14, 23, 16,
+  --                                                     true, false, true, 23, 18, 1, 24, 1, true, 54, 2, 195313,
+  --                                                     c_fft_pipeline, c_fft_pipeline, c_fil_ppf_pipeline);
+  CONSTANT c_wpfb : t_wpfb := (1, 1024, 0, c_nof_wb_streams,
+                               16, 1, 14, 23, 16,
+                               true, false, true, 23, 18, 1, 24, 1, true, 54, 2, c_nof_blk_per_sync,
+                               c_fft_pipeline, c_fft_pipeline, c_fil_ppf_pipeline);
+                               
+  CONSTANT c_N_fft              : NATURAL := c_wpfb.nof_points;
+  CONSTANT c_N_blk              : NATURAL := c_wpfb.nof_blk_per_sync;  -- nof FFT blocks per sync interval
+  CONSTANT c_N_taps             : NATURAL := c_wpfb.nof_taps;
+  CONSTANT c_nof_coefs          : NATURAL := c_N_taps * c_N_fft;
+  CONSTANT c_nof_channels       : NATURAL := 2**c_wpfb.nof_chan;       -- = 2**0 = 1, so no time multiplexing of inputs
+  CONSTANT c_nof_sync           : NATURAL := 2;                        -- nof sync intervals to simulate
+  
+  -- BSN source
+  CONSTANT c_bsn_w              : NATURAL := 64;
+  
+  -- ADC
+  CONSTANT c_W_adc              : NATURAL := c_wpfb.fil_in_dat_w;
+
+  -- TB
+  SIGNAL bs_end                 : STD_LOGIC := '0';
+  SIGNAL tb_end                 : STD_LOGIC := '0';
+  SIGNAL mm_rst                 : STD_LOGIC;
+  SIGNAL mm_clk                 : STD_LOGIC := '0';
+  SIGNAL dp_rst                 : STD_LOGIC;
+  SIGNAL dp_clk                 : STD_LOGIC := '0';
+
+  -- Input
+  SIGNAL bs_sosi                : t_dp_sosi;
+  
+  SIGNAL impulse_data           : STD_LOGIC_VECTOR(c_W_adc-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL impulse_cnt            : NATURAL := 0;
+  
+  SIGNAL in_sosi_arr            : t_dp_sosi_arr(0 DOWNTO 0);
+  SIGNAL in_sosi                : t_dp_sosi;
+  SIGNAL in_a_scope             : INTEGER := 0;   -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL in_b_scope             : INTEGER := 0;   -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL in_val                 : STD_LOGIC;
+  SIGNAL in_val_cnt_per_sop     : NATURAL := 0;   -- count valid samples per block
+  SIGNAL in_val_cnt_per_sync    : NATURAL := 0;   -- count valid samples per sync interval
+  SIGNAL in_blk_cnt             : NATURAL := 0;   -- count blocks per sync interval
+  
+  -- Filter coefficients
+  SIGNAL ref_coefs_arr          : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0);   -- = PFIR coef read from g_fil_coefs_file_prefix file
+  SIGNAL flip_coefs_arr         : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0);   -- = PFIR coef from g_fil_coefs_file_prefix flipped per tap
+  SIGNAL read_coefs_arr         : t_integer_arr(c_nof_coefs-1 downto 0) := (OTHERS=>0);   -- = PFIR coef read via MM from the coefs memories
+
+  SIGNAL ram_fil_coefs_mosi     : t_mem_mosi := c_mem_mosi_rst;
+  SIGNAL ram_fil_coefs_miso     : t_mem_miso;
+
+  -- Filter output
+  SIGNAL fil_sosi_arr           : t_dp_sosi_arr(0 DOWNTO 0);
+  SIGNAL fil_sosi               : t_dp_sosi;
+  SIGNAL fil_re_scope           : INTEGER := 0;   -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL fil_im_scope           : INTEGER := 0;   -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL fil_val                : STD_LOGIC;
+  SIGNAL fil_val_cnt_per_sop    : NATURAL := 0;   -- count valid samples per block
+  SIGNAL fil_val_cnt_per_sync   : NATURAL := 0;   -- count valid samples per sync interval
+  SIGNAL fil_blk_cnt            : NATURAL := 0;   -- count blocks per sync interval
+  
+  -- Output
+  SIGNAL out_sosi_arr           : t_dp_sosi_arr(0 DOWNTO 0);
+  SIGNAL out_sosi               : t_dp_sosi;
+  SIGNAL out_re                 : INTEGER;
+  SIGNAL out_im                 : INTEGER;
+  SIGNAL out_power              : REAL;
+  SIGNAL out_phase              : REAL;
+  SIGNAL out_val                : STD_LOGIC;
+  SIGNAL out_val_cnt            : NATURAL := 0;
+  SIGNAL out_blk_cnt            : NATURAL := 0;
+  
+  SIGNAL out_val_a              : STD_LOGIC;  -- for real A
+  SIGNAL out_val_b              : STD_LOGIC;  -- for real B
+  SIGNAL out_channel            : NATURAL := 0;
+  SIGNAL out_cnt                : NATURAL := 0;
+  SIGNAL out_bin_cnt            : NATURAL := 0;
+  SIGNAL out_bin                : NATURAL := 0;
+  
+  SIGNAL reg_out_sosi           : t_dp_sosi;
+  SIGNAL reg_out_re_a_scope     : INTEGER := 0;  -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL reg_out_im_a_scope     : INTEGER := 0;  -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL reg_out_power_a_scope  : REAL := 0.0;
+  SIGNAL reg_out_phase_a_scope  : REAL := 0.0;
+  SIGNAL reg_out_re_b_scope     : INTEGER := 0;  -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL reg_out_im_b_scope     : INTEGER := 0;  -- init at 0 to fit automatic analog scaling in Wave Window
+  SIGNAL reg_out_power_b_scope  : REAL := 0.0;
+  SIGNAL reg_out_phase_b_scope  : REAL := 0.0;
+  SIGNAL reg_out_val_a          : STD_LOGIC;
+  SIGNAL reg_out_val_b          : STD_LOGIC;
+  SIGNAL reg_out_val            : STD_LOGIC;
+  SIGNAL reg_out_bin            : NATURAL := 0;
+  SIGNAL reg_out_blk_cnt        : NATURAL := 0;
+
+BEGIN
+
+  mm_clk <= (NOT mm_clk) OR tb_end AFTER c_mm_clk_period/2;
+  dp_clk <= (NOT dp_clk) OR tb_end AFTER c_dp_clk_period/2;
+  mm_rst <= '1', '0' AFTER c_mm_clk_period*7;
+  dp_rst <= '1', '0' AFTER c_dp_clk_period*7;
+  
+  -----------------------------------------------------------------------------
+  -- Stimuli
+  -----------------------------------------------------------------------------  
+  
+  p_run_test : PROCESS
+  BEGIN
+    -- Wait for stimuli to finish
+    proc_common_wait_until_high(dp_clk, bs_end);
+
+    tb_end <= '1';
+    WAIT;
+  END PROCESS;
+  
+  p_bs_sosi : PROCESS
+  BEGIN
+    bs_sosi <= c_dp_sosi_rst;
+    proc_common_wait_some_cycles(dp_clk, c_N_fft);
+    -- Start BSN
+    bs_sosi.valid <= '1';
+    FOR K IN 0 TO c_nof_sync LOOP  -- simulate one input sync interval extra to have c_nof_sync output sync intervals
+      bs_sosi.sync <= '1';
+      FOR J IN 0 TO c_N_blk-1 LOOP
+        bs_sosi.sop <= '1';
+        FOR I IN 0 TO c_N_fft-1 LOOP
+          IF I=c_N_fft-1 THEN
+            bs_sosi.eop <= '1';
+          END IF;
+          WAIT UNTIL rising_edge(dp_clk);
+          bs_sosi.sync <= '0';
+          bs_sosi.sop <= '0';
+          bs_sosi.eop <= '0';
+          IF bs_sosi.eop='1' THEN
+            bs_sosi.bsn <= INCR_UVEC(bs_sosi.bsn, 1);
+          END IF;
+        END LOOP;
+      END LOOP;
+    END LOOP;
+    bs_sosi.valid <= '0';
+    bs_end <= '1';
+    WAIT;
+  END PROCESS;
+  
+  p_impulse : PROCESS(dp_clk)
+  BEGIN
+    -- Create impulse during one block every 20 blocks, where 20 > c_N_taps
+    IF rising_edge(dp_clk) THEN
+      IF bs_sosi.eop='1' THEN
+        -- raise impulse for one block
+        IF impulse_cnt=0 THEN
+          impulse_data <= TO_SVEC(2**(c_W_adc-2), c_W_adc);  -- 0.5 * full scale impulse that will be active at sop (= after eop)
+        ELSE
+          impulse_data <= TO_SVEC(0, c_W_adc);
+        END IF;
+        -- maintain impulse period
+        IF impulse_cnt=20 THEN
+          impulse_cnt <= 0;
+        ELSE
+          impulse_cnt <= impulse_cnt + 1;
+        END IF;
+      END IF;
+    END IF;
+  END PROCESS;
+
+  p_in_sosi : PROCESS(bs_sosi)
+  BEGIN
+    -- DUT input
+    in_sosi    <= bs_sosi;
+    -- Use impulse_data at real input to view PFIR coefficients in impulse response in fil_re_scope in Wave Window
+    in_sosi.re <= RESIZE_DP_DSP_DATA(impulse_data);
+    in_sosi.im <= TO_DP_DSP_DATA(0);
+  END PROCESS;
+  
+  in_a_scope <= TO_SINT(in_sosi.re);
+  in_b_scope <= TO_SINT(in_sosi.im);
+  in_val <= in_sosi.valid;
+
+  ---------------------------------------------------------------
+  -- Read and verify FIR coefficients (similar as in tb_fil_ppf_single.vhd)
+  ---------------------------------------------------------------
+
+  gen_mm_wpfb : IF g_sel_pfb="WPFB" GENERATE
+    p_get_coefs_ref : PROCESS
+    begin
+      -- Read all coeffs from coefs file
+      proc_common_read_integer_file(c_fil_coefs_dat_file, 0, c_nof_coefs, 1, ref_coefs_arr);
+      wait for 1 ns;
+      -- Reverse the coeffs per tap
+      for J in 0 to c_N_taps-1 loop
+        for I in 0 to c_N_fft-1 loop
+          flip_coefs_arr(J*c_N_fft + c_N_fft-1-I) <= ref_coefs_arr(J*c_N_fft + I);
+        end loop;
+      end loop;
+      wait;
+    end process;
+
+    p_read_coefs_from_mm : process
+      constant c_mif_coef_mem_addr_w : natural := ceil_log2(c_N_fft);
+      constant c_mif_coef_mem_span   : natural := 2**c_mif_coef_mem_addr_w;  -- mif coef mem span for one tap
+
+      variable v_mif_base    : natural;
+      variable v_I           : natural := 0;
+    begin
+      ram_fil_coefs_mosi <= c_mem_mosi_rst;
+      proc_common_wait_until_low(mm_clk, mm_rst);
+      proc_common_wait_some_cycles(mm_clk, 10);
+
+      for J in 0 to c_N_taps-1 loop
+        v_mif_base := J*c_mif_coef_mem_span;
+        for I in 0 to c_N_fft-1 loop
+          proc_mem_mm_bus_rd(v_mif_base + I, mm_clk, ram_fil_coefs_miso, ram_fil_coefs_mosi);
+          proc_mem_mm_bus_rd_latency(1, mm_clk);
+          read_coefs_arr(v_I) <= TO_SINT(ram_fil_coefs_miso.rddata(c_wpfb.coef_dat_w-1 DOWNTO 0));
+          v_I := v_I + 1;
+        end loop;
+      end loop;
+      proc_common_wait_some_cycles(mm_clk, 1);
+      assert read_coefs_arr = flip_coefs_arr report "Coefs file does not match coefs read via MM" severity error;
+      wait;
+    end process;
+  END GENERATE;
+
+  ---------------------------------------------------------------
+  -- DUT = Device Under Test
+  ---------------------------------------------------------------
+  
+  in_sosi_arr(0) <= in_sosi;
+
+  -- DUT = APERTIF WFPB
+  dut_wpfb_unit_dev : IF g_sel_pfb="WPFB" GENERATE
+    u_wpfb_unit_dev : ENTITY wpfb_lib.wpfb_unit_dev
+    GENERIC MAP (
+      g_wpfb              => c_wpfb,
+      g_coefs_file_prefix => g_fil_coefs_file_prefix
+    )
+    PORT MAP (
+      dp_rst             => dp_rst,
+      dp_clk             => dp_clk,
+      mm_rst             => mm_rst,
+      mm_clk             => mm_clk,
+      ram_fil_coefs_mosi => ram_fil_coefs_mosi,
+      ram_fil_coefs_miso => ram_fil_coefs_miso,
+      in_sosi_arr        => in_sosi_arr,
+      fil_sosi_arr       => fil_sosi_arr,
+      out_sosi_arr       => out_sosi_arr
+    );
+  END GENERATE;
+  
+  -- DUT = LOFAR1 WFPB
+  dut_pfb2_unit : IF g_sel_pfb="PFB2" GENERATE
+    u_pfb2_unit : ENTITY pfb2_lib.pfb2_unit
+    GENERIC MAP (
+      g_nof_streams     => 1,   -- number of pfb2 instances, 1 pfb2 per stream
+      g_nof_points      => c_wpfb.nof_points,
+  
+      -- pfs
+      g_pfs_bypass      => c_pfs_bypass,
+      g_pfs_nof_taps    => c_wpfb.nof_taps,
+      g_pfs_in_dat_w    => c_wpfb.fil_in_dat_w,
+      g_pfs_out_dat_w   => c_wpfb.stage_dat_w,
+      g_pfs_coef_dat_w  => c_wpfb.coef_dat_w,
+      g_pfs_coefs_file  => g_pfir_coefs_file,
+    
+      -- pft2
+      g_pft_mode        => PFT_MODE_REAL2,
+      g_pft_switch_en   => '0',
+      g_pft_out_dat_w   => c_wpfb.fft_out_dat_w,
+      g_pft_stage_dat_w => c_wpfb.stage_dat_w,
+      
+      -- sst
+      g_sst_data_w      => c_wpfb.stat_data_w,
+      g_sst_data_sz     => c_wpfb.stat_data_sz
+    )
+    PORT MAP (
+      dp_rst            => dp_rst,
+      dp_clk            => dp_clk,
+      mm_rst            => mm_rst,
+      mm_clk            => mm_clk,
+      in_sosi_arr       => in_sosi_arr,
+      fil_sosi_arr      => fil_sosi_arr,
+      out_sosi_arr      => out_sosi_arr
+    );
+  END GENERATE;
+  
+  out_sosi <= out_sosi_arr(0);
+
+  ---------------------------------------------------------------
+  -- FIR filter output
+  ---------------------------------------------------------------
+
+  -- Append sync, sop, eop to fil_sosi
+  p_fil_blk_cnt : PROCESS(dp_clk)
+  BEGIN
+    IF rising_edge(dp_clk) THEN
+      -- FIR filter output:
+      IF fil_sosi.eop='1' THEN
+        IF fil_blk_cnt = c_N_blk-1 THEN
+          fil_blk_cnt <= 0;
+        ELSE
+          fil_blk_cnt <= fil_blk_cnt + 1;
+        END IF;
+      END IF;
+    END IF;
+  END PROCESS;
+
+  p_fil_sosi : PROCESS(fil_sosi_arr, fil_val_cnt_per_sop)
+  BEGIN
+    fil_sosi <= fil_sosi_arr(0);
+    -- Add sync, sop and eop to fil_sosi for tb
+    fil_sosi.sync <= '0';
+    fil_sosi.sop <= '0';
+    fil_sosi.eop <= '0';
+    IF fil_sosi_arr(0).valid='1' THEN
+      IF fil_val_cnt_per_sop=0 THEN
+        IF fil_blk_cnt=0 THEN
+          fil_sosi.sync <= '1';
+        END IF;
+        fil_sosi.sop <= '1';
+      END IF;
+      IF fil_val_cnt_per_sop=c_N_fft-1 THEN
+        fil_sosi.eop <= '1';
+      END IF;
+    END IF;
+  END PROCESS;
+
+  fil_re_scope <= TO_SINT(fil_sosi.re);
+  fil_im_scope <= TO_SINT(fil_sosi.im);
+  fil_val <= fil_sosi.valid;
+  
+  ---------------------------------------------------------------
+  -- FFT output
+  ---------------------------------------------------------------
+  
+  out_re    <= TO_SINT(out_sosi.re);
+  out_im    <= TO_SINT(out_sosi.im);
+  out_power <= COMPLEX_RADIUS(out_re, out_im);
+  out_phase <= COMPLEX_PHASE(out_re, out_im);
+  out_val   <= out_sosi.valid;
+
+  out_val_cnt <= out_val_cnt + 1 WHEN rising_edge(dp_clk) AND out_val='1' ELSE out_val_cnt;
+
+  out_blk_cnt <= out_blk_cnt / c_N_fft;
+    
+  proc_fft_out_control(c_wpfb.wb_factor, c_N_fft, c_nof_channels, c_wpfb.use_reorder, c_wpfb.use_fft_shift, c_wpfb.use_separate,
+                       out_val_cnt, out_val, out_val_a, out_val_b, out_channel, out_bin, out_bin_cnt);
+
+  -- clock out_sosi to hold output for A and for B
+  reg_out_val_a    <= out_val_a   WHEN rising_edge(dp_clk);
+  reg_out_val_b    <= out_val_b   WHEN rising_edge(dp_clk);
+  reg_out_val      <= out_val     WHEN rising_edge(dp_clk);
+  reg_out_bin      <= out_bin     WHEN rising_edge(dp_clk);
+  reg_out_blk_cnt  <= out_blk_cnt WHEN rising_edge(dp_clk);
+  
+  reg_out_sosi          <= out_sosi  WHEN rising_edge(dp_clk);
+  reg_out_re_a_scope    <= out_re    WHEN rising_edge(dp_clk) AND out_val_a='1';
+  reg_out_im_a_scope    <= out_im    WHEN rising_edge(dp_clk) AND out_val_a='1';
+  reg_out_power_a_scope <= out_power WHEN rising_edge(dp_clk) AND out_val_a='1';
+  reg_out_phase_a_scope <= out_phase WHEN rising_edge(dp_clk) AND out_val_a='1';
+  reg_out_re_b_scope    <= out_re    WHEN rising_edge(dp_clk) AND out_val_b='1';
+  reg_out_im_b_scope    <= out_im    WHEN rising_edge(dp_clk) AND out_val_b='1';
+  reg_out_power_b_scope <= out_power WHEN rising_edge(dp_clk) AND out_val_b='1';
+  reg_out_phase_b_scope <= out_phase WHEN rising_edge(dp_clk) AND out_val_b='1';
+
+end tb;