diff --git a/applications/lofar2/designs/lofar2_unb2b_ring/src/vhdl/lofar2_unb2b_ring.vhd b/applications/lofar2/designs/lofar2_unb2b_ring/src/vhdl/lofar2_unb2b_ring.vhd
index 5891567b0adc6e12c3d8b24f0a934a632da0d264..612609097a171c416a5f92c2e4dd1992c99ea4e6 100644
--- a/applications/lofar2/designs/lofar2_unb2b_ring/src/vhdl/lofar2_unb2b_ring.vhd
+++ b/applications/lofar2/designs/lofar2_unb2b_ring/src/vhdl/lofar2_unb2b_ring.vhd
@@ -136,7 +136,6 @@ ARCHITECTURE str OF lofar2_unb2b_ring IS
   CONSTANT c_nof_tx_monitors           : NATURAL := c_sdp_N_pn_max; 
   CONSTANT c_err_bi                    : NATURAL := 0; 
   CONSTANT c_nof_err_counts            : NATURAL := 8; 
-  CONSTANT c_validate_err_fifo_size    : NATURAL := 1536; 
   CONSTANT c_bsn_at_sync_check_channel : NATURAL := 1; 
   CONSTANT c_validate_channel          : BOOLEAN := TRUE; 
   CONSTANT c_validate_channel_mode     : STRING  := "=";
@@ -770,7 +769,6 @@ BEGIN
       g_nof_tx_monitors           => c_nof_tx_monitors,
       g_err_bi                    => c_err_bi,
       g_nof_err_counts            => c_nof_err_counts,
-      g_validate_err_fifo_size    => c_validate_err_fifo_size,
       g_bsn_at_sync_check_channel => c_bsn_at_sync_check_channel,
       g_validate_channel          => c_validate_channel,
       g_validate_channel_mode     => c_validate_channel_mode,
@@ -822,7 +820,6 @@ BEGIN
       g_nof_tx_monitors           => c_nof_tx_monitors,
       g_err_bi                    => c_err_bi,
       g_nof_err_counts            => c_nof_err_counts,
-      g_validate_err_fifo_size    => c_validate_err_fifo_size,
       g_bsn_at_sync_check_channel => c_bsn_at_sync_check_channel,
       g_validate_channel          => c_validate_channel,
       g_validate_channel_mode     => c_validate_channel_mode,
diff --git a/libraries/base/dp/src/vhdl/dp_block_validate_err.vhd b/libraries/base/dp/src/vhdl/dp_block_validate_err.vhd
index f661fdbf53d60631f26d0328690dd4269fcf177e..74e3db58e912b6c3b7812450f7840361c155f2ea 100644
--- a/libraries/base/dp/src/vhdl/dp_block_validate_err.vhd
+++ b/libraries/base/dp/src/vhdl/dp_block_validate_err.vhd
@@ -35,14 +35,13 @@
 --     result in multiple counters increasing per block. Therefore, it should not be 
 --     assumed that the sum of the err counters is the total amount of discarded
 --     blocks.
---   . Note that dp_fifo_fill_eop cannot handle continues stream of blocks without 
---     a gap between blocks the dp_fifo_fill_eop needs 1 cycle to process a block.
---     Streaming without gaps may cause the fifo to overflow. Bursts of blocks
---     can be handled by increasing g_fifo_size.
 --   . g_max/min_block_size indicate the minimum / maximum length of incoming blocks.
 --     The ratio of max / min is used to determine a fifo size for the outgoing
 --     sosi.valid signals. To minimize logic the g_min_block_size can be set to
 --     the expected minimum block size.
+--   . g_fifo_size can be set to g_max_block_size if there is no backpressure.
+--     If there is back pressure on the src_in, the fifo_fill_eop can be used to 
+--     to account for this backpressure by using an g_fifo_size > g_max_block_size.
 -------------------------------------------------------------------------------
 -- REGMAP
 -------------------------------------------------------------------------------
