diff --git a/init_hdl.sh b/init_hdl.sh
index 8dfeb67292e7e6c6ddd95e950575a31ab534ffc3..1221c746daf36c56fd1fadd110c35be565f87b32 100644
--- a/init_hdl.sh
+++ b/init_hdl.sh
@@ -31,7 +31,7 @@
 if [[ "$_" == "${0}" ]]; then
     echo "ERROR: Use this command with '. ' or 'source '"
     sleep 1
-    exit
+    return
 fi
 
 # 
@@ -39,7 +39,7 @@ if [ -z "${ALTERA_DIR}" ]; then
     echo "== environ variable 'ALTERA_DIR' not set. =="
     echo "should be in your .bashrc file."
     echo "if it is your .bashrc file but not active run bash in your terminal"
-    exit
+    return
 fi
 
 # Figure out where this script is located and set environment variables accordingly
diff --git a/libraries/base/dp/src/vhdl/dp_fifo_fill_eop.vhd b/libraries/base/dp/src/vhdl/dp_fifo_fill_eop.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..dcebc6288bd85298d199de6da70e72779bedf1ac
--- /dev/null
+++ b/libraries/base/dp/src/vhdl/dp_fifo_fill_eop.vhd
@@ -0,0 +1,399 @@
+--------------------------------------------------------------------------------
+--
+-- Copyright (C) 2019
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- This program is free software: you can redistribute it and/or modify
+-- it under the terms of the GNU General Public License as published by
+-- the Free Software Foundation, either version 3 of the License, or
+-- (at your option) any later version.
+--
+-- This program is distributed in the hope that it will be useful,
+-- but WITHOUT ANY WARRANTY; without even the implied warranty of
+-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+-- GNU General Public License for more details.
+--
+-- You should have received a copy of the GNU General Public License
+-- along with this program.  If not, see <http://www.gnu.org/licenses/>.
+--
+--------------------------------------------------------------------------------
+
+-- Purpose:
+--   The FIFO starts outputting data when the output is ready and it has been
+--   filled with more than g_fifo_fill words or an eop signal has been received. 
+--   Given a fixed frame length, this is useful when the in_val is throttled while 
+--   the out_val should not be inactive valid between out_sop to out_eop. 
+--   This is necessary for frame transport over a PHY link without separate data 
+--   valid signal.
+-- Description:
+--   Modified version of dp_fifo_fill_core. In addition to a frame being available
+--   after the fifo has been filled sufficiently, a frame is also available when
+--   the in_eop has been received earlier than the specified g_fifo_fill. For
+--   more details, please consult the description of dp_fill_fifo_core.
+
+LIBRARY IEEE, common_lib, technology_lib;
+USE IEEE.std_logic_1164.ALL;
+USE IEEE.numeric_std.ALL;
+USE common_lib.common_pkg.ALL;
+USE work.dp_stream_pkg.ALL;
+USE technology_lib.technology_select_pkg.ALL;
+
+ENTITY dp_fifo_fill_eop IS
+  GENERIC (
+    g_technology     : NATURAL := c_tech_select_default;
+    g_use_dual_clock : BOOLEAN := FALSE;
+    g_data_w         : NATURAL := 16;
+    g_bsn_w          : NATURAL := 1;
+    g_empty_w        : NATURAL := 1;
+    g_channel_w      : NATURAL := 1;
+    g_error_w        : NATURAL := 1;
+    g_use_bsn        : BOOLEAN := FALSE;
+    g_use_empty      : BOOLEAN := FALSE;
+    g_use_channel    : BOOLEAN := FALSE;
+    g_use_error      : BOOLEAN := FALSE;
+    g_use_sync       : BOOLEAN := FALSE;
+    g_use_complex    : BOOLEAN := FALSE;  -- TRUE feeds the concatenated complex fields (im & re) through the FIFO instead of the data field.
+    g_fifo_fill      : NATURAL := 0;
+    g_fifo_size      : NATURAL := 256;    -- (32+2) * 256 = 1 M9K, g_data_w+2 for sop and eop
+    g_fifo_af_margin : NATURAL := 4;      -- Nof words below max (full) at which fifo is considered almost full
+    g_fifo_rl        : NATURAL := 1       -- use RL=0 for internal show ahead FIFO, default use RL=1 for internal normal FIFO
+  );
+  PORT (
+    wr_rst      : IN  STD_LOGIC;
+    wr_clk      : IN  STD_LOGIC;
+    rd_rst      : IN  STD_LOGIC;
+    rd_clk      : IN  STD_LOGIC;
+    -- Monitor FIFO filling
+    wr_ful      : OUT STD_LOGIC;  -- corresponds to the carry bit of wr_usedw when FIFO is full
+    wr_usedw    : OUT STD_LOGIC_VECTOR(ceil_log2(largest(g_fifo_size, g_fifo_fill + g_fifo_af_margin + 2))-1 DOWNTO 0);  -- = ceil_log2(c_fifo_size)-1 DOWNTO 0
+    rd_usedw    : OUT STD_LOGIC_VECTOR(ceil_log2(largest(g_fifo_size, g_fifo_fill + g_fifo_af_margin + 2))-1 DOWNTO 0);  -- = ceil_log2(c_fifo_size)-1 DOWNTO 0
+    rd_emp      : OUT STD_LOGIC;
+    -- MM control FIFO filling (assume 32 bit MM interface)
+    wr_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- = wr_usedw
+    rd_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- = rd_usedw
+    rd_fill_32b  : IN  STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := TO_UVEC(g_fifo_fill, c_word_w);
+    -- ST sink
+    snk_out     : OUT t_dp_siso;
+    snk_in      : IN  t_dp_sosi;
+    -- ST source
+    src_in      : IN  t_dp_siso;
+    src_out     : OUT t_dp_sosi
+  );
+END dp_fifo_fill_eop;
+
+
+ARCHITECTURE rtl OF dp_fifo_fill_eop IS
+
+  CONSTANT c_fifo_rl          : NATURAL := sel_a_b(g_fifo_fill=0, 1, g_fifo_rl);
+  CONSTANT c_fifo_fill_margin : NATURAL := g_fifo_af_margin + 2;  -- add +2 extra margin, with tb_dp_fifo_fill it follows that +1 is also enough to avoid almost full when fifo is operating near g_fifo_fill level
+  CONSTANT c_fifo_size        : NATURAL := largest(g_fifo_size, g_fifo_fill + c_fifo_fill_margin);
+  CONSTANT c_fifo_size_w      : NATURAL := ceil_log2(c_fifo_size);    -- = wr_usedw'LENGTH = rd_usedw'LENGTH
+  
+  -- The FIFO filling relies on framed data, so contrary to dp_fifo_sc the sop and eop need to be used.
+  CONSTANT c_use_ctrl  : BOOLEAN := TRUE;
+  
+  -- Define t_state as slv to avoid Modelsim warning "Nonresolved signal 'nxt_state' may have multiple sources". Due to that g_fifo_rl = 0 or 1 ar both supported.
+  --TYPE t_state IS (s_idle, s_fill, s_output, s_xoff);
+  CONSTANT s_idle    : STD_LOGIC_VECTOR(1 DOWNTO 0) := "00";
+  CONSTANT s_fill    : STD_LOGIC_VECTOR(1 DOWNTO 0) := "01";
+  CONSTANT s_output  : STD_LOGIC_VECTOR(1 DOWNTO 0) := "10";
+  CONSTANT s_xoff    : STD_LOGIC_VECTOR(1 DOWNTO 0) := "11";
+  
+  SIGNAL state       : STD_LOGIC_VECTOR(1 DOWNTO 0);  -- t_state
+  SIGNAL nxt_state   : STD_LOGIC_VECTOR(1 DOWNTO 0);  -- t_state
+  
+  SIGNAL xon_reg     : STD_LOGIC;
+  SIGNAL nxt_xon_reg : STD_LOGIC;
+  
+  SIGNAL rd_siso     : t_dp_siso;
+  SIGNAL rd_sosi     : t_dp_sosi := c_dp_sosi_rst;  -- initialize default values for unused sosi fields;
+  
+  SIGNAL wr_fifo_usedw  : STD_LOGIC_VECTOR(c_fifo_size_w-1 DOWNTO 0);  -- = wr_usedw'RANGE
+  SIGNAL rd_fifo_usedw  : STD_LOGIC_VECTOR(c_fifo_size_w-1 DOWNTO 0);  -- = rd_usedw'RANGE
+  SIGNAL rd_fill_ctrl   : STD_LOGIC_VECTOR(c_fifo_size_w-1 DOWNTO 0);  -- used to resize rd_fill_32b to actual maximum width
+
+  SIGNAL i_src_out   : t_dp_sosi;
+  SIGNAL nxt_src_out : t_dp_sosi;
+  
+  -- Signals for g_fifo_rl=1
+  SIGNAL hold_src_in  : t_dp_siso;
+  SIGNAL pend_src_out : t_dp_sosi;
+ 
+  SIGNAL received_eop : BOOLEAN := FALSE;
+  SIGNAL nxt_received_eop : BOOLEAN := FALSE;
+  
+BEGIN
+
+  -- Output monitor FIFO filling
+  wr_usedw <= wr_fifo_usedw;
+  rd_usedw <= rd_fifo_usedw;
+  
+  -- Control FIFO fill level
+  wr_usedw_32b <= RESIZE_UVEC(wr_fifo_usedw, c_word_w);
+  rd_usedw_32b <= RESIZE_UVEC(rd_fifo_usedw, c_word_w);
+  
+  rd_fill_ctrl <= rd_fill_32b(c_fifo_size_w-1 DOWNTO 0);
+
+  gen_dp_fifo_sc : IF g_use_dual_clock=FALSE GENERATE
+    u_dp_fifo_sc : ENTITY work.dp_fifo_sc
+    GENERIC MAP (
+      g_technology     => g_technology,
+      g_data_w         => g_data_w,
+      g_bsn_w          => g_bsn_w,
+      g_empty_w        => g_empty_w,
+      g_channel_w      => g_channel_w,
+      g_error_w        => g_error_w,
+      g_use_bsn        => g_use_bsn,
+      g_use_empty      => g_use_empty,
+      g_use_channel    => g_use_channel,
+      g_use_error      => g_use_error,
+      g_use_sync       => g_use_sync,
+      g_use_ctrl       => c_use_ctrl,
+      g_use_complex    => g_use_complex,
+      g_fifo_size      => c_fifo_size,
+      g_fifo_af_margin => g_fifo_af_margin,
+      g_fifo_rl        => c_fifo_rl
+    )
+    PORT MAP (
+      rst         => rd_rst,
+      clk         => rd_clk,
+      -- Monitor FIFO filling
+      wr_ful      => wr_ful,
+      usedw       => rd_fifo_usedw,
+      rd_emp      => rd_emp,
+      -- ST sink
+      snk_out     => snk_out,
+      snk_in      => snk_in,
+      -- ST source
+      src_in      => rd_siso,  -- for RL = 0 rd_siso.ready acts as read acknowledge, for RL = 1 rd_siso.ready acts as read request
+      src_out     => rd_sosi
+    );
+    
+    wr_fifo_usedw <= rd_fifo_usedw;
+  END GENERATE;
+  
+  gen_dp_fifo_dc : IF g_use_dual_clock=TRUE GENERATE
+    u_dp_fifo_dc : ENTITY work.dp_fifo_dc
+    GENERIC MAP (
+      g_technology     => g_technology,
+      g_data_w         => g_data_w,
+      g_bsn_w          => g_bsn_w,
+      g_empty_w        => g_empty_w,
+      g_channel_w      => g_channel_w,
+      g_error_w        => g_error_w,
+      g_use_bsn        => g_use_bsn,
+      g_use_empty      => g_use_empty,
+      g_use_channel    => g_use_channel,
+      g_use_error      => g_use_error,
+      g_use_sync       => g_use_sync,
+      g_use_ctrl       => c_use_ctrl,
+      --g_use_complex    => g_use_complex,
+      g_fifo_size      => c_fifo_size,
+      g_fifo_af_margin => g_fifo_af_margin,
+      g_fifo_rl        => c_fifo_rl
+    )
+    PORT MAP (
+      wr_rst      => wr_rst,
+      wr_clk      => wr_clk,
+      rd_rst      => rd_rst,
+      rd_clk      => rd_clk,
+      -- Monitor FIFO filling
+      wr_ful      => wr_ful,
+      wr_usedw    => wr_fifo_usedw,
+      rd_usedw    => rd_fifo_usedw,
+      rd_emp      => rd_emp,
+      -- ST sink
+      snk_out     => snk_out,
+      snk_in      => snk_in,
+      -- ST source
+      src_in      => rd_siso,  -- for RL = 0 rd_siso.ready acts as read acknowledge, -- for RL = 1 rd_siso.ready acts as read request
+      src_out     => rd_sosi
+    );
+  END GENERATE;
+    
+  no_fill : IF g_fifo_fill=0 GENERATE
+    rd_siso <= src_in;   -- SISO
+    src_out <= rd_sosi;  -- SOSI
+  END GENERATE;  -- no_fill
+  
+  gen_fill : IF g_fifo_fill>0 GENERATE
+  
+    src_out <= i_src_out;
+    
+    p_rd_clk: PROCESS(rd_clk, rd_rst)
+    BEGIN
+      IF rd_rst='1' THEN
+        xon_reg   <= '0';
+        state     <= s_idle;
+        i_src_out <= c_dp_sosi_rst;
+        received_eop <= FALSE;
+      ELSIF rising_edge(rd_clk) THEN
+        xon_reg   <= nxt_xon_reg;
+        state     <= nxt_state;
+        i_src_out <= nxt_src_out;
+        received_eop <= nxt_received_eop;
+      END IF;
+    END PROCESS;
+    
+    nxt_xon_reg <= src_in.xon;  -- register xon to easy timing closure
+      
+    gen_rl_0 : IF g_fifo_rl=0 GENERATE
+      p_state : PROCESS(state, rd_sosi, src_in, xon_reg, rd_fifo_usedw, rd_fill_ctrl, received_eop)
+      BEGIN
+        nxt_state <= state;
+        
+        rd_siso <= src_in;  -- default acknowledge (RL=1) this input when output is ready
+        
+        -- The output register stage increase RL=0 to 1, so it matches RL = 1 for src_in.ready
+        nxt_src_out       <= rd_sosi;
+        nxt_src_out.valid <= '0';   -- default no output
+        nxt_src_out.sop   <= '0';
+        nxt_src_out.eop   <= '0';
+        nxt_src_out.sync  <= '0';
+
+        IF snk_in.eop = '1' THEN
+          nxt_received_eop <= TRUE;
+        ELSE
+          nxt_received_eop <= received_eop;
+        END IF;        
+
+        CASE state IS
+          WHEN s_idle =>
+            IF xon_reg='0' THEN
+              nxt_state <= s_xoff;
+            ELSE
+              -- read the FIFO until the sop is pending at the output, so discard any valid data between eop and sop
+              IF rd_sosi.sop='0' THEN
+                rd_siso <= c_dp_siso_rdy;   -- acknowledge (RL=0) this input independent of output ready
+              ELSE
+                rd_siso <= c_dp_siso_hold;  -- stop the input, hold the rd_sosi.sop at FIFO output (RL=0)
+                nxt_state <= s_fill;
+              END IF;
+            END IF;
+          WHEN s_fill =>
+            IF xon_reg='0' THEN
+              nxt_state <= s_xoff;
+            ELSE
+              -- stop reading until the FIFO has been filled sufficiently
+              IF UNSIGNED(rd_fifo_usedw)<UNSIGNED(rd_fill_ctrl) AND NOT received_eop THEN
+                rd_siso <= c_dp_siso_hold;  -- stop the input, hold the pend_src_out.sop
+              ELSE
+                -- if the output is ready, then start outputting the frame
+                IF src_in.ready='1' THEN
+                  nxt_src_out <= rd_sosi;  -- output sop that is still at FIFO output (RL=0)
+                  nxt_received_eop <= FALSE;
+                  nxt_state <= s_output;
+                END IF;
+              END IF;
+            END IF;
+          WHEN s_output =>
+            -- if the output is ready continue outputting the frame, ignore xon_reg during this frame
+            IF src_in.ready='1' THEN
+              nxt_src_out <= rd_sosi;  -- output valid
+              IF rd_sosi.eop='1' THEN
+                nxt_state <= s_idle;   -- output eop, so stop reading the FIFO
+              END IF;
+            END IF;
+          WHEN OTHERS => -- s_xoff
+            -- Flush the fill FIFO when xon='0'
+            rd_siso <= c_dp_siso_flush;
+            IF xon_reg='1' THEN
+              nxt_state <= s_idle;
+            END IF;
+        END CASE;
+        
+        -- Pass on frame level flow control
+        rd_siso.xon <= src_in.xon;
+      END PROCESS;
+    END GENERATE;  -- gen_rl_0
+    
+    gen_rl_1 : IF g_fifo_rl=1 GENERATE
+      -- Use dp_hold_input to get equivalent implementation with default RL=1 FIFO.
+      
+      -- Hold the sink input for source output
+      u_snk : ENTITY work.dp_hold_input
+      PORT MAP (
+        rst          => rd_rst,
+        clk          => rd_clk,
+        -- ST sink
+        snk_out      => rd_siso,       -- SISO ready
+        snk_in       => rd_sosi,       -- SOSI
+        -- ST source
+        src_in       => hold_src_in,   -- SISO ready
+        next_src_out => OPEN,          -- SOSI
+        pend_src_out => pend_src_out,
+        src_out_reg  => i_src_out
+      );
+      
+      p_state : PROCESS(state, src_in, xon_reg, pend_src_out, rd_fifo_usedw, rd_fill_ctrl, received_eop)
+      BEGIN
+        nxt_state <= state;
+        
+        hold_src_in <= src_in;  -- default request (RL=1) new input when output is ready
+        
+        -- The output register stage matches RL = 1 for src_in.ready
+        nxt_src_out       <= pend_src_out;
+        nxt_src_out.valid <= '0';          -- default no output
+        nxt_src_out.sop   <= '0';
+        nxt_src_out.eop   <= '0';
+        nxt_src_out.sync  <= '0';
+       
+        IF snk_in.eop = '1' THEN
+          nxt_received_eop <= TRUE;
+        ELSE
+          nxt_received_eop <= received_eop;
+        END IF;
+ 
+        CASE state IS
+          WHEN s_idle =>
+            IF xon_reg='0' THEN
+              nxt_state <= s_xoff;
+            ELSE
+              -- read the FIFO until the sop is pending at the output, so discard any valid data between eop and sop
+              IF pend_src_out.sop='0' THEN
+                hold_src_in <= c_dp_siso_rdy;   -- request (RL=1) new input independent of output ready
+              ELSE
+                hold_src_in <= c_dp_siso_hold;  -- stop the input, hold the pend_src_out.sop in dp_hold_input
+                nxt_state <= s_fill;
+              END IF;
+            END IF;
+          WHEN s_fill =>
+            IF xon_reg='0' THEN
+              nxt_state <= s_xoff;
+            ELSE
+              -- stop reading until the FIFO has been filled sufficiently
+              IF UNSIGNED(rd_fifo_usedw)<UNSIGNED(rd_fill_ctrl) AND NOT received_eop THEN
+                hold_src_in <= c_dp_siso_hold;  -- stop the input, hold the pend_src_out.sop
+              ELSE
+                -- if the output is ready, then start outputting the input frame
+                IF src_in.ready='1' THEN
+                  nxt_src_out <= pend_src_out;  -- output sop that is still pending in dp_hold_input
+                  nxt_received_eop <= FALSE;
+                  nxt_state <= s_output;
+                END IF;
+              END IF;
+            END IF;
+          WHEN s_output =>
+            -- if the output is ready continue outputting the input frame, ignore xon_reg during this frame
+            IF src_in.ready='1' THEN
+              nxt_src_out <= pend_src_out;  -- output valid
+              IF pend_src_out.eop='1' THEN
+                nxt_state <= s_idle;        -- output eop, so stop reading the FIFO
+              END IF;
+            END IF;
+          WHEN OTHERS => -- s_xon
+            -- Flush the fill FIFO when xon='0'
+            hold_src_in <= c_dp_siso_flush;
+            IF xon_reg='1' THEN
+              nxt_state <= s_idle;
+            END IF;
+        END CASE;
+        
+        -- Pass on frame level flow control
+        hold_src_in.xon <= src_in.xon;
+      END PROCESS;
+    END GENERATE;  -- gen_rl_1
+    
+  END GENERATE;  -- gen_fill
+END rtl;
diff --git a/libraries/base/dp/tb/vhdl/tb_dp_fifo_fill_eop.vhd b/libraries/base/dp/tb/vhdl/tb_dp_fifo_fill_eop.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..a6dc8a1a3f9ecb805bd27cf984084b74ac31b1ab
--- /dev/null
+++ b/libraries/base/dp/tb/vhdl/tb_dp_fifo_fill_eop.vhd
@@ -0,0 +1,284 @@
+-------------------------------------------------------------------------------
+--
+-- Copyright (C) 2010
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- JIVE (Joint Institute for VLBI in Europe) <http://www.jive.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- This program is free software: you can redistribute it and/or modify
+-- it under the terms of the GNU General Public License as published by
+-- the Free Software Foundation, either version 3 of the License, or
+-- (at your option) any later version.
+--
+-- This program is distributed in the hope that it will be useful,
+-- but WITHOUT ANY WARRANTY; without even the implied warranty of
+-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+-- GNU General Public License for more details.
+--
+-- You should have received a copy of the GNU General Public License
+-- along with this program.  If not, see <http://www.gnu.org/licenses/>.
+--
+-------------------------------------------------------------------------------
+
+-- Purpose:
+--   Test bench for dp_fifo_fill_eop
+-- Description:
+--   The tb verifies the DUT using the old style proc_dp_count_en() with
+--   various stimuli for cnt_en and out_siso.ready.
+-- Remark:
+--   The frame level flow control via out_siso.xon is not tested, because it is
+--   fixed at '1'.
+-- Usage:
+-- > as 10
+-- > run -all
+-- . signal tb_end will stop the simulation by stopping the clk
+-- . the tb is self checking
+-- 
+LIBRARY IEEE, common_lib;
+USE IEEE.std_logic_1164.ALL;
+USE IEEE.numeric_std.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.tb_common_pkg.ALL;
+USE work.dp_stream_pkg.ALL;
+USE work.tb_dp_pkg.ALL;
+
+ENTITY tb_dp_fifo_fill_eop IS
+  GENERIC (
+    -- Try FIFO settings
+    g_dut_use_bsn         : BOOLEAN := FALSE;
+    g_dut_use_empty       : BOOLEAN := FALSE;
+    g_dut_use_channel     : BOOLEAN := FALSE;
+    g_dut_use_sync        : BOOLEAN := FALSE;
+    g_dut_fifo_rl         : NATURAL := 1;                  -- internal RL,  use 0 for look ahead FIFO, default 1 for normal FIFO
+    g_dut_fifo_size       : NATURAL := 128;
+    g_dut_fifo_fill       : NATURAL := 100;               -- selectable >= 0 for dp_fifo_fill
+    g_dut_use_rd_fill_32b : BOOLEAN := False 
+  );
+END tb_dp_fifo_fill_eop;
+
+
+ARCHITECTURE tb OF tb_dp_fifo_fill_eop IS
+
+  -- See tb_dp_pkg.vhd for explanation and run time
+
+  -- DUT
+  CONSTANT c_dut_in_latency     : NATURAL := 1;                 -- fixed for dp_fifo_fill
+  CONSTANT c_dut_out_latency    : NATURAL := 1;                 -- fixed for dp_fifo_fill, only internally dp_fifo_fill may use RL=0 or 1 dependent on g_dut_fifo_rl
+  CONSTANT c_dut_fifo_af_margin : NATURAL := 4;  
+
+  -- Stimuli
+  CONSTANT c_tx_latency     : NATURAL := c_dut_in_latency;   -- TX ready latency of TB
+  CONSTANT c_tx_void        : NATURAL := sel_a_b(c_tx_latency, 1, 0);  -- used to avoid empty range VHDL warnings when c_tx_latency=0
+  CONSTANT c_tx_offset_sop  : NATURAL := 3;
+  CONSTANT c_tx_period_sop  : NATURAL := 14;                  -- sop in data valid cycle 3,  17,  31, ...
+  CONSTANT c_tx_offset_eop  : NATURAL := 12;                  -- eop in data valid cycle 12,  26,  40, ...
+  CONSTANT c_tx_period_eop  : NATURAL := c_tx_period_sop;
+  CONSTANT c_tx_offset_sync : NATURAL := 3;                  -- sync in data valid cycle 3, 20, 37, ...
+  CONSTANT c_tx_period_sync : NATURAL := 17;
+  CONSTANT c_tx_offset_gap  : NATURAL := 5;                  -- gap in data valid cycle 5, 19, 33, ...
+  CONSTANT c_tx_period_gap  : NATURAL := c_tx_period_sop;
+  CONSTANT c_rx_latency     : NATURAL := c_dut_out_latency;  -- RX ready latency from DUT
+  CONSTANT c_verify_en_wait : NATURAL := 20+g_dut_fifo_fill;  -- wait some cycles before asserting verify enable
+  CONSTANT c_verify_data_en : BOOLEAN := c_tx_offset_eop-c_tx_offset_sop = c_tx_period_sop-1;
+  
+  CONSTANT c_bsn_offset     : NATURAL := 1;
+  CONSTANT c_empty_offset   : NATURAL := 2;
+  CONSTANT c_channel_offset : NATURAL := 3;
+  
+  CONSTANT c_random_w       : NATURAL := 19;
+  
+  SIGNAL tb_end         : STD_LOGIC := '0';
+  SIGNAL clk            : STD_LOGIC := '0';
+  SIGNAL rst            : STD_LOGIC;
+  SIGNAL sync           : STD_LOGIC;
+  SIGNAL lfsr1          : STD_LOGIC_VECTOR(c_random_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL lfsr2          : STD_LOGIC_VECTOR(c_random_w   DOWNTO 0) := (OTHERS=>'0');
+  
+  SIGNAL cnt_dat        : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
+  SIGNAL cnt_val        : STD_LOGIC;
+  SIGNAL cnt_en         : STD_LOGIC;
+  
+  SIGNAL tx_data        : t_dp_data_arr(0 TO c_tx_latency + c_tx_void)    := (OTHERS=>(OTHERS=>'0'));
+  SIGNAL tx_val         : STD_LOGIC_VECTOR(0 TO c_tx_latency + c_tx_void) := (OTHERS=>'0');
+  
+  SIGNAL in_ready       : STD_LOGIC;
+  SIGNAL in_data        : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL in_bsn         : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL in_empty       : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL in_channel     : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL in_sync        : STD_LOGIC;
+  SIGNAL in_val         : STD_LOGIC;
+  SIGNAL in_sop         : STD_LOGIC;
+  SIGNAL in_eop         : STD_LOGIC;
+  
+  SIGNAL wr_ful         : STD_LOGIC;
+  SIGNAL rd_usedw       : STD_LOGIC_VECTOR(ceil_log2(largest(g_dut_fifo_size, g_dut_fifo_fill + c_dut_fifo_af_margin + 2))-1 DOWNTO 0);
+  SIGNAL rd_fill_32b    : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := TO_UVEC(g_dut_fifo_fill, c_word_w);
+  SIGNAL in_siso        : t_dp_siso;
+  SIGNAL in_sosi        : t_dp_sosi := c_dp_sosi_rst;
+  SIGNAL out_siso       : t_dp_siso;
+  SIGNAL out_sosi       : t_dp_sosi;
+  
+  SIGNAL out_ready      : STD_LOGIC;
+  SIGNAL prev_out_ready : STD_LOGIC_VECTOR(0 TO c_rx_latency);
+  SIGNAL out_data       : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
+  SIGNAL out_bsn        : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL out_empty      : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL out_channel    : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL out_sync       : STD_LOGIC;
+  SIGNAL out_val        : STD_LOGIC;
+  SIGNAL out_sop        : STD_LOGIC;
+  SIGNAL out_eop        : STD_LOGIC;
+  SIGNAL prev_out_data  : STD_LOGIC_VECTOR(out_data'RANGE);
+  
+  SIGNAL state          : t_dp_state_enum;
+  
+  SIGNAL verify_en      : STD_LOGIC;
+  SIGNAL verify_done    : STD_LOGIC;
+  SIGNAL tb_done        : STD_LOGIC;
+  
+  SIGNAL exp_data       : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := TO_UVEC(15000, c_dp_data_w);
+
+  SIGNAL gap_en         : STD_LOGIC := '0';
+  
+BEGIN
+
+
+
+  clk <= NOT clk OR tb_end AFTER clk_period/2;
+  rst <= '1', '0' AFTER clk_period*7;
+  
+  -- Sync interval
+  proc_dp_sync_interval(clk, sync);
+  
+  -- Input data
+  cnt_val <= in_ready AND cnt_en AND NOT gap_en;
+
+
+  proc_dp_cnt_dat(rst, clk, cnt_val, cnt_dat);
+  proc_dp_tx_data(c_tx_latency, rst, clk, cnt_val, cnt_dat, tx_data, tx_val, in_data, in_val);
+  proc_dp_tx_ctrl(c_tx_offset_sync, c_tx_period_sync, in_data, in_val, in_sync);
+  proc_dp_tx_ctrl(c_tx_offset_sop, c_tx_period_sop, in_data, in_val, in_sop);
+  proc_dp_tx_ctrl(c_tx_offset_eop, c_tx_period_eop, in_data, in_val, in_eop);
+  proc_dp_tx_ctrl(c_tx_offset_gap, c_tx_period_gap, in_data, in_val, gap_en);
+
+  in_bsn     <= INCR_UVEC(in_data, c_bsn_offset);
+  in_empty   <= INCR_UVEC(in_data, c_empty_offset);
+  in_channel <= INCR_UVEC(in_data, c_channel_offset);
+
+  -- Stimuli control
+  proc_dp_count_en(rst, clk, sync, lfsr1, state, verify_done, tb_done, cnt_en);
+  proc_dp_out_ready(rst, clk, sync, lfsr2, out_ready);
+  
+  -- Output verify
+  proc_dp_verify_en(c_verify_en_wait, rst, clk, sync, verify_en);
+  
+  gen_verify_data : IF c_verify_data_en=TRUE GENERATE
+    proc_dp_verify_data("out_sosi.data", c_rx_latency, clk, verify_en, out_ready, out_val, out_data, prev_out_data);
+  END GENERATE;
+  ASSERT c_verify_data_en=TRUE REPORT "proc_dp_verify_data() can not verify the data if it is not continuous" SEVERITY WARNING;
+  
+  proc_dp_verify_valid(c_rx_latency, clk, verify_en, out_ready, prev_out_ready, out_val);
+  proc_dp_verify_ctrl(c_tx_offset_sop, c_tx_period_sop, "sop", clk, verify_en, out_data, out_val, out_sop);
+  proc_dp_verify_ctrl(c_tx_offset_eop, c_tx_period_eop, "eop", clk, verify_en, out_data, out_val, out_eop);
+  
+  gen_verify_sync : IF g_dut_use_sync=TRUE GENERATE
+    proc_dp_verify_ctrl(c_tx_offset_sync, c_tx_period_sync, "sync", clk, verify_en, out_data, out_val, out_sync);
+  END GENERATE;
+  
+  gen_verify_bsn : IF g_dut_use_bsn=TRUE GENERATE
+    proc_dp_verify_other_sosi("bsn", INCR_UVEC(out_data, c_bsn_offset), clk, verify_en, out_bsn);
+  END GENERATE;
+  
+  gen_verify_empty : IF g_dut_use_empty=TRUE GENERATE
+    proc_dp_verify_other_sosi("empty", INCR_UVEC(out_data, c_empty_offset), clk, verify_en, out_empty);
+  END GENERATE;
+  
+  gen_verify_channel : IF g_dut_use_channel=TRUE GENERATE
+    proc_dp_verify_other_sosi("channel", INCR_UVEC(out_data, c_channel_offset), clk, verify_en, out_channel);
+  END GENERATE;
+  
+  -- Check that the test has ran at all
+  proc_dp_verify_value(e_at_least, clk, verify_done, exp_data, out_data);
+  
+  -- Verify fill level
+  p_verify_fifo_fill : PROCESS
+  BEGIN
+    IF g_dut_fifo_fill>0 THEN
+      -- Use rd_fill_32b /= g_dut_fifo_fill to verify dynamic control
+      IF g_dut_use_rd_fill_32b=TRUE THEN
+        rd_fill_32b <= TO_UVEC(g_dut_fifo_size/5, c_word_w);
+      END IF;
+      
+      -- Check fill level at first output
+      proc_common_wait_until_high(clk, out_val);
+      ASSERT UNSIGNED(rd_usedw)=UNSIGNED(rd_fill_32b) REPORT "Usedw is not equal to fill level at start" SEVERITY ERROR;
+      
+      -- Check fill level after last output (account for block length given by c_tx_period_sop)
+      proc_common_wait_until_high(clk, verify_done);
+      proc_common_wait_some_cycles(clk, g_dut_fifo_size);
+      ASSERT UNSIGNED(rd_usedw)>=UNSIGNED(rd_fill_32b)-c_tx_period_sop REPORT "Usedw does not match fill level at end" SEVERITY ERROR;
+    END IF;
+    
+    proc_common_wait_until_high(clk, tb_done);
+    tb_end <= '1';
+    WAIT;
+  END PROCESS;
+ 
+  ------------------------------------------------------------------------------
+  -- DUT dp_fifo_fill
+  ------------------------------------------------------------------------------
+  
+  -- map sl, slv to record
+  in_ready <= in_siso.ready;                           -- SISO
+  in_sosi.data(c_dp_data_w-1 DOWNTO 0) <= in_data;     -- SOSI
+  in_sosi.bsn(c_dp_bsn_w-1 DOWNTO 0)   <= in_bsn(c_dp_bsn_w-1 DOWNTO 0);
+  in_sosi.empty                        <= in_empty(c_dp_empty_w-1 DOWNTO 0);
+  in_sosi.channel                      <= in_channel(c_dp_channel_w-1 DOWNTO 0);
+  in_sosi.sync                         <= in_sync;
+  in_sosi.valid                        <= (in_val AND NOT gap_en);
+  in_sosi.sop                          <= in_sop;
+  in_sosi.eop                          <= in_eop;
+  
+  out_siso.ready <= out_ready;                                                      -- SISO
+  out_siso.xon   <= '1';
+  out_data                               <= out_sosi.data(c_dp_data_w-1 DOWNTO 0);  -- SOSI
+  out_bsn(c_dp_bsn_w-1 DOWNTO 0)         <= out_sosi.bsn(c_dp_bsn_w-1 DOWNTO 0);
+  out_empty(c_dp_empty_w-1 DOWNTO 0)     <= out_sosi.empty;
+  out_channel(c_dp_channel_w-1 DOWNTO 0) <= out_sosi.channel;
+  out_sync                               <= out_sosi.sync;
+  out_val                                <= out_sosi.valid;
+  out_sop                                <= out_sosi.sop;
+  out_eop                                <= out_sosi.eop;
+  
+  dut : ENTITY work.dp_fifo_fill_eop
+  GENERIC MAP (
+    g_data_w      => c_dp_data_w,
+    g_bsn_w       => c_dp_bsn_w,
+    g_empty_w     => c_dp_empty_w,
+    g_channel_w   => c_dp_channel_w,
+    g_error_w     => 1,
+    g_use_bsn     => g_dut_use_bsn,
+    g_use_empty   => g_dut_use_empty,
+    g_use_channel => g_dut_use_channel,
+    g_use_error   => FALSE,
+    g_use_sync    => g_dut_use_sync,
+    g_fifo_fill   => g_dut_fifo_fill,
+    g_fifo_size   => g_dut_fifo_size,
+    g_fifo_rl     => g_dut_fifo_rl
+  )
+  PORT MAP (
+    rd_rst      => rst,
+    rd_clk      => clk,
+    wr_rst      => rst,
+    wr_clk      => clk,
+    wr_ful      => wr_ful,
+    rd_usedw    => rd_usedw,
+    rd_fill_32b => rd_fill_32b,
+    snk_out     => in_siso,     -- OUT = request to upstream ST source
+    snk_in      => in_sosi,
+    src_in      => out_siso,    -- IN  = request from downstream ST sink
+    src_out     => out_sosi
+  );
+
+END tb;