@@ -69,11 +68,11 @@ USE common_lib.common_mem_pkg.ALL;
 ENTITY dp_block_validate_err IS
   GENERIC (
     g_cnt_w              : NATURAL  := c_word_w; -- max is c_word_w due to mm word width
-    g_max_block_size     : POSITIVE := 250;
-    g_min_block_size     : POSITIVE := 1;
+    g_max_block_size     : POSITIVE := 250; -- largest possible incoming block size.
+    g_min_block_size     : POSITIVE := 1;   -- smallest possible incoming block size.
     g_nof_err_counts     : NATURAL  := 8;
     -- fifo generics
-    g_fifo_size          : POSITIVE := 256;
+    g_fifo_size          : POSITIVE := 256; -- fifo size to buffer incoming blocks, should be >= g_max_block_size 
     g_data_w             : NATURAL  := 16;
     g_bsn_w              : NATURAL  := 1;
     g_empty_w            : NATURAL  := 1;
diff --git a/libraries/base/dp/src/vhdl/dp_fifo_fill_eop.vhd b/libraries/base/dp/src/vhdl/dp_fifo_fill_eop.vhd
index 74776150ed3d99824cde735d1f16483cae61616b..cd8c20ec66c1124a89b45a2f99b40819aabf776b 100644
--- a/libraries/base/dp/src/vhdl/dp_fifo_fill_eop.vhd
+++ b/libraries/base/dp/src/vhdl/dp_fifo_fill_eop.vhd
@@ -32,10 +32,6 @@
 --   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.
--- Remark:
---   . dp_fifo_fill_eop needs 1 clock cycle gap between eop and sop to process
---     the block. Therefore it cannot handle contious streams without gaps. It
---     can handle bursts by increasing g_fifo_size.
 -------------------------------------------------------------------------------
 
 LIBRARY IEEE, common_lib, technology_lib;
@@ -48,6 +44,7 @@ USE technology_lib.technology_select_pkg.ALL;
 ENTITY dp_fifo_fill_eop IS
   GENERIC (
     g_technology     : NATURAL := c_tech_select_default;
+    g_note_is_ful    : BOOLEAN := TRUE;
     g_use_dual_clock : BOOLEAN := FALSE;
     g_data_w         : NATURAL := 16;
     g_bsn_w          : NATURAL := 1;
@@ -99,16 +96,12 @@ ARCHITECTURE rtl OF dp_fifo_fill_eop IS
   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";
+  TYPE t_state IS (s_fill, s_output, s_xoff);
 
   CONSTANT c_nof_spulse : NATURAL := 3;
   
-  SIGNAL state       : STD_LOGIC_VECTOR(1 DOWNTO 0);  -- t_state
-  SIGNAL nxt_state   : STD_LOGIC_VECTOR(1 DOWNTO 0);  -- t_state
+  SIGNAL state       : t_state;
+  SIGNAL nxt_state   : t_state;
   
   SIGNAL xon_reg     : STD_LOGIC;
   SIGNAL nxt_xon_reg : STD_LOGIC;
@@ -150,106 +143,50 @@ BEGIN
   -- 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;
-
-    -- No need to transfer eop counter across clock domains
-    rd_eop_cnt     <= wr_eop_cnt;
-    rd_eop_new     <= '1';
-    p_sc: PROCESS(wr_clk, wr_rst)
-    BEGIN
-      IF wr_rst='1' THEN
-        wr_eop_cnt <= 0;
-      ELSIF rising_edge(wr_clk) THEN
-        IF snk_in.eop = '1' THEN
-          wr_eop_cnt <= 1;
-        ELSE
-          wr_eop_cnt <= 0;
-        END IF; 
-      END IF;
-    END PROCESS; 
-
-
-  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
-    );
+  u_dp_fifo_core : ENTITY work.dp_fifo_core
+  GENERIC MAP (
+    g_technology     => g_technology,
+    g_note_is_ful    => g_note_is_ful,
+    g_use_dual_clock => g_use_dual_clock,
+    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
+  );
 
-    -- Transfer eop counter across clock domains
+  -- Transfer eop counter across clock domains for dual clock
+  gen_rd_eop_cnt_dc : IF g_use_dual_clock=TRUE GENERATE  
     reg_wr_eop_cnt <= TO_UVEC(wr_eop_cnt, c_word_w);
-    rd_eop_cnt <= TO_UINT(reg_rd_eop_cnt);
     u_common_reg_cross_domain : ENTITY common_lib.common_reg_cross_domain
     PORT MAP (
       in_rst  => wr_rst,
@@ -262,38 +199,68 @@ BEGIN
       out_dat => reg_rd_eop_cnt,
       out_new => rd_eop_new
     );
+  END GENERATE;
+    
+  -- No need to transfer eop counter across clock domains for single clock
+  gen_rd_eop_cnt_sc : IF g_use_dual_clock=FALSE GENERATE
+    wr_fifo_usedw  <= rd_fifo_usedw;
+    rd_eop_new     <= '1';
+  END GENERATE;
 
-    p_dc: PROCESS(wr_clk, wr_rst)
-      VARIABLE v_wr_eop_cnt: NATURAL;
-    BEGIN
-      IF wr_rst='1' THEN
-        wr_eop_busy <= '0';
-        wr_eop_cnt <= 0;
-        wr_eop_new <= '0'; 
-      ELSIF rising_edge(wr_clk) THEN
-        v_wr_eop_cnt := wr_eop_cnt;
-        IF wr_eop_done = '1' THEN
+  -- Set rd_eop_cnt outside generate statements to avoid Modelsim warning "Nonresolved signal 'rd_eop_cnt' may have multiple sources".
+  -- This is only the case with INTEGER (sub) types as it does not have a resolve function te decide the value in case of multiple sources
+  -- through GENERATE statements. STD_LOGIC / STD_LOGIC VECTORS do have such a resolve function. Modelsim cannot resolve that the two GENERATE
+  -- statements where g_use_dual_clock = FALSE / TRUE will never be active simultaneously as a GENERATE statement cannot have an ELSE statement.
+  rd_eop_cnt <= TO_UINT(reg_rd_eop_cnt) WHEN g_use_dual_clock ELSE wr_eop_cnt;
+
+  p_eop_cnt: PROCESS(wr_clk, wr_rst)
+    VARIABLE v_wr_eop_cnt: NATURAL;
+  BEGIN
+    IF wr_rst='1' THEN
+      wr_eop_busy <= '0';
+      wr_eop_cnt <= 0;
+      wr_eop_new <= '0'; 
+    ELSIF rising_edge(wr_clk) THEN
+      -- We need to control in_new signal for common_reg_cross_domain. We can simply pulse in_new after in_done = '1'.
+      -- After we have send the wr_eop_cnt accross the clock domain by seting wr_eop_new, the wr_eop_cnt is reset to 0.
+      -- It is not possible to set in_new = snk_in.eop as there can be more snk_in.eop during the clock cross time necessary by common_reg_cross_domain.
+      IF g_use_dual_clock THEN 
+        v_wr_eop_cnt := wr_eop_cnt; 
+        
+        -- When done = 1, busy can be set to 0.
+        IF wr_eop_done = '1' THEN 
           wr_eop_busy <= '0';
         END IF;
-
+        -- If common_reg_cross_domain is not busy transfering the register we can initiate a new transfer by setting wr_eop_new.
         IF wr_eop_busy = '0' THEN
           wr_eop_busy <= '1';
           wr_eop_new <= '1'; 
         END IF; 
-
+  
+        -- After we transfered wr_eop_cnt, we can reset it to 0.
         IF wr_eop_new = '1' THEN
           wr_eop_new <= '0';
           v_wr_eop_cnt := 0;
         END IF;
-
-        IF snk_in.eop = '1' THEN
+  
+        -- Count incoming snk_in.eop
+        IF snk_in.eop = '1' THEN 
           v_wr_eop_cnt := v_wr_eop_cnt + 1;
         END IF;
         wr_eop_cnt <= v_wr_eop_cnt;
+
+      -- No need to transfer eop counter across clock domains for single clock
+      ELSE 
+        IF snk_in.eop = '1' THEN
+          wr_eop_cnt <= 1; -- wr_eop_cnt can simply be set to 1 instead of counting as it is immidiatly processed due to having a single clock.
+        ELSE
+          wr_eop_cnt <= 0;
+        END IF; 
       END IF;
-    END PROCESS;  
-  END GENERATE;
-    
+    END IF;
+  END PROCESS; 
+
+
   no_fill : IF g_fifo_fill=0 GENERATE
     rd_siso <= src_in;   -- SISO
     src_out <= rd_sosi;  -- SOSI
@@ -307,7 +274,7 @@ BEGIN
     BEGIN
       IF rd_rst='1' THEN
         xon_reg   <= '0';
-        state     <= s_idle;
+        state     <= s_fill;
         i_src_out <= c_dp_sosi_rst;
         eop_cnt   <= 0;
       ELSIF rising_edge(rd_clk) THEN
@@ -320,77 +287,6 @@ BEGIN
      
     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, rd_eop_cnt, eop_cnt, rd_eop_new)
-      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';
-        nxt_eop_cnt       <= eop_cnt;
-        IF rd_eop_new = '1' THEN
-          nxt_eop_cnt <= eop_cnt + rd_eop_cnt;
-        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 eop_cnt <= 0 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_state <= s_output;
-                  IF rd_eop_new = '1' THEN
-                    nxt_eop_cnt <= eop_cnt + rd_eop_cnt - 1;
-                  ELSE
-                    nxt_eop_cnt <= eop_cnt -1;
-                  END IF;
-                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.
       
@@ -408,42 +304,40 @@ BEGIN
         pend_src_out => pend_src_out,
         src_out_reg  => i_src_out
       );
+    END GENERATE; 
+
+    gen_rl_0 : IF g_fifo_rl=0 GENERATE
+      pend_src_out <= rd_sosi;
+      rd_siso <= hold_src_in;
+    END GENERATE;
       
-      p_state : PROCESS(state, src_in, xon_reg, pend_src_out, rd_fifo_usedw, rd_fill_ctrl, rd_eop_cnt, eop_cnt, rd_eop_new)
-      BEGIN
-        nxt_state <= state;
+ 
+    p_state : PROCESS(state, src_in, xon_reg, pend_src_out, rd_fifo_usedw, rd_fill_ctrl, rd_eop_cnt, eop_cnt, rd_eop_new)
+    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';
-        nxt_eop_cnt       <= eop_cnt;
-        IF rd_eop_new = '1' THEN
-          nxt_eop_cnt <= eop_cnt + rd_eop_cnt;
-        END IF;
+      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';
+      nxt_eop_cnt       <= eop_cnt;
+      IF rd_eop_new = '1' THEN
+        nxt_eop_cnt <= eop_cnt + rd_eop_cnt;
+      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;
+      CASE state IS
+        WHEN s_fill =>
+          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
-              -- stop reading until the FIFO has been filled sufficiently
               IF UNSIGNED(rd_fifo_usedw)<UNSIGNED(rd_fill_ctrl) AND eop_cnt <= 0 THEN
                 hold_src_in <= c_dp_siso_hold;  -- stop the input, hold the pend_src_out.sop
               ELSE
@@ -459,26 +353,26 @@ BEGIN
                 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 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_fill;        -- output eop, so stop reading the FIFO
             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;
+          END IF;
+        WHEN OTHERS => -- s_xoff
+          -- Flush the fill FIFO when xon='0'
+          hold_src_in <= c_dp_siso_flush;
+          IF xon_reg='1' THEN
+            nxt_state <= s_fill;
+          END IF;
+      END CASE;
 
-        -- Pass on frame level flow control
-        hold_src_in.xon <= src_in.xon;
-      END PROCESS;
-    END GENERATE;  -- gen_rl_1
+      -- Pass on frame level flow control
+      hold_src_in.xon <= src_in.xon;
+    END PROCESS;
     
   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
index f4cdef3d2f04a248b6adc1ec808472daa621080e..ab79f93e74ee1318c7bd4884dfee5dc1097fcf91 100644
--- a/libraries/base/dp/tb/vhdl/tb_dp_fifo_fill_eop.vhd
+++ b/libraries/base/dp/tb/vhdl/tb_dp_fifo_fill_eop.vhd
@@ -55,7 +55,9 @@ ENTITY tb_dp_fifo_fill_eop IS
     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 
+    g_dut_use_rd_fill_32b : BOOLEAN := FALSE;
+    g_dut_use_gap         : BOOLEAN := TRUE;   
+    g_dut_use_random_ctrl : BOOLEAN := TRUE   
   );
 END tb_dp_fifo_fill_eop;
 
@@ -74,7 +76,7 @@ ARCHITECTURE tb OF tb_dp_fifo_fill_eop IS
   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_offset_eop  : NATURAL := sel_a_b(g_dut_use_gap, 12, 16);  -- 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;
@@ -99,7 +101,7 @@ ARCHITECTURE tb OF tb_dp_fifo_fill_eop IS
   
   SIGNAL cnt_dat        : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
   SIGNAL cnt_val        : STD_LOGIC;
-  SIGNAL cnt_en         : STD_LOGIC;
+  SIGNAL cnt_en         : STD_LOGIC := '1'; -- default always active input control.
   
   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');
@@ -122,7 +124,7 @@ ARCHITECTURE tb OF tb_dp_fifo_fill_eop IS
   SIGNAL out_siso       : t_dp_siso;
   SIGNAL out_sosi       : t_dp_sosi;
   
-  SIGNAL out_ready      : STD_LOGIC;
+  SIGNAL out_ready      : STD_LOGIC := '1'; -- default always active output flow control.
   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');
@@ -155,7 +157,7 @@ BEGIN
   proc_dp_sync_interval(clk, sync);
   
   -- Input data
-  cnt_val <= in_ready AND cnt_en AND NOT gap_en;
+  cnt_val <= in_ready AND cnt_en AND NOT gap_en WHEN g_dut_use_random_ctrl ELSE in_ready AND NOT gap_en;
 
 
   proc_dp_cnt_dat(rst, clk, cnt_val, cnt_dat);
@@ -163,15 +165,19 @@ BEGIN
   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);
+  gen_gap: IF g_dut_use_gap GENERATE
+    proc_dp_tx_ctrl(c_tx_offset_gap, c_tx_period_gap, in_data, in_val, gap_en);
+  END GENERATE;
 
   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);
+    proc_dp_count_en(rst, clk, sync, lfsr1, state, verify_done, tb_done, cnt_en);
+  gen_random_ctrl : IF g_dut_use_random_ctrl GENERATE
+    proc_dp_out_ready(rst, clk, sync, lfsr2, out_ready);
+  END GENERATE;
   
   -- Output verify
   proc_dp_verify_en(c_verify_en_wait, rst, clk, sync, verify_en);
diff --git a/libraries/base/dp/tb/vhdl/tb_tb_dp_fifo_fill_eop.vhd b/libraries/base/dp/tb/vhdl/tb_tb_dp_fifo_fill_eop.vhd
index f4b4106cbc87fedc54cf9fafefc95f3ee48d8af9..c3711898d24ce8b63624e3ffb43dc72a504a276f 100644
--- a/libraries/base/dp/tb/vhdl/tb_tb_dp_fifo_fill_eop.vhd
+++ b/libraries/base/dp/tb/vhdl/tb_tb_dp_fifo_fill_eop.vhd
@@ -45,8 +45,18 @@ END tb_tb_dp_fifo_fill_eop;
 ARCHITECTURE tb OF tb_tb_dp_fifo_fill_eop IS
   SIGNAL tb_end : STD_LOGIC := '0';  -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
 BEGIN
-  -- Try FIFO settings : GENERIC MAP (g_dut_use_dual_clock, g_dut_use_bsn, g_dut_use_empty, g_dut_use_channel, g_dut_use_sync, g_dut_fifo_rl, g_dut_fifo_size, g_dut_fifo_fill, g_dut_use_rd_fill_32b)
-  u_dut_sc          : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => FALSE); 
-  u_dut_dc          : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => TRUE);
+  -- Try FIFO settings : GENERIC MAP (g_dut_use_dual_clock, g_dut_use_bsn, g_dut_use_empty, g_dut_use_channel, g_dut_use_sync, g_dut_fifo_rl, g_dut_fifo_size, g_dut_fifo_fill, g_dut_use_rd_fill_32b, g_dut_use_gap, g_dut_use_random_ctrl)
   
+  u_dut_sc_1             : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => FALSE, g_dut_fifo_rl => 1, g_dut_use_random_ctrl => FALSE); 
+  u_dut_sc_1_no_gap      : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => FALSE, g_dut_fifo_rl => 1, g_dut_use_random_ctrl => FALSE, g_dut_use_gap => FALSE); 
+  u_dut_dc_1_no_gap      : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => TRUE,  g_dut_fifo_rl => 1, g_dut_use_random_ctrl => FALSE, g_dut_use_gap => FALSE); 
+  u_dut_dc_0_no_gap      : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => TRUE,  g_dut_fifo_rl => 0, g_dut_use_random_ctrl => FALSE, g_dut_use_gap => FALSE); 
+  u_dut_sc_1_rand        : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => FALSE, g_dut_fifo_rl => 1, g_dut_use_random_ctrl => TRUE); 
+  u_dut_dc_1_rand        : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => TRUE,  g_dut_fifo_rl => 1, g_dut_use_random_ctrl => TRUE);
+  u_dut_sc_0_rand        : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => FALSE, g_dut_fifo_rl => 0, g_dut_use_random_ctrl => TRUE); 
+  u_dut_dc_0_rand        : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => TRUE,  g_dut_fifo_rl => 0, g_dut_use_random_ctrl => TRUE);
+  u_dut_sc_1_rand_no_gap : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => FALSE, g_dut_fifo_rl => 1, g_dut_use_random_ctrl => TRUE, g_dut_use_gap => FALSE); 
+  u_dut_dc_1_rand_no_gap : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => TRUE,  g_dut_fifo_rl => 1, g_dut_use_random_ctrl => TRUE, g_dut_use_gap => FALSE);
+  u_dut_sc_0_rand_no_gap : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => FALSE, g_dut_fifo_rl => 0, g_dut_use_random_ctrl => TRUE, g_dut_use_gap => FALSE); 
+  u_dut_dc_0_rand_no_gap : ENTITY work.tb_dp_fifo_fill_eop GENERIC MAP (g_dut_use_dual_clock => TRUE,  g_dut_fifo_rl => 0, g_dut_use_random_ctrl => TRUE, g_dut_use_gap => FALSE);  
 END tb;
diff --git a/libraries/base/ring/src/vhdl/ring_lane.vhd b/libraries/base/ring/src/vhdl/ring_lane.vhd
index bf2ba0fe87e0f08e2103f347f725ae8a8a18223b..e0afcc2efffd9056c47a16cb486628751de84c8e 100644
--- a/libraries/base/ring/src/vhdl/ring_lane.vhd
+++ b/libraries/base/ring/src/vhdl/ring_lane.vhd
@@ -50,7 +50,6 @@ ENTITY ring_lane IS
     g_nof_tx_monitors           : NATURAL := 1;
     g_err_bi                    : NATURAL := 0; -- ring_rx bit index in sosi.err field to set for wrongly sized packets 
     g_nof_err_counts            : NATURAL := 1; -- nof counters to count the set err bits in range sosi.err(g_nof_err_counts-1 DOWNTO 0)
-    g_validate_err_fifo_size    : NATURAL := 1536; -- should be >= g_lane_packet_length
     g_bsn_at_sync_check_channel : NATURAL := 1; -- on which channel should the bsn be checked
     g_validate_channel          : BOOLEAN := TRUE;
     g_validate_channel_mode     : STRING := ">";
@@ -122,7 +121,6 @@ BEGIN
     g_err_bi          => g_err_bi, 
     g_block_size      => g_lane_packet_length, 
     g_nof_err_counts  => g_nof_err_counts, 
-    g_fifo_size       => g_validate_err_fifo_size, 
     g_check_channel   => g_bsn_at_sync_check_channel, 
     g_sync_timeout    => g_sync_timeout
   )
diff --git a/libraries/base/ring/src/vhdl/ring_rx.vhd b/libraries/base/ring/src/vhdl/ring_rx.vhd
index 7ac8a4a6e774bad9889adf4aef24d82c972b852d..c7096b82a629028175d5bf0fe54ff8fc50929de4 100644
--- a/libraries/base/ring/src/vhdl/ring_rx.vhd
+++ b/libraries/base/ring/src/vhdl/ring_rx.vhd
@@ -24,11 +24,6 @@
 
 -- Purpose: Handle RX side of ring design.
 -- Description: See https://support.astron.nl/confluence/x/jyu7Ag
--- Remark:
--- . Note that the dp_fifo_fill_eop in dp_block_validate_err cannot handle
---   continues stream of blocks without a gap between blocks the dp_fifo_fill_eop 
---   needs 1 cycle to process a block. Streaming without gaps may cause the fifo 
---   to overflow. Bursts of blocks can be handled by increasing g_fifo_size.
 
 -------------------------------------------------------------------------------
 
@@ -49,7 +44,6 @@ ENTITY ring_rx IS
     g_err_bi           : NATURAL := 0;  
     g_block_size       : NATURAL := 1024; 
     g_nof_err_counts   : NATURAL := 1; 
-    g_fifo_size        : NATURAL := 1536; 
     g_check_channel    : NATURAL := 1;
     g_sync_timeout     : NATURAL := 220*10**6  -- 10% margin
   );
@@ -124,7 +118,7 @@ BEGIN
     g_max_block_size  => c_packet_size,
     g_min_block_size  => c_packet_size,
     g_nof_err_counts  => g_nof_err_counts,
-    g_fifo_size       => g_fifo_size,
+    g_fifo_size       => c_packet_size, -- can be same as g_max_block_size as src_in.ready = '1'
     g_data_w          => g_data_w
   )
   PORT MAP (