diff --git a/cores/base/dp/dp_components/dp_hold_ctrl.vhd b/cores/base/dp/dp_components/dp_hold_ctrl.vhd
deleted file mode 100644
index fa36f9310c02a57584afb31b854c896430b33a9e..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_components/dp_hold_ctrl.vhd
+++ /dev/null
@@ -1,70 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_components_lib;
-USE IEEE.std_logic_1164.all;
-
--- Purpose:
---   Hold hld_ctrl active until next ready high when in_ctrl is active while
---   ready went low
--- Description:
---   When ready goes low there may still arrive one new valid data. The control
---   information for this data can then be held with this component. When ready
---   goes high again the held data can then be output and the hld_ctrl is 
---   released. After that the subsequent data output can come directly from the
---   up stream source, until ready goes low again.
--- Remarks:
--- . Ready latency RL = 1
--- . The in_ctrl is typically in_valid, in_sop or in_eop
--- . Typically used together with dp_hold_data
-
-ENTITY dp_hold_ctrl IS
-  PORT (
-    rst      : IN  STD_LOGIC;
-    clk      : IN  STD_LOGIC;
-    ready    : IN  STD_LOGIC;
-    in_ctrl  : IN  STD_LOGIC;
-    hld_ctrl : OUT STD_LOGIC
-  );
-END dp_hold_ctrl;
-
-
-ARCHITECTURE rtl OF dp_hold_ctrl IS
-  
-  SIGNAL hi_ctrl : STD_LOGIC;
-  SIGNAL lo_ctrl : STD_LOGIC;
-
-BEGIN
-
-  hi_ctrl <=     in_ctrl AND NOT ready;  -- capture
-  lo_ctrl <= NOT in_ctrl AND     ready;  -- release
-  
-  u_hld_ctrl : ENTITY common_components_lib.common_switch
-  PORT MAP (
-    rst         => rst,
-    clk         => clk,
-    switch_high => hi_ctrl,
-    switch_low  => lo_ctrl,
-    out_level   => hld_ctrl
-  );
-  
-END rtl;
diff --git a/cores/base/dp/dp_components/dp_hold_input.vhd b/cores/base/dp/dp_components/dp_hold_input.vhd
deleted file mode 100644
index 81ab370cfc135e4089c9fe9f7c74759d13285801..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_components/dp_hold_input.vhd
+++ /dev/null
@@ -1,157 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, dp_pkg_lib;
-USE IEEE.std_logic_1164.all;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
--- Purpose:
---   Hold the sink input
--- Description:
---   This dp_hold_input provides the necessary input logic to hold the input
---   data and control to easily register the source output. Compared to
---   dp_pipeling the dp_hold_input is the same except for the output register
---   stage. In this way dp_hold_input can be used in a more complicated stream
---   component where the output is not always the same as the input.
---   The snk_in.valid and hold_in.valid are never high at the same time.
---   If src_in.ready goes low while snk_in.valid is high then this snk_in.valid
---   is held in hold_in.valid and the corresponding snk_in.data will get held
---   in the external src_out_reg.data. When src_in.ready goes high again then
---   the held data becomes valid via src_out_reg.valid and hold_in.valid goes
---   low. Due to the RL=1 the next cycle the snk_in.valid from the sink may go
---   high. The next_src_out control signals are equal to pend_src_out AND
---   src_in.ready, so they can directly be assigned to src_out_reg.data if the
---   snk_in.data needs to be passed on.
---   The internal pend_src_out control signals are available outside, in
---   addition to the next_src_out control signals, to support external control
---   independent of src_in.ready. Use pend_scr_out instead of next_src_out
---   to avoid combinatorial loop when src_in.ready depends on next_src_out.
---   The pend_src_out signals are used to implement show ahead behaviour like
---   with RL=0, but for RL=1. The input can then be stopped based on the snk_in
---   data and later on continued again without losing this snk_in data, because
---   it was held as described above.
--- Remarks:
--- . Ready latency = 1
--- . Without flow control so when src_in.ready = '1' fixed, then dp_hold_input
---   becomes void because the dp_hold_ctrl output then remains '0'.
-
-ENTITY dp_hold_input IS
-  PORT (
-    rst              : IN  STD_LOGIC;
-    clk              : IN  STD_LOGIC;
-    -- ST sink
-    snk_out          : OUT t_dp_siso;
-    snk_in           : IN  t_dp_sosi;
-    -- ST source
-    src_in           : IN  t_dp_siso;
-    next_src_out     : OUT t_dp_sosi;
-    pend_src_out     : OUT t_dp_sosi;  -- the SOSI data fields are the same as for next_src_out
-    src_out_reg      : IN  t_dp_sosi   -- uses only the SOSI data fields
-  );
-END dp_hold_input;
-
-
-ARCHITECTURE rtl OF dp_hold_input IS
-  
-  SIGNAL i_pend_src_out : t_dp_sosi;
-  SIGNAL hold_in        : t_dp_sosi;  -- uses only the SOSI ctrl fields
-  
-BEGIN
-
-  pend_src_out <= i_pend_src_out;
-
-  -- SISO:
-  snk_out <= src_in;  --  No change in ready latency, pass on xon frame level flow control
-  
-  -- SOSI:
-  -- Take care of active snk_in.valid, snk_in.sync, snk_in.sop and snk_in.eop
-  -- when src_in.ready went low. If hold_in.valid would not be used for
-  -- pend_src_out.valid and next_src_out.valid, then the pipeline would still
-  -- work, but the valid snk_in.data that came when src_in.ready went low,
-  -- will then only get pushed out on the next valid snk_in.valid. Whereas
-  -- hold_in.valid ensures that it will get pushed out as soon as src_in.ready
-  -- goes high again. This is typically necessary in case of packetized data
-  -- where the eop of one packet should not have to wait for the valid (sop)
-  -- of a next packet to get pushed out.
-  
-  u_hold_val : ENTITY work.dp_hold_ctrl
-  PORT MAP (
-    rst      => rst,
-    clk      => clk,
-    ready    => src_in.ready,
-    in_ctrl  => snk_in.valid,
-    hld_ctrl => hold_in.valid
-  );
-  
-  u_hold_sync : ENTITY work.dp_hold_ctrl
-  PORT MAP (
-    rst      => rst,
-    clk      => clk,
-    ready    => src_in.ready,
-    in_ctrl  => snk_in.sync,
-    hld_ctrl => hold_in.sync
-  );
-  
-  u_hold_sop : ENTITY work.dp_hold_ctrl
-  PORT MAP (
-    rst      => rst,
-    clk      => clk,
-    ready    => src_in.ready,
-    in_ctrl  => snk_in.sop,
-    hld_ctrl => hold_in.sop
-  );
-  
-  u_hold_eop : ENTITY work.dp_hold_ctrl
-  PORT MAP (
-    rst      => rst,
-    clk      => clk,
-    ready    => src_in.ready,
-    in_ctrl  => snk_in.eop,
-    hld_ctrl => hold_in.eop
-  );
-  
-  p_pend_src_out : PROCESS(snk_in, src_out_reg, hold_in)
-  BEGIN
-    -- Pend data
-    IF snk_in.valid='1' THEN
-      i_pend_src_out <= snk_in;       -- Input data
-    ELSE
-      i_pend_src_out <= src_out_reg;  -- Hold data
-    END IF;
-    i_pend_src_out.valid <= snk_in.valid OR hold_in.valid;
-    i_pend_src_out.sync  <= snk_in.sync  OR hold_in.sync;
-    i_pend_src_out.sop   <= snk_in.sop   OR hold_in.sop;
-    i_pend_src_out.eop   <= snk_in.eop   OR hold_in.eop;
-  END PROCESS;
-  
-  p_next_src_out : PROCESS(i_pend_src_out, src_in)
-  BEGIN
-    -- Next data
-    next_src_out       <= i_pend_src_out;
-    -- Next control
-    next_src_out.valid <= i_pend_src_out.valid AND src_in.ready;
-    next_src_out.sync  <= i_pend_src_out.sync  AND src_in.ready;
-    next_src_out.sop   <= i_pend_src_out.sop   AND src_in.ready;
-    next_src_out.eop   <= i_pend_src_out.eop   AND src_in.ready;
-  END PROCESS;
-    
-END rtl;
diff --git a/cores/base/dp/dp_components/dp_latency_adapter.vhd b/cores/base/dp/dp_components/dp_latency_adapter.vhd
deleted file mode 100644
index 9fcca836dd9b256c160e26b5535a0e61b3a6b419..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_components/dp_latency_adapter.vhd
+++ /dev/null
@@ -1,260 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
--- Purpose:
---   Adapt the g_in_latency input ready to the g_out_latency output latency.
---   A typical application is to use this latency adapter to provide a read
---   ahead interface to a default FIFO with e.g. read latency 1 or 2.
--- Description:
---   If g_in_latency > g_out_latency then the input latency is first adapted
---   to zero latency by means of a latency FIFO. After that a delay line for
---   src_in.ready yields the g_out_latency output latency.
---   If g_in_latency < g_out_latency, then a delay line for src_in.ready yields
---   the g_out_latency output latency.
---   The sync input is also passed on, only if it occurs during valid. The
---   constant c_pass_sync_during_not_valid is defined to preserve the
---   corresponding section of code for passing the sync also during not valid.
--- Remark:
--- . The snk_out.ready is derived combinatorially from the src_in.ready. If for
---   timing performance it is needed to register snk_out.ready, then this can
---   be done by first increasing the ready latency using this adapter with
---   g_in_latency = g_out_latency + 1, followed by a second adapter to reach
---   the required output ready latency latency.
-
-ENTITY dp_latency_adapter IS
-  GENERIC (
-    g_in_latency   : NATURAL := 3;
-    g_out_latency  : NATURAL := 1
-  );
-  PORT (
-    rst          : IN  STD_LOGIC;
-    clk          : IN  STD_LOGIC;
-    -- Monitor internal FIFO filling
-    fifo_usedw   : OUT STD_LOGIC_VECTOR(ceil_log2(2+g_in_latency)-1 DOWNTO 0);  -- see description of c_fifo_size, c_usedw_w for explanation of why +2
-    fifo_ful     : OUT STD_LOGIC;
-    fifo_emp     : OUT STD_LOGIC;
-    -- 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_latency_adapter;
-
-
-ARCHITECTURE rtl OF dp_latency_adapter IS
-
-  -- The difference between the input ready latency and the output ready latency
-  CONSTANT c_diff_latency               : INTEGER := g_out_latency - g_in_latency;
-  
-  -- Define constant to preserve the corresponding section of code, but default keep it at FALSE
-  CONSTANT c_pass_sync_during_not_valid : BOOLEAN := FALSE;
-  
-  -- Use g_in_latency+1 words for the FIFO data array, to go to zero latency
-  CONSTANT c_high           : NATURAL := g_in_latency;
-  CONSTANT c_fifo_size      : NATURAL := g_in_latency+1;            -- +1 because RL=0 also requires a word
-  CONSTANT c_usedw_w        : NATURAL := ceil_log2(c_fifo_size+1);  -- +1 because to store value 2**n requires n+1 bits
-
-  SIGNAL fifo_reg           : t_dp_sosi_arr(c_high DOWNTO 0);
-  SIGNAL nxt_fifo_reg       : t_dp_sosi_arr(c_high DOWNTO 0);
-  SIGNAL fifo_reg_valid     : STD_LOGIC_VECTOR(c_high DOWNTO 0);    -- debug signal for Wave window
-  
-  SIGNAL nxt_fifo_usedw     : STD_LOGIC_VECTOR(c_usedw_w-1 DOWNTO 0);
-  SIGNAL nxt_fifo_ful       : STD_LOGIC;
-  SIGNAL nxt_fifo_emp       : STD_LOGIC;
-
-  SIGNAL ff_siso            : t_dp_siso;  -- SISO ready
-  SIGNAL ff_sosi            : t_dp_sosi;  -- SOSI
-  
-  SIGNAL i_snk_out          : t_dp_siso := c_dp_siso_rdy;
-  
-BEGIN
-
-  -- Use i_snk_out with defaults to force unused snk_out bits and fields to '0'
-  snk_out <= i_snk_out;
-  
-  gen_wires : IF c_diff_latency = 0 GENERATE  -- g_out_latency = g_in_latency
-    i_snk_out <= src_in;  -- SISO
-    src_out   <= snk_in;  -- SOSI
-  END GENERATE gen_wires;
-
-
-  no_fifo : IF c_diff_latency > 0 GENERATE  -- g_out_latency > g_in_latency
-    -- Go from g_in_latency to required larger g_out_latency
-    u_latency : ENTITY work.dp_latency_increase
-    GENERIC MAP (
-      g_in_latency   => g_in_latency,
-      g_incr_latency => c_diff_latency
-    )
-    PORT MAP (
-      rst       => rst,
-      clk       => clk,
-      -- ST sink
-      snk_out   => i_snk_out,
-      snk_in    => snk_in,
-      -- ST source
-      src_in    => src_in,
-      src_out   => src_out
-    );
-  END GENERATE no_fifo;
-  
-  
-  gen_fifo : IF c_diff_latency < 0 GENERATE  -- g_out_latency < g_in_latency
-    -- Register [0] contains the FIFO output with zero ready latency
-    ff_sosi <= fifo_reg(0);
-  
-    p_clk_fifo : PROCESS(rst, clk)
-    BEGIN
-      IF rst='1' THEN
-        fifo_reg   <= (OTHERS=>c_dp_sosi_rst);
-        fifo_usedw <= (OTHERS=>'0');
-        fifo_ful   <= '0';
-        fifo_emp   <= '1';
-      ELSIF rising_edge(clk) THEN
-        fifo_reg   <= nxt_fifo_reg;
-        fifo_usedw <= nxt_fifo_usedw;
-        fifo_ful   <= nxt_fifo_ful;
-        fifo_emp   <= nxt_fifo_emp;
-      END IF;
-    END PROCESS;
-    
-    -- Pass on frame level flow control
-    i_snk_out.xon <= src_in.xon;
-    
-    p_snk_out_ready : PROCESS(fifo_reg, ff_siso, snk_in)
-    BEGIN
-      i_snk_out.ready <= '0';
-      IF ff_siso.ready='1' THEN
-        -- Default snk_out ready when the source is ready.
-        i_snk_out.ready <= '1';
-      ELSE
-        -- Extra snk_out ready to look ahead for src_in RL = 0.
-        -- The fifo_reg[h:0] size is g_in_latency+1 number of SOSI values.
-        -- . The fifo_reg[h:1] provide free space for h=g_in_latency nof data
-        --   when snk_out.ready is pulled low, because then there can still
-        --   arrive g_in_latency nof new data with snk_in.valid asserted.
-        -- . The [0] is the registered output SOSI value with RL=0. Therefore
-        --   fifo_reg[0] can still accept a new input when ff_siso.ready is
-        --   low. If this assignment is omitted then the functionallity is
-        --   still OK, but the throughtput sligthly reduces.
-        IF fifo_reg(0).valid='0' THEN
-          i_snk_out.ready <= '1';
-        ELSIF fifo_reg(1).valid='0' THEN
-          i_snk_out.ready <= NOT(snk_in.valid);
-        END IF;
-      END IF;
-    END PROCESS;
-  
-    p_fifo_reg : PROCESS(fifo_reg, ff_siso, snk_in)
-    BEGIN
-      -- Keep or shift the fifo_reg dependent on ff_siso.ready, no need to explicitly check fifo_reg().valid
-      nxt_fifo_reg <= fifo_reg;
-      IF ff_siso.ready='1' THEN
-        nxt_fifo_reg(c_high-1 DOWNTO 0) <= fifo_reg(c_high DOWNTO 1);
-        nxt_fifo_reg(c_high).valid <= '0';
-        nxt_fifo_reg(c_high).sync  <= '0';
-        nxt_fifo_reg(c_high).sop   <= '0';
-        nxt_fifo_reg(c_high).eop   <= '0';
-        -- Forcing the nxt_fifo_reg[h] control fields to '0' is robust, but not
-        -- strictly necessary, because the control fields in fifo_reg[h] will
-        -- have been set to '0' already earlier due to the snk_in when
-        -- ff_siso.ready was '0'.
-      END IF;
-  
-      -- Put input data at the first available location dependent on ff_siso.ready, no need to explicitly check snk_in.valid
-      IF fifo_reg(0).valid='0' THEN
-        nxt_fifo_reg(0) <= snk_in;               -- fifo_reg is empty
-      ELSE
-        -- The fifo_reg is not empty, so filled to some extend
-        FOR I IN 1 TO c_high LOOP
-          IF fifo_reg(I).valid='0' THEN
-            IF ff_siso.ready='0' THEN
-              nxt_fifo_reg(I)   <= snk_in;
-            ELSE
-              nxt_fifo_reg(I-1) <= snk_in;
-            END IF;
-            EXIT;
-          END IF;
-        END LOOP;
-        
-        -- Default the input sync during input data valid is only passed on with the valid input data.
-        -- When c_pass_sync_during_not_valid is enabled then the input sync during input data not valid is passed on via the head fifo_reg(0) if the fifo_reg is empty.
-        IF c_pass_sync_during_not_valid=TRUE AND snk_in.sync='1' AND snk_in.valid='0' THEN
-          -- Otherwise for input sync during input data not valid we need to insert the input sync at the last location with valid data independent of ff_siso.ready, to avoid that it gets lost.
-          -- For streams that do not use the sync this logic will be void and optimize away by synthesis, because then snk_in.sync = '0' fixed.
-          IF fifo_reg(c_high).valid='1' THEN     -- fifo_reg is full
-            nxt_fifo_reg(c_high).sync <= '1';    -- insert input sync
-          ELSE
-            FOR I IN c_high-1 DOWNTO 0 LOOP      -- fifo_reg is filled to some extend, so not full and not empty
-              IF fifo_reg(I).valid='1' THEN
-                nxt_fifo_reg(I+1).sync <= '0';   -- overrule default sync assignment
-                nxt_fifo_reg(I).sync   <= '1';   -- insert input sync
-                EXIT;
-              END IF;
-            END LOOP;
-          END IF;
-        END IF;
-      END IF;
-    END PROCESS;
-    
-    p_fifo_usedw : PROCESS(nxt_fifo_reg)
-    BEGIN
-      nxt_fifo_usedw <= (OTHERS=>'0');
-      FOR I IN c_high DOWNTO 0 LOOP
-        IF nxt_fifo_reg(I).valid='1' THEN
-          nxt_fifo_usedw <= TO_UVEC(I+1, c_usedw_w);
-          EXIT;
-        END IF;
-      END LOOP;
-    END PROCESS;
-    
-    fifo_reg_valid <= func_dp_stream_arr_get(fifo_reg, "VALID");
-    
-    nxt_fifo_ful <= '1' WHEN TO_UINT(nxt_fifo_usedw)>=c_high+1 ELSE '0';  -- using >= or = is equivalent here
-    nxt_fifo_emp <= '1' WHEN TO_UINT(nxt_fifo_usedw) =0        ELSE '0';
-    
-    -- Go from 0 FIFO latency to required g_out_latency (only wires when g_out_latency=0)
-    u_latency : ENTITY work.dp_latency_increase
-    GENERIC MAP (
-      g_in_latency   => 0,
-      g_incr_latency => g_out_latency
-    )
-    PORT MAP (
-      rst       => rst,
-      clk       => clk,
-      -- ST sink
-      snk_out   => ff_siso,
-      snk_in    => ff_sosi,
-      -- ST source
-      src_in    => src_in,
-      src_out   => src_out
-    );
-  END GENERATE gen_fifo;
-
-END rtl;
diff --git a/cores/base/dp/dp_components/dp_latency_increase.vhd b/cores/base/dp/dp_components/dp_latency_increase.vhd
deleted file mode 100644
index 2ddc1cfe38489449f18a9e1a4a60c0b674bd9ce6..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_components/dp_latency_increase.vhd
+++ /dev/null
@@ -1,117 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
--- Purpose:
---   Typically used in dp_latency_adapter.
--- Description:
---   Increase the output ready latency by g_incr_latency compared to the input
---   ready latency g_in_latency. Hence the output latency becomes g_in_latency
---   + g_incr_latency.
--- Remark:
--- . The SOSI data stream signals (i.e. data, empty, channel, err) are passed
---   on as wires.
--- . The out_sync, out_val, out_sop and out_eop are internally AND with the
---   delayed src_in.ready, this is only truely necessary if the input ready
---   latency is 0, but it does not harm to do it also when the input ready
---   latency > 0. However to easy achieving P&R timing it is better to not have
---   unnessary logic in the combinatorial path of out_sync, out_val, out_sop
---   and out_eop, therefore the AND with reg_val is only generated when
---   g_in_latency=0.
-
-ENTITY dp_latency_increase IS
-  GENERIC (
-    g_in_latency   : NATURAL := 0;  -- >= 0
-    g_incr_latency : NATURAL := 2   -- >= 0
-  );
-  PORT (
-    rst          : IN  STD_LOGIC;
-    clk          : IN  STD_LOGIC;
-    -- 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_latency_increase;
-
-
-ARCHITECTURE rtl OF dp_latency_increase IS
-
-  CONSTANT c_out_latency : NATURAL := g_in_latency + g_incr_latency;
-  
-  SIGNAL reg_ready : STD_LOGIC_VECTOR(c_out_latency DOWNTO 0);
-  SIGNAL reg_val   : STD_LOGIC;
-  
-  SIGNAL i_snk_out : t_dp_siso := c_dp_siso_rdy;
-  
-BEGIN
-
-  -- Use i_snk_out with defaults to force unused snk_out bits and fields to '0'
-  snk_out <= i_snk_out;
-
-  -- Support wires only for g_incr_latency=0
-  no_latency : IF g_incr_latency=0 GENERATE
-    i_snk_out <= src_in;  -- SISO
-    src_out   <= snk_in;  -- SOSI
-  END GENERATE no_latency;
-  
-  gen_latency : IF g_incr_latency>0 GENERATE
-    -- SISO
-    reg_ready(0) <= src_in.ready;  -- use reg_ready(0) to combinatorially store src_in.ready
-    p_clk : PROCESS(rst, clk)
-    BEGIN
-      IF rst='1' THEN
-        reg_ready(c_out_latency DOWNTO 1) <= (OTHERS=>'0');
-      ELSIF rising_edge(clk) THEN
-        reg_ready(c_out_latency DOWNTO 1) <= reg_ready(c_out_latency-1 DOWNTO 0);
-      END IF;
-    END PROCESS;
-    
-    i_snk_out.xon   <= src_in.xon;                 -- Pass on frame level flow control
-    i_snk_out.ready <= reg_ready(g_incr_latency);  -- Adjust ready latency
-    
-    -- SOSI
-    gen_out : IF g_in_latency/=0 GENERATE
-      src_out <= snk_in;
-    END GENERATE;
-    gen_zero_out : IF g_in_latency=0 GENERATE
-      reg_val <= reg_ready(c_out_latency);
-    
-      p_src_out : PROCESS(snk_in, reg_val)
-      BEGIN
-        src_out       <= snk_in;
-        src_out.sync  <= snk_in.sync  AND reg_val;
-        src_out.valid <= snk_in.valid AND reg_val;
-        src_out.sop   <= snk_in.sop   AND reg_val;
-        src_out.eop   <= snk_in.eop   AND reg_val;
-      END PROCESS;
-    END GENERATE;
-  END GENERATE gen_latency;
-  
-END rtl;
diff --git a/cores/base/dp/dp_components/hdllib.cfg b/cores/base/dp/dp_components/hdllib.cfg
deleted file mode 100644
index 28b973ab8d93d763520924ea3e1a4c7c0394dbc8..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_components/hdllib.cfg
+++ /dev/null
@@ -1,22 +0,0 @@
-hdl_lib_name = dp_components
-hdl_library_clause_name = dp_components_lib
-hdl_lib_uses_synth = common_pkg common_components dp_pkg
-hdl_lib_uses_sim = 
-hdl_lib_technology = 
-
-synth_files =
-    dp_latency_increase.vhd
-    dp_latency_adapter.vhd
-    dp_hold_ctrl.vhd
-    dp_hold_input.vhd
-   
-test_bench_files = 
-    tb_dp_latency_adapter.vhd
-
-regression_test_vhdl = 
-    tb_dp_latency_adapter.vhd
-    
-[modelsim_project_file]
-
-
-[quartus_project_file]
diff --git a/cores/base/dp/dp_components/tb_dp_latency_adapter.vhd b/cores/base/dp/dp_components/tb_dp_latency_adapter.vhd
deleted file mode 100644
index b4b1633b68030f936d48417f5225bee3bb166d72..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_components/tb_dp_latency_adapter.vhd
+++ /dev/null
@@ -1,254 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
-ENTITY tb_dp_latency_adapter IS
-END tb_dp_latency_adapter;
-
-
-ARCHITECTURE tb OF tb_dp_latency_adapter IS
-
-  -- See tb_dp_pkg.vhd for explanation and run time
-  
-  SUBTYPE t_dut_range  IS INTEGER RANGE -1 to INTEGER'HIGH; 
-
-  TYPE t_dut_natural_arr  IS ARRAY (t_dut_range RANGE <>) OF NATURAL;
-  TYPE t_dut_data_arr     IS ARRAY (t_dut_range RANGE <>) OF STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
-  TYPE t_dut_logic_arr    IS ARRAY (t_dut_range RANGE <>) OF STD_LOGIC;  -- can not use STD_LOGIC_VECTOR because of integer range 
-  
-  -- TX ready latency to DUT chain
-  CONSTANT c_tx_latency     : NATURAL := 3;
-  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 := 7;              -- sop in data valid cycle 3,  10,  17, ...
-  CONSTANT c_tx_offset_eop  : NATURAL := 5;              -- eop in data valid cycle   5,  12,  19, ...
-  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;
-  
-  -- The TB supports using 1 or more dp_latency_adapter Devices Under Test in a chain. DUT 0 is the first DUT and it
-  -- gets the tx_data from this test bench, which has index -1. Each next DUT gets its input from the previous DUT,
-  -- hence the ready latency between DUTs should be the same.
-  -- The output latency of the previous must equal the input latency of the next DUT, hence it is sufficient to define
-  -- only the DUT output latencies.
-  --CONSTANT c_dut_latency    : t_dut_natural_arr := (c_tx_latency, 3);  -- verify single dp_latency_adapter with only wires
-  --CONSTANT c_dut_latency    : t_dut_natural_arr := (c_tx_latency, 4);  -- verify single dp_latency_adapter with latency increase
-  --CONSTANT c_dut_latency    : t_dut_natural_arr := (c_tx_latency, 1);  -- verify single dp_latency_adapter with latency decrease
-  CONSTANT c_dut_latency    : t_dut_natural_arr := (c_tx_latency, 1, 2, 0, 5, 5, 2, 1, 0, 7);
-  
-  -- The nof dut latencies in the c_dut_latency array automatically also defines the nof DUTs c_nof_dut.
-  CONSTANT c_nof_dut        : NATURAL := c_dut_latency'HIGH+1;
-  
-  -- RX ready latency from DUT chain
-  CONSTANT c_rx_latency     : NATURAL := c_dut_latency(c_nof_dut-1);
-  
-  CONSTANT c_verify_en_wait : NATURAL := 10+c_nof_dut*2;  -- wait some cycles before asserting verify enable
-  
-  CONSTANT c_empty_offset   : NATURAL := 1;
-  CONSTANT c_channel_offset : NATURAL := 2;
-  
-  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);
-  SIGNAL tx_val         : STD_LOGIC_VECTOR(0 TO c_tx_latency + c_tx_void);
-  
-  SIGNAL in_ready       : STD_LOGIC;
-  SIGNAL in_data        : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
-  SIGNAL in_sync        : STD_LOGIC;
-  SIGNAL in_val         : STD_LOGIC;
-  SIGNAL in_sop         : STD_LOGIC;
-  SIGNAL in_eop         : STD_LOGIC;
-  
-  -- DUT index -1 = in_data
-  SIGNAL dut_ready      : t_dut_logic_arr(-1 TO c_nof_dut-1);  -- SISO
-  SIGNAL dut_data       : t_dut_data_arr(-1 TO c_nof_dut-1);   -- SOSI
-  SIGNAL dut_empty      : t_dut_data_arr(-1 TO c_nof_dut-1) := (OTHERS=>(OTHERS=>'0'));
-  SIGNAL dut_channel    : t_dut_data_arr(-1 TO c_nof_dut-1) := (OTHERS=>(OTHERS=>'0'));
-  SIGNAL dut_sync       : t_dut_logic_arr(-1 TO c_nof_dut-1);
-  SIGNAL dut_val        : t_dut_logic_arr(-1 TO c_nof_dut-1);
-  SIGNAL dut_sop        : t_dut_logic_arr(-1 TO c_nof_dut-1);
-  SIGNAL dut_eop        : t_dut_logic_arr(-1 TO c_nof_dut-1);
-  -- DUT index c_nof_dut-1 = out_data
-  SIGNAL dut_siso       : t_dp_siso_arr(-1 TO c_nof_dut-1);
-  SIGNAL dut_sosi       : t_dp_sosi_arr(-1 TO c_nof_dut-1) := (OTHERS=>c_dp_sosi_rst);
-  
-  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_empty      : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
-  SIGNAL out_channel    : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
-  SIGNAL out_sync       : STD_LOGIC;
-  SIGNAL out_val        : STD_LOGIC;
-  SIGNAL out_sop        : STD_LOGIC;
-  SIGNAL out_eop        : STD_LOGIC;
-  SIGNAL hold_out_sop   : 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 exp_data       : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := TO_UVEC(19555, c_dp_data_w);
-  
-BEGIN
-
-  -- Use intervals marked by sync to start a new test named by state.
-  --
-  -- Under all circumstances the out_data should not mis or duplicate a count
-  -- while out_val is asserted as checked by p_verify.
-  -- The throughput must remain 100%, with only some increase in latency. This
-  -- can be checked manually by checking that cnt_val does not toggle when the
-  -- out_ready is asserted continuously. E.g. check that the out_data value 
-  -- is sufficiently high given the number of sync intervals that have passed.
-  --
-  -- Stimuli to verify the dp_latency_adapter DUT:
-  --
-  -- * Use various ready latency combinations in c_dut_latency:
-  --   .     c_in_latency > c_out_latency = 0
-  --   .     c_in_latency > c_out_latency > 0
-  --   .     c_in_latency = c_out_latency = 0
-  --   .     c_in_latency = c_out_latency > 0
-  --   . 0 = c_in_latency < c_out_latency
-  --   . 0 < c_in_latency < c_out_latency
-  --
-  -- * Manipulate the stimuli in:
-  --   . p_cnt_en    : cnt_en not always active when in_ready is asserted
-  --   . p_out_ready : out_ready not always active
-
-  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;
-  
-  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);
-  
-  -- Stimuli control
-  proc_dp_count_en(rst, clk, sync, lfsr1, state, verify_done, tb_end, 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);
-  proc_dp_verify_data("out_data", c_rx_latency, clk, verify_en, out_ready, out_val, out_data, prev_out_data);
-  proc_dp_verify_valid(c_rx_latency, clk, verify_en, out_ready, prev_out_ready, out_val);
-  proc_dp_verify_ctrl(c_tx_offset_sync, c_tx_period_sync, "sync", clk, verify_en, out_data, out_val, out_sync);
-  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);
-  proc_dp_verify_sop_and_eop(c_rx_latency, FALSE, clk, out_val, out_val, out_sop, out_eop, hold_out_sop);  -- Verify that sop and eop come in pairs, no check on valid between eop and sop
-  proc_dp_verify_other_sosi("empty", INCR_UVEC(out_data, c_empty_offset), clk, verify_en, out_empty);
-  proc_dp_verify_other_sosi("channel", INCR_UVEC(out_data, c_channel_offset), clk, verify_en, out_channel);
-
-  -- Check that the test has ran at all
-  proc_dp_verify_value(e_equal, clk, verify_done, exp_data, out_data);
-  
-  ------------------------------------------------------------------------------
-  -- Chain of 1 or more dp_latency_adapter DUTs
-  --
-  -- . Note this also models a series of streaming modules in a data path
-  --
-  ------------------------------------------------------------------------------
-  
-  -- Map the test bench tx counter data to the input of the chain
-  in_ready        <= dut_ready(-1);
-  dut_data(-1)    <=           in_data;
-  dut_empty(-1)   <= INCR_UVEC(in_data, c_empty_offset);
-  dut_channel(-1) <= INCR_UVEC(in_data, c_channel_offset);
-  dut_sync(-1)    <= in_sync;
-  dut_val(-1)     <= in_val;
-  dut_sop(-1)     <= in_sop;
-  dut_eop(-1)     <= in_eop;
-  
-  -- map sl, slv to record
-  dut_ready(-1) <= dut_siso(-1).ready;                           -- SISO
-  dut_sosi(-1).data(c_dp_data_w-1 DOWNTO 0) <= dut_data(-1);     -- SOSI
-  dut_sosi(-1).empty                        <= dut_empty(-1)(c_dp_empty_w-1 DOWNTO 0);
-  dut_sosi(-1).channel                      <= dut_channel(-1)(c_dp_channel_w-1 DOWNTO 0);
-  dut_sosi(-1).sync                         <= dut_sync(-1);
-  dut_sosi(-1).valid                        <= dut_val(-1);
-  dut_sosi(-1).sop                          <= dut_sop(-1);
-  dut_sosi(-1).eop                          <= dut_eop(-1);
-    
-  gen_chain : FOR I IN 0 TO c_nof_dut-1 GENERATE
-    dut : ENTITY work.dp_latency_adapter
-    GENERIC MAP (
-      g_in_latency  => c_dut_latency(I-1),
-      g_out_latency => c_dut_latency(I)
-    )
-    PORT MAP (
-      rst       => rst,
-      clk       => clk,
-      -- ST sink
-      snk_out   => dut_siso(I-1),
-      snk_in    => dut_sosi(I-1),
-      -- ST source
-      src_in    => dut_siso(I),
-      src_out   => dut_sosi(I)
-    );
-  END GENERATE;
-
-  -- map record to sl, slv
-  dut_siso(c_nof_dut-1).ready <= dut_ready(c_nof_dut-1);                                                      -- SISO
-  dut_data(c_nof_dut-1)                               <= dut_sosi(c_nof_dut-1).data(c_dp_data_w-1 DOWNTO 0);  -- SOSI
-  dut_empty(c_nof_dut-1)(c_dp_empty_w-1 DOWNTO 0)     <= dut_sosi(c_nof_dut-1).empty;
-  dut_channel(c_nof_dut-1)(c_dp_channel_w-1 DOWNTO 0) <= dut_sosi(c_nof_dut-1).channel;
-  dut_sync(c_nof_dut-1)                               <= dut_sosi(c_nof_dut-1).sync;
-  dut_val(c_nof_dut-1)                                <= dut_sosi(c_nof_dut-1).valid;
-  dut_sop(c_nof_dut-1)                                <= dut_sosi(c_nof_dut-1).sop;
-  dut_eop(c_nof_dut-1)                                <= dut_sosi(c_nof_dut-1).eop;
-  
-  -- Map the output of the DUT chain to the test bench output data
-  dut_ready(c_nof_dut-1) <= out_ready;
-  out_data               <= dut_data(c_nof_dut-1);
-  out_empty              <= dut_empty(c_nof_dut-1);
-  out_channel            <= dut_channel(c_nof_dut-1);
-  out_sync               <= dut_sync(c_nof_dut-1);
-  out_val                <= dut_val(c_nof_dut-1);
-  out_sop                <= dut_sop(c_nof_dut-1);
-  out_eop                <= dut_eop(c_nof_dut-1);
-    
-END tb;
diff --git a/cores/base/dp/dp_counter/dp_counter.vhd b/cores/base/dp/dp_counter/dp_counter.vhd
deleted file mode 100644
index 6e92fe1af263e3fd51c38223b00c3a44318db97a..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_counter/dp_counter.vhd
+++ /dev/null
@@ -1,213 +0,0 @@
---------------------------------------------------------------------------------
---
--- Copyright (C) 2017
--- 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/>.
---
---------------------------------------------------------------------------------
-
--- Author:
--- . Daniel van der Schuur
--- Purpose:
--- . Pipeline wrapper around dp_counter_func
--- Description:
--- . See dp_counter_func.
--- . dp_counter_func contains only functional logic (no pipelining).
--- . This wrapper adds pipelining for the source side outputs (g_pipeline_src_out)
---   and source side inputs (g_pipeline_src_in).
--- Usage:
--- . When g_nof_counters = 1 then dp_counter can reshape the block sizes in a
---   sync intervals, as is done in dp_block_reshape.vhd
--- . When g_nof_counters = 2 then dp_counter can reshape the block sizes and the
---   sync interval, as is done in dp_block_reshape_sync.vhd
--- . When g_nof_counters > 1 then the dp_counter count_src_out_arr provides the 
---   block indices for an array of data. The g_nof_counters then defines the 
---   dimension of the array within a sync interval. For example:
---
---     a[N][M][P] with N=3, M=5, p=10 will have N*M*P = 150 valid per sync interval. 
---
---   The dp_counter can then provide for each valid in the sync interval the
---   corresponding array index (n, m, p), using:
---
---     g_nof_counters = 3
---     g_range_start  = (0, 0,  0)
---     g_range_stop   = (3, 5, 10)
---     g_range_step   = (1, 1,  1)
---
--- Remarks:
--- . Unfortunately it is not possible to use a generic in the definition of another generic. Therefore the
---   g_range_* generics are defined as unconstraint.
--- . When dp_counter is instanciated the length of the g_range_* generics must at least fit g_nof_counters.
---   In theory count_src_out_arr could be declared as unconstraint and then g_nof_counters could be derived
---   from the length of count_src_out_arr, but it is more clear to explitely to declare g_nof_counters.
---
---   31-05-2018 J Hargreaves added count_offset_in_arr input
---     This signal can be used to apply an offset to the start count
---   USAGE
---     Do not connect the signal if it is not needed: It will consume extra resources
---     It only works when g_range_step(i) is 1
---     It only works when g_range_start(i) + count_offset_in_arr(i) < g_range_stop(i)
---     Any other useage will break counters >= stage i
-
-LIBRARY IEEE, dp_pipeline_lib, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ENTITY dp_counter IS
-  GENERIC (
-    g_nof_counters     : NATURAL := 1;
-    g_range_start      : t_nat_natural_arr;  -- range must fit (g_nof_counters-1 DOWNTO 0)
-    g_range_stop       : t_nat_natural_arr;  -- range must fit (g_nof_counters-1 DOWNTO 0)
-    g_range_step       : t_nat_natural_arr;  -- range must fit (g_nof_counters-1 DOWNTO 0)
-    g_pipeline_src_out : NATURAL := 1;       -- Pipeline source outputs (data,valid,sop,eop etc)
-    g_pipeline_src_in  : NATURAL := 0        -- Pipeline source inputs (ready,xon). This will also pipeline src_out.
-  );
-  PORT (                                                    
-    clk         : IN  STD_LOGIC;
-    rst         : IN  STD_LOGIC;
-
-    snk_in      : IN  t_dp_sosi;
-    snk_out     : OUT t_dp_siso;
-
-    src_out     : OUT t_dp_sosi;
-    src_in      : IN  t_dp_siso := c_dp_siso_rdy;
-
-    count_offset_in_arr : IN  t_nat_natural_arr(g_nof_counters-1 DOWNTO 0) := (OTHERS=>0);  
-    count_src_out_arr : OUT t_dp_sosi_arr(g_nof_counters-1 DOWNTO 0)
-  );
-END dp_counter;
-
-
-ARCHITECTURE wrap OF dp_counter IS
-
-  -- force downto range for unconstraint g_range generics
-  CONSTANT c_range_len             : NATURAL := g_range_start'LENGTH;  -- g_nof_counters must be <= c_range_len
-  CONSTANT c_range_start           : t_nat_natural_arr(c_range_len-1 DOWNTO 0) := g_range_start;
-  CONSTANT c_range_stop            : t_nat_natural_arr(c_range_len-1 DOWNTO 0) := g_range_stop;
-  CONSTANT c_range_step            : t_nat_natural_arr(c_range_len-1 DOWNTO 0) := g_range_step;
-
-  CONSTANT c_use_dp_pipeline       : BOOLEAN := (g_pipeline_src_out>0 AND g_pipeline_src_in=0);
-  CONSTANT c_use_dp_pipeline_ready : BOOLEAN := (g_pipeline_src_in>0);
-
-  SIGNAL dp_counter_func_src_out_arr : t_dp_sosi_arr(g_nof_counters-1 DOWNTO 0);
-
-BEGIN
-
-  ------------------------------------------------------------------------------
-  -- dp_counter_func
-  ------------------------------------------------------------------------------ 
-  u_dp_counter_func : ENTITY work.dp_counter_func
-  GENERIC MAP (
-    g_nof_counters => g_nof_counters,
-    g_range_start  => c_range_start,
-    g_range_stop   => c_range_stop,
-    g_range_step   => c_range_step
-  )
-  PORT MAP (
-    rst       => rst,
-    clk       => clk,
-
-    count_en  => snk_in.valid,
-
-    count_offset_in_arr => count_offset_in_arr,
-    count_src_out_arr   => dp_counter_func_src_out_arr
-  );
-  
-  ------------------------------------------------------------------------------
-  -- dp_pipeline
-  ------------------------------------------------------------------------------
-  gen_dp_pipeline : IF c_use_dp_pipeline = TRUE GENERATE
-    u_dp_pipeline_snk_in : ENTITY dp_pipeline_lib.dp_pipeline
-    GENERIC MAP (
-      g_pipeline => g_pipeline_src_out
-    )
-    PORT MAP (
-      clk         => clk,
-      rst         => rst,
-  
-      snk_in      => snk_in,
-      snk_out     => snk_out,
-  
-      src_out     => src_out,
-      src_in      => src_in
-    );
-
-    gen_dp_pipeline_count_src_out_arr : FOR i IN 0 TO g_nof_counters-1 GENERATE
-      u_dp_pipeline_count_src_out_arr : ENTITY dp_pipeline_lib.dp_pipeline
-      GENERIC MAP (
-        g_pipeline => g_pipeline_src_out
-      )
-      PORT MAP (
-        clk     => clk,
-        rst     => rst,
-    
-        snk_in  => dp_counter_func_src_out_arr(i),
-    
-        src_out => count_src_out_arr(i),
-        src_in  => src_in
-      );
-    END GENERATE;
-  END GENERATE;
-
-  ------------------------------------------------------------------------------
-  -- dp_pipeline_ready
-  ------------------------------------------------------------------------------
-  gen_dp_pipeline_ready : IF c_use_dp_pipeline_ready = TRUE GENERATE
-    u_dp_pipeline_ready : ENTITY dp_pipeline_lib.dp_pipeline_ready
-    GENERIC MAP (
-      g_in_latency   => 1
-    )
-    PORT MAP (
-      clk          => clk,
-      rst          => rst,
-  
-      snk_in       => snk_in,
-      snk_out      => snk_out,
-  
-      src_out      => src_out,
-      src_in       => src_in
-    );
-
-    gen_dp_pipeline_ready_count_src_out_arr : FOR i IN 0 TO g_nof_counters-1 GENERATE
-      u_dp_pipeline_ready_count_src_out_arr : ENTITY dp_pipeline_lib.dp_pipeline_ready
-      GENERIC MAP (
-        g_in_latency => 1
-      )
-      PORT MAP (
-        clk     => clk,
-        rst     => rst,
-    
-        snk_in  => dp_counter_func_src_out_arr(i),
-    
-        src_out => count_src_out_arr(i),
-        src_in  => src_in
-      );
-    END GENERATE;
-  END GENERATE;  
-
-  ------------------------------------------------------------------------------
-  -- No pipelining
-  ------------------------------------------------------------------------------
-  no_dp_pipeline : IF c_use_dp_pipeline=FALSE AND c_use_dp_pipeline_ready=FALSE GENERATE
-    src_out <= snk_in;
-    snk_out <= src_in;
-    
-    count_src_out_arr <= dp_counter_func_src_out_arr;
-  END GENERATE;
-
-END wrap;
diff --git a/cores/base/dp/dp_counter/dp_counter_func.vhd b/cores/base/dp/dp_counter/dp_counter_func.vhd
deleted file mode 100644
index 188250c85c45a2fcdb8da3c40caae92b244b4316..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_counter/dp_counter_func.vhd
+++ /dev/null
@@ -1,139 +0,0 @@
---------------------------------------------------------------------------------
---
--- Copyright (C) 2017
--- 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/>.
---
---------------------------------------------------------------------------------
-
--- Author:
--- . Daniel van der Schuur
--- Purpose:
--- . Provide an array of counters with dimension carryover
--- Description:
--- . Provides g_nof_counters counters,[g_nof_counters-1]..[c0]
--- . Every counter is specified like Python's range(start,stop,step).
--- . c0 changes the fastest, c4 changes the slowest
--- . Faster changing dimensions carry over in slower changing dimensions 
---   when dimension maximum is reached
--- . The outputs are in sync with / apply to src_out.
--- . range(0,1,1) = [0] is the smallest count range
--- Usage:
--- . The count values themselves (c0..c4) are very useful to tag streaming
---   data with corresponding ID indices.
--- . The extra outputs (e.g. c0_min, c0_max) can be used to trigger other
---   logic when minimum/maximum values per dimension are reached.
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ENTITY dp_counter_func IS
-  GENERIC (
-    g_nof_counters    : NATURAL := 1;
-    g_range_start     : t_nat_natural_arr;  -- range must fit (g_nof_counters-1 DOWNTO 0)
-    g_range_stop      : t_nat_natural_arr;  -- range must fit (g_nof_counters-1 DOWNTO 0)
-    g_range_step      : t_nat_natural_arr   -- range must fit (g_nof_counters-1 DOWNTO 0)
-  );
-  PORT (                                                    
-    clk         : IN  STD_LOGIC;
-    rst         : IN  STD_LOGIC;
-
-    count_en    : IN  STD_LOGIC;
-  
-    count_offset_in_arr : IN  t_nat_natural_arr(g_nof_counters-1 DOWNTO 0) := (OTHERS=>0);  
-    count_src_out_arr   : OUT t_dp_sosi_arr(g_nof_counters-1 DOWNTO 0)
-  );
-END dp_counter_func;
-
-
-ARCHITECTURE str OF dp_counter_func IS
-
-  -- force downto range for unconstraint g_range generics
-  CONSTANT c_range_len             : NATURAL := g_range_start'LENGTH;  -- g_nof_counters must be <= c_range_len
-  CONSTANT c_range_start           : t_nat_natural_arr(c_range_len-1 DOWNTO 0) := g_range_start;
-  CONSTANT c_range_stop            : t_nat_natural_arr(c_range_len-1 DOWNTO 0) := g_range_stop;
-  CONSTANT c_range_step            : t_nat_natural_arr(c_range_len-1 DOWNTO 0) := g_range_step;
-  
-  CONSTANT c_max_count_w : NATURAL := 32;
-
-  SIGNAL count_en_arr   : STD_LOGIC_VECTOR(g_nof_counters-1 DOWNTO 0);
-  SIGNAL check_max_arr  : STD_LOGIC_VECTOR(g_nof_counters-1 DOWNTO 0);
-  SIGNAL count_init_arr : STD_LOGIC_VECTOR(g_nof_counters-1 DOWNTO 0);
-  SIGNAL count_min_arr  : STD_LOGIC_VECTOR(g_nof_counters-1 DOWNTO 0);
-  SIGNAL count_max_arr  : STD_LOGIC_VECTOR(g_nof_counters-1 DOWNTO 0);
-  TYPE t_count_arr IS ARRAY(g_nof_counters-1 DOWNTO 0) OF STD_LOGIC_VECTOR(c_max_count_w-1 DOWNTO 0);
-  SIGNAL count_arr      : t_count_arr;
-
-BEGIN
-
-  --------------------------------------------------------------------------------
-  -- Counter control inputs
-  -------------------------------------------------------------------------------
-  gen_dp_counter_func_single_input : FOR i IN 0 TO g_nof_counters-1 GENERATE
-
-    gen_c0 : IF i=0 GENERATE
-      count_en_arr(i)  <= count_en;
-      check_max_arr(i) <= count_en;
-    END GENERATE;
-
-    gen_c1_upwards : IF i>0 GENERATE
-       count_en_arr(i)  <= count_init_arr(i-1) OR count_min_arr(i-1);
-       check_max_arr(i) <= count_max_arr(i-1);
-    END GENERATE;
-
-  END GENERATE;
-
-  --------------------------------------------------------------------------------
-  -- Array of dp_counter_func_single instances
-  -------------------------------------------------------------------------------
-  gen_dp_counter_func_single : FOR i IN 0 TO g_nof_counters-1 GENERATE
-    u_dp_counter_func_single : ENTITY work.dp_counter_func_single
-    GENERIC MAP (
-      g_range_start => c_range_start(i),
-      g_range_stop  => c_range_stop(i),
-      g_range_step  => c_range_step(i)
-    )
-    PORT MAP (
-      rst        => rst,
-      clk        => clk,
-   
-      count_en   => count_en_arr(i),
-      check_max  => check_max_arr(i),
-      count_offset => count_offset_in_arr(i),
-   
-      count      => count_arr(i),
-      count_init => count_init_arr(i),
-      count_min  => count_min_arr(i),
-      count_max  => count_max_arr(i)
-    );
-  END GENERATE;
- 
-  --------------------------------------------------------------------------------
-  -- Counter outputs
-  -------------------------------------------------------------------------------
-  gen_dp_counter_func_single_output : FOR i IN 0 TO g_nof_counters-1 GENERATE
-    count_src_out_arr(i).sync <= '0';  -- not used, force to '0' to avoid toggling between '0' and 'X' in Wave window
-                                       -- when sync is passed on through other components
-    count_src_out_arr(i).sop <= count_min_arr(i);
-    count_src_out_arr(i).eop <= count_max_arr(i);
-    count_src_out_arr(i).valid <= count_en;
-    count_src_out_arr(i).data <= RESIZE_DP_DATA(count_arr(i));
-  END GENERATE;
-    
-END str;
diff --git a/cores/base/dp/dp_counter/dp_counter_func_single.vhd b/cores/base/dp/dp_counter/dp_counter_func_single.vhd
deleted file mode 100644
index 7281e35970e3b8a343554998e78dde688e9015ba..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_counter/dp_counter_func_single.vhd
+++ /dev/null
@@ -1,152 +0,0 @@
---------------------------------------------------------------------------------
---
--- Copyright (C) 2017
--- 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/>.
---
---------------------------------------------------------------------------------
-
--- Author:
--- . Daniel van der Schuur
--- Purpose:
--- . Simple counter with start, stop, step; used in dp_counter_func.
--- Description:
--- . range(0,2,1) = [0, 1] is the smallest count range allowed
--- Usage:
--- . Not for standalone use; part of dp_counter_func.
- 
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ENTITY dp_counter_func_single IS --FIXME move this to common
-  GENERIC (
-    g_range_start : NATURAL; -- (start,stop,step) like python range(start, stop, step)
-    g_range_stop  : NATURAL;
-    g_range_step  : NATURAL
-  );
-  PORT (                                                    
-    clk        : IN  STD_LOGIC;
-    rst        : IN  STD_LOGIC;
-
-    count_en   : IN STD_LOGIC;
-    check_max  : IN STD_LOGIC := '1';
-    count_offset : NATURAL := 0;
-   
-    count      : OUT STD_LOGIC_VECTOR(31 DOWNTO 0);
-    count_init : OUT STD_LOGIC; -- Pulses at first init
-    count_min  : OUT STD_LOGIC; --Pulses when count=start
-    count_max  : OUT STD_LOGIC  --Pulses when count=max
-  );
-END dp_counter_func_single;
-
-
-ARCHITECTURE rtl OF dp_counter_func_single IS
-
- -- The user defines the counters like a Python range(start,stop,step) in which the stop value
-  -- is never actually reached. Calculate the actual maximum values here.
-  -- . Example:
-  --   . range(0,4,2) = [0, 2]
-  --   . range(0,5,2) = [0, 2, 4]
-  --   . range(0,6,2) = [0, 2, 4]
-  --   . range(0,7,2) = [0, 2, 4, 6]
-  --   . range(1,7,2) = [1, 3, 5]
-  -- . The maximum value is: start+((stop-1-start)/step)*step
-  CONSTANT c_nof_count : NATURAL := (g_range_stop-1-g_range_start)/g_range_step + 1;
-  CONSTANT c_count_max : NATURAL := g_range_start+(c_nof_count-1)*g_range_step;
-  CONSTANT c_count_w   : NATURAL := ceil_log2(c_count_max+1);
-
-  TYPE t_reg IS RECORD
-    count_en  : STD_LOGIC;
-    count     : STD_LOGIC_VECTOR(c_count_w-1 DOWNTO 0);
-    count_min : STD_LOGIC;
-    count_max : STD_LOGIC;
-    count_init : STD_LOGIC;
-  END RECORD;
-
-  SIGNAL r, nxt_r : t_reg;
-
-BEGIN
-  
-  --------------------------------------------------------------------------------
-  -- Combinational logic
-  --------------------------------------------------------------------------------
-  p_comb : PROCESS(rst, r, count_en, check_max, count_offset) 
-    VARIABLE v : t_reg;
-  BEGIN
-    v           := r;
-    v.count_min := '0';
-    v.count_max := '0';
-    v.count_init := '0';
-
-    IF count_en='1' THEN
-
-      -- Start counting / init
-      IF r.count_en='0' THEN
-        v.count_en := '1';
-        v.count := TO_UVEC(g_range_start+count_offset, c_count_w);
-        v.count_min := '1';
-        v.count_init := '1';     
-      -- keep counting
-      ELSE
-        v.count := INCR_UVEC(r.count, g_range_step);
-        IF c_count_max>0 AND check_max='1' AND r.count = TO_UVEC(c_count_max-g_range_step, c_count_w) THEN -- count max almost reached
-          v.count_max := '1';
-        ELSIF r.count = TO_UVEC(c_count_max, c_count_w) THEN -- count max reached
-          -- Reset count to start value
-          v.count := TO_UVEC(g_range_start, c_count_w);
-          v.count_min := '1';
-        END IF;
-      END IF;
-
-      -- If the maximum count is 0, count_max is always high.
-      IF c_count_max=0 THEN
-        v.count_max := '1';       
-      END IF;   
-
-    ELSIF check_max='1' AND r.count = TO_UVEC(c_count_max, c_count_w) THEN -- count max reached
-      v.count_max := '1';
-    END IF;
-   
-    IF rst = '1' THEN
-      v.count_en  := '0';
-      v.count     := (OTHERS=>'0');
-      v.count_min := '0';
-      v.count_max := '0';
-      v.count_init := '0';
-    END IF;
- 
-    nxt_r <= v;
-  END PROCESS;
-
-  --------------------------------------------------------------------------------
-  -- Register stage
-  --------------------------------------------------------------------------------
-  r <= nxt_r WHEN rising_edge(clk);
-
-  --------------------------------------------------------------------------------
-  -- Outputs
-  --------------------------------------------------------------------------------
-  count(31 DOWNTO c_count_w)  <= (OTHERS=>'0');
-  count(c_count_w-1 DOWNTO 0) <= nxt_r.count;
-  count_init <= nxt_r.count_init;
-  count_min  <= nxt_r.count_min;
-  count_max  <= nxt_r.count_max;
-
-
-END rtl;
diff --git a/cores/base/dp/dp_counter/hdllib.cfg b/cores/base/dp/dp_counter/hdllib.cfg
deleted file mode 100644
index 0df6e6b19279d7ca761b602abdff627c169fa445..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_counter/hdllib.cfg
+++ /dev/null
@@ -1,24 +0,0 @@
-hdl_lib_name = dp_counter
-hdl_library_clause_name = dp_counter_lib
-hdl_lib_uses_synth = dp_pipeline
-hdl_lib_uses_sim = 
-hdl_lib_technology = 
-
-synth_files =
-    dp_counter_func_single.vhd
-    dp_counter_func.vhd
-    dp_counter.vhd
-   
-test_bench_files = 
-    tb_dp_counter_func.vhd
-    tb_dp_counter.vhd
-    tb_tb_dp_counter.vhd
-
-regression_test_vhdl = 
-    tb_dp_counter_func.vhd
-    tb_tb_dp_counter.vhd
-    
-[modelsim_project_file]
-
-
-[quartus_project_file]
diff --git a/cores/base/dp/dp_counter/tb_dp_counter.vhd b/cores/base/dp/dp_counter/tb_dp_counter.vhd
deleted file mode 100644
index 386a231b946fb2b37d10def31cfcb8562ea15267..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_counter/tb_dp_counter.vhd
+++ /dev/null
@@ -1,224 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2017
--- 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/>.
---
--------------------------------------------------------------------------------
-
--- Author:
---   Eric Kooistra, 23 Apr 2018
--- Purpose:
--- . Test bench for dp_counter.
--- Description:
---   Functional details are verified by tb_dp_counter_func.vhd. This
---   tb_dp_counter.vhd shows the dp_counter with pipelining.
---Usage:
--- . as 10
--- . run -all
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE common_pkg_lib.common_str_pkg.ALL;
-USE common_pkg_lib.common_lfsr_sequences_pkg.ALL;
-USE common_pkg_lib.tb_common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
-ENTITY tb_dp_counter IS
-  GENERIC (
-    -- general
-    g_flow_control_stimuli   : t_dp_flow_control_enum := e_active;  -- always active, random or pulse flow control
-    g_flow_control_verify    : t_dp_flow_control_enum := e_active;  -- always active, random or pulse flow control
-    -- dut
-    g_pipeline_src_out : NATURAL := 1;  -- Pipeline source outputs (data,valid,sop,eop etc)
-    g_pipeline_src_in  : NATURAL := 0;  -- Pipeline source inputs (ready,xon). This will also pipeline src_out.
-    g_nof_counters     : NATURAL := 3;
-    -- min range = [0,2,1] => (0,1) 'the Python way'
-    g_range_start      : t_nat_natural_arr(9 DOWNTO 0) := (0,0,0,0,0,0,0, 1, 0, 0);
-    g_range_stop       : t_nat_natural_arr(9 DOWNTO 0) := (2,2,2,2,2,2,7,16,16, 1);
-    g_range_step       : t_nat_natural_arr(9 DOWNTO 0) := (1,1,1,1,1,1,2, 2, 2, 1)
-  );
-END tb_dp_counter;
-
-
-ARCHITECTURE tb OF tb_dp_counter IS
-
-  ------------------------------------------------------------------------------
-  -- Clock & reset
-  ------------------------------------------------------------------------------
-  CONSTANT c_clk_period : TIME := 5 ns;
-  CONSTANT c_max_count_w : NATURAL := 32;
-
-  CONSTANT c_rl          : NATURAL := 1;
-  CONSTANT c_data_w      : NATURAL := 32;
-  CONSTANT c_data_init   : NATURAL := 0;
-  
-  SIGNAL clk            : STD_LOGIC := '1';
-  SIGNAL rst            : STD_LOGIC := '1';
-  SIGNAL tb_end         : STD_LOGIC := '0';
-
-  ------------------------------------------------------------------------------
-  -- dp_counter
-  ------------------------------------------------------------------------------ 
-  SIGNAL snk_in            : t_dp_sosi := c_dp_sosi_rst;
-  SIGNAL snk_out           : t_dp_siso;
-  SIGNAL src_out           : t_dp_sosi;
-  SIGNAL src_in            : t_dp_siso := c_dp_siso_rdy;
-  SIGNAL count_src_out_arr : t_dp_sosi_arr(g_nof_counters-1 DOWNTO 0);
-  SIGNAL period            : NATURAL;
-  
-  FUNCTION calculate_period(g_counter : NATURAL) RETURN NATURAL IS
-    VARIABLE v_range_period : t_nat_natural_arr(g_counter DOWNTO 0);
-    VARIABLE v_period       : NATURAL := 1;
-  BEGIN
-    FOR I IN 0 TO g_counter LOOP
-      v_range_period(I) := (g_range_stop(I)-1 - g_range_start(I)) / g_range_step(I) + 1;  -- Python style range(start, stop, step)
-      v_period := v_period * v_range_period(I);
-    END LOOP;
-    RETURN v_period;
-  END;
-  
-  ------------------------------------------------------------------------------
-  -- flow control
-  ------------------------------------------------------------------------------ 
-  CONSTANT c_in_random_w       : NATURAL := 15;
-  CONSTANT c_out_random_w      : NATURAL := 16;  -- use different length per random source
-  CONSTANT c_in_pulse_active   : NATURAL := 1;
-  CONSTANT c_out_pulse_active  : NATURAL := 1;
-  CONSTANT c_in_pulse_period   : NATURAL := 2;
-  CONSTANT c_out_pulse_period  : NATURAL := 2;
-  
-  SIGNAL in_random           : STD_LOGIC_VECTOR(c_in_random_w-1 DOWNTO 0) := TO_UVEC(1, c_in_random_w);
-  SIGNAL out_random          : STD_LOGIC_VECTOR(c_out_random_w-1 DOWNTO 0) := TO_UVEC(1, c_out_random_w);
-  SIGNAL in_pulse            : STD_LOGIC;
-  SIGNAL out_pulse           : STD_LOGIC;
-  SIGNAL in_pulse_en         : STD_LOGIC := '1';
-  SIGNAL out_pulse_en        : STD_LOGIC := '1';
-  
-  SIGNAL in_en          : STD_LOGIC := '0';
-  SIGNAL out_ready      : STD_LOGIC := '0';
-  
-  
-BEGIN
-  
-  ------------------------------------------------------------------------------
-  -- Flow control
-  ------------------------------------------------------------------------------
-  in_random <= func_common_random(in_random) WHEN rising_edge(clk);
-  out_random <= func_common_random(out_random) WHEN rising_edge(clk);
-  
-  proc_common_gen_duty_pulse(c_in_pulse_active, c_in_pulse_period, '1', rst, clk, in_pulse_en, in_pulse);
-  proc_common_gen_duty_pulse(c_out_pulse_active, c_out_pulse_period, '1', rst, clk, out_pulse_en, out_pulse);
-
-  in_en <= '1'                       WHEN g_flow_control_stimuli=e_active ELSE
-           in_random(in_random'HIGH) WHEN g_flow_control_stimuli=e_random ELSE
-           in_pulse                  WHEN g_flow_control_stimuli=e_pulse;
-
-  out_ready <= '1'                         WHEN g_flow_control_verify=e_active ELSE
-               out_random(out_random'HIGH) WHEN g_flow_control_verify=e_random ELSE
-               out_pulse                   WHEN g_flow_control_verify=e_pulse;
-                
-  src_in.ready <= out_ready;
-  src_in.xon <= NOT src_in.xon WHEN rising_edge(clk);  -- should have no effect, only passed on from src_in to snk_out
-
-  ------------------------------------------------------------------------------
-  -- Clock & reset
-  ------------------------------------------------------------------------------
-  clk <= (NOT clk) OR tb_end AFTER c_clk_period/2;
-  rst <= '1', '0' AFTER c_clk_period*7;
-  
-  ------------------------------------------------------------------------------
-  -- Stimuli: 
-  ------------------------------------------------------------------------------
-
-  -- Generate snk_in incrementing data with valid
-  proc_dp_gen_data(c_rl,
-                   c_data_w,
-                   c_data_init,
-                   rst,
-                   clk,
-                   in_en,
-                   snk_out,
-                   snk_in);
-  
-  p_stimuli : PROCESS
-  BEGIN
-    -- run some more intervals for slowest counter, to more view how the slowest counter behaves
-    FOR I IN 0 TO 2 LOOP
-      proc_common_wait_until_hi_lo(clk, count_src_out_arr(g_nof_counters-1).eop);  -- wait for carry over
-    END LOOP;
-    
-    tb_end <= '1';    
-    WAIT;
-  END PROCESS;
-
-  ------------------------------------------------------------------------------
-  -- DUT
-  ------------------------------------------------------------------------------     
-  u_dp_counter : ENTITY work.dp_counter
-  GENERIC MAP (
-    g_nof_counters     => g_nof_counters,
-    g_range_start      => g_range_start,
-    g_range_stop       => g_range_stop,
-    g_range_step       => g_range_step,
-    g_pipeline_src_out => g_pipeline_src_out,
-    g_pipeline_src_in  => g_pipeline_src_in
-  )
-  PORT MAP (
-    rst               => rst,
-    clk               => clk,
-
-    snk_in            => snk_in,
-    snk_out           => snk_out,
-
-    src_out           => src_out,
-    src_in            => src_in,
-
-    count_src_out_arr => count_src_out_arr
-  );
-  
-  ------------------------------------------------------------------------------
-  -- Verification
-  --   Verify dp_counter using the counter data from the stimuli as reference.
-  --   Only verify the dp_counter for the highest counter, because that covers
-  --   also the low level counters. The details of dp_counter_func are tested
-  --   in tb_dp_counter_func.vhd.
-  ------------------------------------------------------------------------------
-  p_verify : PROCESS(clk)
-    CONSTANT c_period  : NATURAL := calculate_period(g_nof_counters-1);
-    
-    VARIABLE v_cnt : NATURAL := 0;
-  BEGIN
-    period <= c_period;  -- to view c_period in wave window
-    IF rising_edge(clk) THEN
-      IF count_src_out_arr(g_nof_counters-1).valid='1' THEN
-        ASSERT v_cnt = TO_UINT(src_out.data) REPORT "Wrong cnt at valid : " & int_to_str(v_cnt) SEVERITY ERROR;
-        IF count_src_out_arr(g_nof_counters-1).sop='1' THEN
-          ASSERT v_cnt MOD c_period = 0 REPORT "Wrong cnt at sop : " & int_to_str(v_cnt) SEVERITY ERROR;
-        END IF;
-        IF count_src_out_arr(g_nof_counters-1).eop='1' THEN
-          ASSERT v_cnt MOD c_period = c_period-1 REPORT "Wrong cnt at eop : " & int_to_str(v_cnt) SEVERITY ERROR;
-        END IF;
-        v_cnt := v_cnt + 1;
-      END IF;
-    END IF;
-  END PROCESS;
-  
-END tb;
diff --git a/cores/base/dp/dp_counter/tb_dp_counter_func.vhd b/cores/base/dp/dp_counter/tb_dp_counter_func.vhd
deleted file mode 100644
index 3ac3804f058b6f66683b1161b4037339d7b3ab88..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_counter/tb_dp_counter_func.vhd
+++ /dev/null
@@ -1,249 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2017
--- 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/>.
---
--------------------------------------------------------------------------------
-
--- Author:
--- . initial, Daniel van der Schuur
---   Pieter Donker, Mar-2018, filled in verify process. 
---   Pieter Donker, Apr-2018, add stop test. 
--- Purpose:
--- . Test bench for dp_counter_func
--- Description:
--- . dp_counter_func contains *only* the function
---   . so no flow control (taken care of in dp_counter.vhd wrapper)
---   . so no pipelining   (taken care of in dp_counter.vhd wrapper)
--- . The above means that this TB does not have to cover flow control or
---   pipelining either, which greatly simplifies things.
---Usage:
--- . as 10
--- . run -all
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE common_pkg_lib.common_str_pkg.ALL;
-USE common_pkg_lib.common_lfsr_sequences_pkg.ALL;
-USE common_pkg_lib.tb_common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
-ENTITY tb_dp_counter_func IS
-  GENERIC (
-    g_nof_counters : NATURAL := 2;
-    -- min range = [0,2,1] => (0,1) 'the python way'
-    g_range_start  : t_nat_natural_arr(9 DOWNTO 0) := (0,0,0,0,0,0,0, 1, 0, 0);
-    g_range_stop   : t_nat_natural_arr(9 DOWNTO 0) := (2,2,2,2,2,2,7,16,16,16);
-    g_range_step   : t_nat_natural_arr(9 DOWNTO 0) := (1,1,1,1,1,1,2, 2, 2, 1)
-  );
-END tb_dp_counter_func;
-
-
-ARCHITECTURE tb OF tb_dp_counter_func IS
-
-  ------------------------------------------------------------------------------
-  -- Clock & reset
-  ------------------------------------------------------------------------------
-  CONSTANT c_clk_period : TIME := 5 ns;
-  CONSTANT c_max_count_w : NATURAL := 32;
-
-  SIGNAL clk            : STD_LOGIC := '1';
-  SIGNAL rst            : STD_LOGIC := '1';
-
-  ------------------------------------------------------------------------------
-  -- dp_counter_func
-  ------------------------------------------------------------------------------ 
-  SIGNAL dp_counter_func_count_en          : STD_LOGIC := '0';
-  SIGNAL dp_counter_func_count_src_out_arr : t_dp_sosi_arr(g_nof_counters-1 DOWNTO 0);
-  
-  -- It is difficult / not possible to avoid the glitches in the dp_counter_func outputs, because
-  -- dp_counter_func intentionally works combinatorially, so its outputs can vary during a few
-  -- delta-cycles, before the finalize. Therefore use a pipeline debug signal to view the outputs
-  -- without the combinatorial glitches in the wave window. 
-  SIGNAL dp_counter_func_count_src_out_arr_p : t_dp_sosi_arr(g_nof_counters-1 DOWNTO 0);
-
-  ------------------------------------------------------------------------------
-  -- Verification
-  ------------------------------------------------------------------------------
-  SIGNAL tb_eop_sop_en   : STD_LOGIC := '1';
-  SIGNAL tb_step_en      : STD_LOGIC := '0';
-  SIGNAL tb_start_en     : STD_LOGIC := '0';
-  SIGNAL tb_stopped_en   : STD_LOGIC := '0';
-  SIGNAL tb_carryover_en : STD_LOGIC := '0';
-  SIGNAL tb_end          : STD_LOGIC := '0';
-
-  TYPE t_count_arr IS ARRAY(g_nof_counters-1 DOWNTO 0) OF NATURAL;
-  SIGNAL tb_count_arr      : t_count_arr := (others => 0);
-  SIGNAL tb_last_count_arr : t_count_arr := (others => 0);
-
-  BEGIN
-  
-  ------------------------------------------------------------------------------
-  -- Clock & reset
-  ------------------------------------------------------------------------------
-  clk <= (NOT clk) OR tb_end AFTER c_clk_period/2;
-  rst <= '1', '0' AFTER c_clk_period*7;
-  
-  ------------------------------------------------------------------------------
-  -- Stimuli: 
-  ------------------------------------------------------------------------------
-  
-  p_stimuli : PROCESS
-  VARIABLE run_clk_cnt: NATURAL := 1;
-  BEGIN
-    -- wait for reset
-    proc_common_wait_until_low(clk, rst);
-    proc_common_wait_some_cycles(clk, 1);
-    
-    REPORT "Start tb dp_counter_func";      
-    
-    dp_counter_func_count_en <= '1';  -- start counting
-    proc_common_gen_pulse(clk, tb_start_en);  -- check start value
-    
-    proc_common_wait_some_cycles(clk, 10);  -- wait some time
-    dp_counter_func_count_en <= '0';  -- stop counting
-    proc_common_wait_some_cycles(clk, 10);  -- wait some time
-    proc_common_gen_pulse(clk, tb_stopped_en);  -- check if counting is stopped
-    
-    dp_counter_func_count_en <= '1';  -- start counting again
-    tb_step_en <= '1';  -- enable step-size check
-
-    IF g_nof_counters>1 THEN
-      -- issue strobe to check counter carry over
-      proc_common_wait_until_lo_hi(clk, dp_counter_func_count_src_out_arr(g_nof_counters-2).eop);  -- wait for carryover
-      proc_common_gen_pulse(clk, tb_carryover_en);  -- check if dimension carryover is going right
-    END IF;
-    
-    -- keep running for full range counting of the slowest counter
-    proc_common_wait_until_hi_lo(clk, dp_counter_func_count_src_out_arr(g_nof_counters-1).eop);  -- wait for carryover
-  
-    -- run some more intervals for slowest counter, to more clearly view how the slowest counter behaves
-    proc_common_wait_until_hi_lo(clk, dp_counter_func_count_src_out_arr(g_nof_counters-1).eop);  -- wait for carryover
-    proc_common_wait_until_hi_lo(clk, dp_counter_func_count_src_out_arr(g_nof_counters-1).eop);  -- wait for carryover
-    
-    REPORT "Stop tb dp_counter_func";  
-    tb_end <= '1';    
-    WAIT;
-  END PROCESS;
-
-  ------------------------------------------------------------------------------
-  -- dp_counter_func
-  ------------------------------------------------------------------------------     
-  u_dp_counter_func : ENTITY work.dp_counter_func
-  GENERIC MAP (
-    g_nof_counters => g_nof_counters,
-    g_range_start  => g_range_start,
-    g_range_stop   => g_range_stop,
-    g_range_step   => g_range_step
-  )
-  PORT MAP (
-    rst       => rst,
-    clk       => clk,
-
-    count_en  => dp_counter_func_count_en,
-
-    count_src_out_arr => dp_counter_func_count_src_out_arr
-  );
-  
-  -- Add pipeline to removed combinatorial glitches for viewing in the wave window
-  dp_counter_func_count_src_out_arr_p <= dp_counter_func_count_src_out_arr WHEN rising_edge(clk);
-  
-  ------------------------------------------------------------------------------
-  -- Verification
-  ------------------------------------------------------------------------------
-  p_verify : PROCESS(clk)
-  BEGIN
-    IF rising_edge(clk) THEN
-      -- check if direct after start the counters hold the start value
-      IF tb_start_en = '1' THEN
-        FOR I IN 0 TO g_nof_counters-1 LOOP
-          ASSERT tb_count_arr(I) = g_range_start(I)
-            REPORT "DP : Wrong start of counter " & int_to_str(I) SEVERITY ERROR;
-        END LOOP;
-      END IF; 
-      
-      -- check if dp_counter_func is stopped after dp_counter_func_count_en <= '0'
-      IF tb_stopped_en = '1' THEN
-        FOR I IN 0 TO g_nof_counters-1 LOOP
-          ASSERT tb_count_arr(I) = TO_UINT(dp_counter_func_count_src_out_arr(I).data(c_max_count_w-1 DOWNTO 0))
-            REPORT "DP : Counter " & int_to_str(I) & " not stopped after dp_counter_func_count_en <= 0" SEVERITY ERROR;
-        END LOOP;
-      END IF; 
-
-      -- check dimension carryover
-      IF tb_carryover_en = '1' THEN
-        -- all counters except the last one should hold the start value
-        FOR I IN 0 TO g_nof_counters-2 LOOP
-          ASSERT tb_count_arr(I) = g_range_start(I)
-            REPORT "DP : Wrong carryover, counter:" & int_to_str(I) SEVERITY ERROR;
-        END LOOP;
-        -- the last counter should hold the start value + step
-        ASSERT tb_count_arr(g_nof_counters-1) = g_range_start(g_nof_counters-1) + g_range_step(g_nof_counters-1)
-            REPORT "DP : Wrong carryover, counter:" & int_to_str(g_nof_counters-1) SEVERITY ERROR;
-      END IF;
-
-      -- check counter values on sop and eop
-      IF tb_eop_sop_en = '1' THEN  
-        FOR I IN 0 TO g_nof_counters-1 LOOP
-          -- on eop counter should hold the stop_value-1
-          IF dp_counter_func_count_src_out_arr(I).eop = '1' THEN
-            ASSERT tb_count_arr(I) = ((g_range_stop(I) - 1 - g_range_start(I)) / g_range_step(I)) * g_range_step(I) + g_range_start(I)
-              REPORT "DP : Wrong stop count on eop, counter:" & int_to_str(I) & 
-                     " is:" & int_to_str(tb_count_arr(I)) & 
-                     " expected:" & int_to_str(((g_range_stop(I) - 1 - g_range_start(I)) / g_range_step(I)) * g_range_step(I) + g_range_start(I)) SEVERITY ERROR;
-          END IF;
-          -- on sop counter should hold the start_value
-          IF dp_counter_func_count_src_out_arr(I).sop = '1' THEN
-            ASSERT tb_count_arr(I) = g_range_start(I)
-              REPORT "DP : Wrong start count on sop, counter:" & int_to_str(I) & 
-                     " is:" & int_to_str(tb_count_arr(I)) & 
-                     " expected:" & int_to_str(g_range_start(I)) SEVERITY ERROR;
-          END IF;
-        END LOOP;
-      END IF;
-
-      -- check step values
-      IF tb_step_en = '1' THEN
-        FOR I IN 0 TO g_nof_counters-1 LOOP
-          IF tb_count_arr(I) > tb_last_count_arr(I) THEN
-            ASSERT (tb_last_count_arr(I) + g_range_step(I)) = tb_count_arr(I) 
-              REPORT "DP : Wrong step count, counter:" & int_to_str(I) & 
-                     " is:" & int_to_str(tb_count_arr(I)) & 
-                     " expected:" & int_to_str(tb_last_count_arr(I) + g_range_step(I)) SEVERITY ERROR;
-          ELSIF tb_count_arr(I) < tb_last_count_arr(I) THEN
-            ASSERT g_range_start(I) = tb_count_arr(I)
-              REPORT "DP : Wrong step count, counter:" & int_to_str(I) & 
-                     " is:" & int_to_str(tb_count_arr(I)) & 
-                     " expected:" & int_to_str(g_range_start(I)) & ")" SEVERITY ERROR;
-          END IF;
-        END LOOP;
-      END IF;
-    END IF;
-  END PROCESS;
-  
-  
-  tb_last_count_arr <= tb_count_arr WHEN rising_edge(clk);
-
-  gen_tb_count_arr : FOR i IN 0 TO g_nof_counters-1 GENERATE
-    tb_count_arr(I) <= TO_UINT(dp_counter_func_count_src_out_arr(I).data(c_max_count_w-1 DOWNTO 0)) WHEN dp_counter_func_count_en = '1';
-  END GENERATE;
-
-END tb;
diff --git a/cores/base/dp/dp_counter/tb_tb_dp_counter.vhd b/cores/base/dp/dp_counter/tb_tb_dp_counter.vhd
deleted file mode 100644
index 5652cfa766ef822d726acff3dc860efe30167d41..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_counter/tb_tb_dp_counter.vhd
+++ /dev/null
@@ -1,64 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2015
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
--- Purpose: Verify multiple variations of tb_dp_counter
--- Description:
--- Usage:
--- > as 6
--- > run -all
-
-ENTITY tb_tb_dp_counter IS
-END tb_tb_dp_counter;
-
-
-ARCHITECTURE tb OF tb_tb_dp_counter IS
-
-  SIGNAL tb_end : STD_LOGIC := '0';  -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
-  
-BEGIN
-
-  -- -- general
-  -- g_flow_control_stimuli   : t_dp_flow_control_enum := e_active;   -- always active, random or pulse flow control
-  -- g_flow_control_verify    : t_dp_flow_control_enum := e_pulse;  -- always active, random or pulse flow control
-  -- -- dut
-  -- g_pipeline_src_out : NATURAL := 1; -- Pipeline source outputs (data,valid,sop,eop etc)
-  -- g_pipeline_src_in  : NATURAL := 0  -- Pipeline source inputs (ready,xon). This will also pipeline src_out.
-  -- g_nof_counters     : NATURAL := 2;
-  -- -- min range = [0,2,1] => (0,1) 'the Python way'
-  -- g_range_start      : t_nat_natural_arr(9 DOWNTO 0) := (0,0,0,0,0,0,0, 1, 0, 0);
-  -- g_range_stop       : t_nat_natural_arr(9 DOWNTO 0) := (2,2,2,2,2,2,7,16,16,16);
-  -- g_range_step       : t_nat_natural_arr(9 DOWNTO 0) := (1,1,1,1,1,1,2, 2, 2, 1);
-
-  u_act_act_comb     : ENTITY work.tb_dp_counter GENERIC MAP (e_active, e_active, 0, 0, 3);
-  u_act_act_pipe_out : ENTITY work.tb_dp_counter GENERIC MAP (e_active, e_active, 1, 0, 3);
-  u_act_act_pipe_in  : ENTITY work.tb_dp_counter GENERIC MAP (e_active, e_active, 0, 1, 3);
-                                                                                         
-  u_rnd_rnd_comb     : ENTITY work.tb_dp_counter GENERIC MAP (e_random, e_random, 0, 0, 3);
-  u_rnd_rnd_pipe_out : ENTITY work.tb_dp_counter GENERIC MAP (e_random, e_random, 1, 0, 3);
-  u_rnd_rnd_pipe_in  : ENTITY work.tb_dp_counter GENERIC MAP (e_random, e_random, 0, 1, 3);
-  
-END tb;
diff --git a/cores/base/dp/dp_pipeline/dp_pipeline.vhd b/cores/base/dp/dp_pipeline/dp_pipeline.vhd
deleted file mode 100644
index 3ecd34351a44511e80201e87ff83eb98d3fb8092..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/dp_pipeline.vhd
+++ /dev/null
@@ -1,156 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, dp_pkg_lib, dp_components_lib;
-USE IEEE.std_logic_1164.all;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
--- Purpose:
---   Pipeline the source output by one cycle or by g_pipeline cycles.
--- Description:
---   The dp_pipeline instantiates 0:g_pipeline stages of dp_pipeline_one.
---   The dp_pipeline_one provides a single clock cycle delay of the source
---   output (i.e. sosi). The dp_pipeline_one holds valid sink input in case
---   src_in.ready goes low and makes src_out.valid high again when
---   src_in.ready goes high again, without the need for a valid sink input to
---   push this held data out.
---   The dp_pipeline delays the data, sop, eop by one cycle relative to the
---   valid. However the src_out.valid still has the same phase as the
---   snk_in.valid, because both valids depends on the same src_in.ready.
---   Therefore dp_pipeline cannot be used to delay the valid phase by one
---   cycle. Hence the may purpose of dp_pipeline is to register the sosi.
--- Remarks:
--- . Ready latency = 1
--- . Without flow control so when src_in.ready = '1' fixed, then the hold
---   logic in dp_pipeline becomes void and dp_pipeline then just pipelines the
---   snk_in sosi.
-
-ENTITY dp_pipeline IS
-  GENERIC (
-    g_pipeline   : NATURAL := 1  -- 0 for wires, > 0 for registers, 
-  );
-  PORT (
-    rst          : IN  STD_LOGIC;
-    clk          : IN  STD_LOGIC;
-    -- ST sink
-    snk_out      : OUT t_dp_siso;
-    snk_in       : IN  t_dp_sosi;
-    -- ST source
-    src_in       : IN  t_dp_siso := c_dp_siso_rdy;
-    src_out      : OUT t_dp_sosi
-  );
-END dp_pipeline;
-
-
-LIBRARY IEEE, dp_pkg_lib, dp_components_lib;
-USE IEEE.std_logic_1164.all;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ENTITY dp_pipeline_one IS
-  PORT (
-    rst          : IN  STD_LOGIC;
-    clk          : IN  STD_LOGIC;
-    -- ST sink
-    snk_out      : OUT t_dp_siso;
-    snk_in       : IN  t_dp_sosi;
-    -- ST source
-    src_in       : IN  t_dp_siso := c_dp_siso_rdy;
-    src_out      : OUT t_dp_sosi
-  );
-END dp_pipeline_one;
-
-
-LIBRARY IEEE, dp_pkg_lib, dp_components_lib;
-USE IEEE.std_logic_1164.all;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ARCHITECTURE str OF dp_pipeline IS
-
-  SIGNAL snk_out_arr      : t_dp_siso_arr(0 TO g_pipeline);
-  SIGNAL snk_in_arr       : t_dp_sosi_arr(0 TO g_pipeline);
-  
-BEGIN
-
-  -- Input at index 0
-  snk_out       <= snk_out_arr(0);
-  snk_in_arr(0) <= snk_in;
-  
-  -- Output at index g_pipeline
-  snk_out_arr(g_pipeline) <= src_in;
-  src_out                 <= snk_in_arr(g_pipeline);
-  
-  gen_p : FOR I IN 1 TO g_pipeline GENERATE
-    u_p : ENTITY work.dp_pipeline_one
-    PORT MAP (
-      rst          => rst,
-      clk          => clk,
-      -- ST sink
-      snk_out      => snk_out_arr(I-1),
-      snk_in       => snk_in_arr(I-1),
-      -- ST source
-      src_in       => snk_out_arr(I),
-      src_out      => snk_in_arr(I)
-    );
-  END GENERATE;
-  
-END str;
-
-
-LIBRARY IEEE, dp_pkg_lib, dp_components_lib;
-USE IEEE.std_logic_1164.all;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ARCHITECTURE str OF dp_pipeline_one IS
-
-  SIGNAL nxt_src_out      : t_dp_sosi;
-  SIGNAL i_src_out        : t_dp_sosi;
-  
-BEGIN
-
-  src_out <= i_src_out;
-
-  -- Pipeline register
-  p_clk : PROCESS(rst, clk)
-  BEGIN
-    IF rst='1' THEN
-      i_src_out <= c_dp_sosi_rst;
-    ELSIF rising_edge(clk) THEN
-      i_src_out <= nxt_src_out;
-    END IF;
-  END PROCESS;
-  
-  -- Input control
-  u_hold_input : ENTITY dp_components_lib.dp_hold_input
-  PORT MAP (
-    rst              => rst,
-    clk              => clk,
-    -- ST sink
-    snk_out          => snk_out,
-    snk_in           => snk_in,
-    -- ST source
-    src_in           => src_in,
-    next_src_out     => nxt_src_out,
-    pend_src_out     => OPEN,
-    src_out_reg      => i_src_out
-  );  
-    
-END str;
diff --git a/cores/base/dp/dp_pipeline/dp_pipeline_arr.vhd b/cores/base/dp/dp_pipeline/dp_pipeline_arr.vhd
deleted file mode 100644
index f0407d893fd6496e262e0a20381196806a3f325d..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/dp_pipeline_arr.vhd
+++ /dev/null
@@ -1,71 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2015
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, dp_pkg_lib;
-USE IEEE.std_logic_1164.all;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
--- Purpose:
---   Pipeline array of g_nof_streams by g_pipeline cycles.
--- Description:
---   See dp_pipeline.
-
-ENTITY dp_pipeline_arr IS
-  GENERIC (
-    g_nof_streams : NATURAL := 1;
-    g_pipeline    : NATURAL := 1  -- 0 for wires, > 0 for registers, 
-  );
-  PORT (
-    rst          : IN  STD_LOGIC;
-    clk          : IN  STD_LOGIC;
-    -- ST sink
-    snk_out_arr  : OUT t_dp_siso_arr(g_nof_streams-1 DOWNTO 0);
-    snk_in_arr   : IN  t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
-    -- ST source
-    src_in_arr   : IN  t_dp_siso_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>c_dp_siso_rdy);
-    src_out_arr  : OUT t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0)
-  );
-END dp_pipeline_arr;
-
-
-ARCHITECTURE str OF dp_pipeline_arr IS
-
-BEGIN
-
-  gen_nof_streams : FOR I IN 0 TO g_nof_streams-1 GENERATE
-    u_p : ENTITY work.dp_pipeline
-    GENERIC MAP (
-      g_pipeline => g_pipeline
-    )
-    PORT MAP (
-      rst          => rst,
-      clk          => clk,
-      -- ST sink
-      snk_out      => snk_out_arr(I),
-      snk_in       => snk_in_arr(I),
-      -- ST source
-      src_in       => src_in_arr(I),
-      src_out      => src_out_arr(I)
-    );
-  END GENERATE;
-  
-END str;
diff --git a/cores/base/dp/dp_pipeline/dp_pipeline_ready.vhd b/cores/base/dp/dp_pipeline/dp_pipeline_ready.vhd
deleted file mode 100644
index d44b22316b2b436336bebc32d12b0d16372bc160..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/dp_pipeline_ready.vhd
+++ /dev/null
@@ -1,157 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, dp_pkg_lib, dp_components_lib;
-USE IEEE.std_logic_1164.all;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
--- Purpose:
---   Pipeline the source input
--- Description:
---   This dp_pipeline_ready provides a single clock cycle delay of the source
---   input (i.e. siso). It does this by first going from RL = g_in_latency -->
---   0 and then to RL = g_out_latency. 
--- Data flow:
---   . out RL >  in RL                : incr(out RL - in RL)
---   . out RL <= in RL AND out RL = 0 : incr(1) --> adapt(out RL)
---   . out RL <= in RL AND out RL > 0 : adapt(0) --> incr(out RL)
--- Remark:
--- . The g_in_latency may be 0, but for g_in_latency=0 the sosi.ready acts
---   as an acknowledge and that could simply also be registered by the user.
-
-ENTITY dp_pipeline_ready IS
-  GENERIC (
-    g_in_latency   : NATURAL := 1;  -- >= 0
-    g_out_latency  : NATURAL := 1   -- >= 0
-  );
-  PORT (
-    rst          : IN  STD_LOGIC;
-    clk          : IN  STD_LOGIC;
-    -- 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_pipeline_ready;
-
-
-ARCHITECTURE str OF dp_pipeline_ready IS
-
-  SIGNAL internal_siso  : t_dp_siso;
-  SIGNAL internal_sosi  : t_dp_sosi;
- 
-BEGIN
-
-  gen_out_incr_rl : IF g_out_latency>g_in_latency GENERATE
-    -- Register siso by incrementing the input RL first
-    u_incr : ENTITY dp_components_lib.dp_latency_increase
-    GENERIC MAP (
-      g_in_latency   => g_in_latency,
-      g_incr_latency => g_out_latency-g_in_latency
-    )
-    PORT MAP (
-      rst          => rst,
-      clk          => clk,
-      -- ST sink
-      snk_out      => snk_out,
-      snk_in       => snk_in,
-      -- ST source
-      src_in       => src_in,
-      src_out      => src_out
-    );
-  END GENERATE;
-  
-  gen_out_rl_0 : IF g_out_latency<=g_in_latency AND g_out_latency=0 GENERATE
-    -- Register siso by incrementing the input RL first
-    u_incr : ENTITY dp_components_lib.dp_latency_increase
-    GENERIC MAP (
-      g_in_latency   => g_in_latency,
-      g_incr_latency => 1
-    )
-    PORT MAP (
-      rst          => rst,
-      clk          => clk,
-      -- ST sink
-      snk_out      => snk_out,
-      snk_in       => snk_in,
-      -- ST source
-      src_in       => internal_siso,
-      src_out      => internal_sosi
-    );
-
-    -- Input RL --> 0
-    u_adapt : ENTITY dp_components_lib.dp_latency_adapter
-    GENERIC MAP (
-      g_in_latency   => g_in_latency+1,
-      g_out_latency  => g_out_latency
-    )
-    PORT MAP (
-      rst          => rst,
-      clk          => clk,
-      -- ST sink
-      snk_out      => internal_siso,
-      snk_in       => internal_sosi,
-      -- ST source
-      src_in       => src_in,
-      src_out      => src_out
-    );
-  END GENERATE;
-  
-  gen_out_rl : IF g_out_latency<=g_in_latency AND g_out_latency>0 GENERATE
-    -- First adapt the input RL --> 0
-    u_adapt : ENTITY dp_components_lib.dp_latency_adapter
-    GENERIC MAP (
-      g_in_latency   => g_in_latency,
-      g_out_latency  => 0
-    )
-    PORT MAP (
-      rst          => rst,
-      clk          => clk,
-      -- ST sink
-      snk_out      => snk_out,
-      snk_in       => snk_in,
-      -- ST source
-      src_in       => internal_siso,
-      src_out      => internal_sosi
-    );
-
-    -- Register siso by incrementing the internal RL = 0 --> the output RL
-    u_incr : ENTITY dp_components_lib.dp_latency_increase
-    GENERIC MAP (
-      g_in_latency   => 0,
-      g_incr_latency => g_out_latency
-    )
-    PORT MAP (
-      rst          => rst,
-      clk          => clk,
-      -- ST sink
-      snk_out      => internal_siso,
-      snk_in       => internal_sosi,
-      -- ST source
-      src_in       => src_in,
-      src_out      => src_out
-    );
-  END GENERATE;
-    
-END str;
diff --git a/cores/base/dp/dp_pipeline/hdllib.cfg b/cores/base/dp/dp_pipeline/hdllib.cfg
deleted file mode 100644
index 0ea1977989f467f74cfb23811bdcd0f992e6861f..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/hdllib.cfg
+++ /dev/null
@@ -1,25 +0,0 @@
-hdl_lib_name = dp_pipeline
-hdl_library_clause_name = dp_pipeline_lib
-hdl_lib_uses_synth = dp_components
-hdl_lib_uses_sim = 
-hdl_lib_technology = 
-
-synth_files =
-    dp_pipeline.vhd
-    dp_pipeline_arr.vhd
-    dp_pipeline_ready.vhd
-   
-test_bench_files = 
-    tb_dp_pipeline.vhd
-    tb_dp_pipeline_ready.vhd
-    tb_tb_dp_pipeline.vhd
-    tb_tb_dp_pipeline_ready.vhd
-
-regression_test_vhdl = 
-    tb_tb_dp_pipeline.vhd
-    tb_tb_dp_pipeline_ready.vhd
-
-[modelsim_project_file]
-
-
-[quartus_project_file]
diff --git a/cores/base/dp/dp_pipeline/tb_dp_pipeline.vhd b/cores/base/dp/dp_pipeline/tb_dp_pipeline.vhd
deleted file mode 100644
index 52e7b50b71423f14cddf9c090864fcb513592cd4..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/tb_dp_pipeline.vhd
+++ /dev/null
@@ -1,164 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
-ENTITY tb_dp_pipeline IS
-  GENERIC (
-    g_pipeline : NATURAL := 5
-  );
-END tb_dp_pipeline;
-
-
-ARCHITECTURE tb OF tb_dp_pipeline IS
-
-  -- See tb_dp_pkg.vhd for explanation and run time
-
-  -- DUT ready latency
-  CONSTANT c_dut_latency    : NATURAL := 1;              -- fixed 1 for dp_pipeline
-  CONSTANT c_tx_latency     : NATURAL := c_dut_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 := 7;              -- sop in data valid cycle 3,  10,  17, ...
-  CONSTANT c_tx_offset_eop  : NATURAL := 5;              -- eop in data valid cycle   5,  12,  19, ...
-  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_rx_latency     : NATURAL := c_dut_latency;  -- RX ready latency from DUT
-  CONSTANT c_verify_en_wait : NATURAL := 4+g_pipeline;   -- wait some cycles before asserting verify enable
-  
-  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_sync        : STD_LOGIC;
-  SIGNAL in_val         : STD_LOGIC;
-  SIGNAL in_sop         : STD_LOGIC;
-  SIGNAL in_eop         : STD_LOGIC;
-  
-  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_sync       : STD_LOGIC;
-  SIGNAL out_val        : STD_LOGIC;
-  SIGNAL out_sop        : STD_LOGIC;
-  SIGNAL out_eop        : STD_LOGIC;
-  SIGNAL hold_out_sop   : 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 exp_data       : STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0) := TO_UVEC(sel_a_b(g_pipeline=0, 18953, 18952), c_dp_data_w);
-  
-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;
-  
-  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);
-
-  -- Stimuli control
-  proc_dp_count_en(rst, clk, sync, lfsr1, state, verify_done, tb_end, 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);
-  proc_dp_verify_data("out_sosi.data", c_rx_latency, clk, verify_en, out_ready, out_val, out_data, prev_out_data);
-  proc_dp_verify_valid(c_rx_latency, clk, verify_en, out_ready, prev_out_ready, out_val);
-  proc_dp_verify_sop_and_eop(c_rx_latency, FALSE, clk, out_val, out_val, out_sop, out_eop, hold_out_sop);  -- Verify that sop and eop come in pairs, no check on valid between eop and sop
-  proc_dp_verify_ctrl(c_tx_offset_sync, c_tx_period_sync, "sync", clk, verify_en, out_data, out_val, out_sync);
-  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);
-  
-  -- Check that the test has ran at all
-  proc_dp_verify_value(e_equal, clk, verify_done, exp_data, out_data);
-  
-  ------------------------------------------------------------------------------
-  -- DUT dp_pipeline
-  ------------------------------------------------------------------------------
-  
-  -- 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.sync                         <= in_sync;
-  in_sosi.valid                        <= in_val;
-  in_sosi.sop                          <= in_sop;
-  in_sosi.eop                          <= in_eop;
-  
-  out_siso.ready <= out_ready;                        -- SISO
-  out_data <= out_sosi.data(c_dp_data_w-1 DOWNTO 0);  -- SOSI
-  out_sync <= out_sosi.sync;
-  out_val  <= out_sosi.valid;
-  out_sop  <= out_sosi.sop;
-  out_eop  <= out_sosi.eop;
-  
-  dut : ENTITY work.dp_pipeline
-  GENERIC MAP (
-    g_pipeline => g_pipeline
-  )
-  PORT MAP (
-    rst         => rst,
-    clk         => clk,
-    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;
diff --git a/cores/base/dp/dp_pipeline/tb_dp_pipeline_ready.vhd b/cores/base/dp/dp_pipeline/tb_dp_pipeline_ready.vhd
deleted file mode 100644
index 4c3bb7b24e5943844dda99186f24fe512c656207..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/tb_dp_pipeline_ready.vhd
+++ /dev/null
@@ -1,223 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2011
--- 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: Verify dp_pipeline_ready for different RL
--- Description:
--- Usage:
--- > as 10
--- > run -all  -- signal tb_end will stop the simulation by stopping the clk
--- . The verify procedures check the correct output
-  
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib, dp_components_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE common_pkg_lib.common_lfsr_sequences_pkg.ALL;
-USE common_pkg_lib.tb_common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
-
-ENTITY tb_dp_pipeline_ready IS
-  GENERIC (
-    g_in_en          : t_dp_flow_control_enum := e_random;  -- always active, random or pulse flow control
-    g_out_ready      : t_dp_flow_control_enum := e_random;  -- always active, random or pulse flow control
-    g_in_latency     : NATURAL := 1;  -- >= 0
-    g_out_latency    : NATURAL := 0;  -- >= 0
-    g_nof_repeat     : NATURAL := 50
-  );
-END tb_dp_pipeline_ready;
-
-
-ARCHITECTURE tb OF tb_dp_pipeline_ready IS
-  CONSTANT c_data_w          : NATURAL := 16;
-  CONSTANT c_rl              : NATURAL := 1;
-  CONSTANT c_data_init       : INTEGER := 0;
-  CONSTANT c_frame_len_init  : NATURAL := 1;  -- >= 1
-  CONSTANT c_pulse_active    : NATURAL := 1;
-  CONSTANT c_pulse_period    : NATURAL := 7;
-  CONSTANT c_sync_period     : NATURAL := 7;
-  CONSTANT c_sync_offset     : NATURAL := 2;
-
-  SIGNAL tb_end              : STD_LOGIC := '0';
-  SIGNAL clk                 : STD_LOGIC := '1';
-  SIGNAL rst                 : STD_LOGIC := '1';
-
-  -- Flow control
-  SIGNAL random_0            : STD_LOGIC_VECTOR(14 DOWNTO 0) := (OTHERS=>'0');  -- use different lengths to have different random sequences
-  SIGNAL random_1            : STD_LOGIC_VECTOR(15 DOWNTO 0) := (OTHERS=>'0');  -- use different lengths to have different random sequences
-  SIGNAL pulse_0             : STD_LOGIC;
-  SIGNAL pulse_1             : STD_LOGIC;
-  SIGNAL pulse_en            : STD_LOGIC := '1';
-
-  -- Stimuli
-  SIGNAL in_en               : STD_LOGIC := '1';
-  SIGNAL in_siso             : t_dp_siso;
-  SIGNAL in_sosi             : t_dp_sosi;
-  SIGNAL adapt_siso          : t_dp_siso;
-  SIGNAL adapt_sosi          : t_dp_sosi;
-
-  SIGNAL out_siso            : t_dp_siso := c_dp_siso_hold;  -- ready='0', xon='1'
-  SIGNAL out_sosi            : t_dp_sosi;
-
-  -- Verification
-  SIGNAL verify_en           : STD_LOGIC := '0';
-  SIGNAL verify_done         : STD_LOGIC := '0';
-  SIGNAL count_eop           : NATURAL := 0;
-
-  SIGNAL prev_out_ready      : STD_LOGIC_VECTOR(0 TO g_out_latency);
-  SIGNAL prev_out_data       : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0) := TO_SVEC(c_data_init-1, c_data_w);
-  SIGNAL out_bsn             : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0);
-  SIGNAL out_data            : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0);
-  SIGNAL out_sync            : STD_LOGIC;
-  SIGNAL out_val             : STD_LOGIC;
-  SIGNAL out_sop             : STD_LOGIC;
-  SIGNAL out_eop             : STD_LOGIC;
-  SIGNAL hold_out_sop        : STD_LOGIC;
-  SIGNAL expected_out_data   : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0);
-
-BEGIN
-
-  clk <= (NOT clk) OR tb_end AFTER clk_period/2;
-  rst <= '1', '0' AFTER clk_period*7;
-
-  random_0 <= func_common_random(random_0) WHEN rising_edge(clk);
-  random_1 <= func_common_random(random_1) WHEN rising_edge(clk);
-
-  proc_common_gen_duty_pulse(c_pulse_active, c_pulse_period,   '1', rst, clk, pulse_en, pulse_0);
-  proc_common_gen_duty_pulse(c_pulse_active, c_pulse_period+1, '1', rst, clk, pulse_en, pulse_1);
-
-
-  ------------------------------------------------------------------------------
-  -- STREAM CONTROL
-  ------------------------------------------------------------------------------
-
-  in_en          <= '1'                     WHEN g_in_en=e_active      ELSE
-                    random_0(random_0'HIGH) WHEN g_in_en=e_random      ELSE
-                    pulse_0                 WHEN g_in_en=e_pulse;
-
-  out_siso.ready <= '1'                     WHEN g_out_ready=e_active  ELSE
-                    random_1(random_1'HIGH) WHEN g_out_ready=e_random  ELSE
-                    pulse_1                 WHEN g_out_ready=e_pulse;
-
-
-  ------------------------------------------------------------------------------
-  -- DATA GENERATION
-  ------------------------------------------------------------------------------
-
-  -- Generate data path input data
-  p_stimuli : PROCESS
-    VARIABLE v_data_init   : NATURAL;
-    VARIABLE v_frame_len   : NATURAL;
-    VARIABLE v_sync        : STD_LOGIC;
-  BEGIN
-    v_data_init := c_data_init;
-    v_frame_len := c_frame_len_init;
-    in_sosi <= c_dp_sosi_rst;
-    proc_common_wait_until_low(clk, rst);
-    proc_common_wait_some_cycles(clk, 5);
-
-    -- Begin of stimuli
-    FOR R IN 0 TO g_nof_repeat-1 LOOP
-      v_sync := sel_a_b(R MOD c_sync_period = c_sync_offset, '1', '0');
-      proc_dp_gen_block_data(c_rl, TRUE, c_data_w, c_data_w, v_data_init, 0, 0, v_frame_len, 0, 0, v_sync, TO_DP_BSN(R), clk, in_en, in_siso, in_sosi);
-      --proc_common_wait_some_cycles(clk, 10);
-      v_data_init := v_data_init + v_frame_len;
-      v_frame_len := v_frame_len + 1;
-    END LOOP;
-
-    -- End of stimuli
-    expected_out_data <= TO_UVEC(v_data_init-1, c_data_w);
-
-    proc_common_wait_until_high(clk, verify_done);
-    proc_common_wait_some_cycles(clk, 10);
-    tb_end <= '1';
-    WAIT;
-  END PROCESS;
-  
-  -- proc_dp_gen_block_data() only supports RL=0 or 1, so use a latency adpater to support any g_in_latency
-  u_input_adapt : ENTITY dp_components_lib.dp_latency_adapter
-  GENERIC MAP (
-    g_in_latency   => c_rl,
-    g_out_latency  => g_in_latency
-  )
-  PORT MAP (
-    rst          => rst,
-    clk          => clk,
-    -- ST sink
-    snk_out      => in_siso,
-    snk_in       => in_sosi,
-    -- ST source
-    src_in       => adapt_siso,
-    src_out      => adapt_sosi 
-  );
-
-
-  ------------------------------------------------------------------------------
-  -- DATA VERIFICATION
-  ------------------------------------------------------------------------------
-
-
-  -- Verification logistics
-  verify_en <= '1'          WHEN rising_edge(clk) AND out_sosi.sop='1';          -- enable verify after first output sop
-  count_eop <= count_eop+1  WHEN rising_edge(clk) AND out_sosi.eop='1' AND((g_out_latency>0) OR
-                                                                           (g_out_latency=0 AND out_siso.ready='1'));  -- count number of output eop
-  verify_done <= '1'        WHEN rising_edge(clk) AND count_eop = g_nof_repeat;  -- signal verify done after g_nof_repeat frames
-
-  -- Actual verification of the output streams
-  proc_dp_verify_data("out_sosi.data", g_out_latency, clk, verify_en, out_siso.ready, out_sosi.valid, out_data, prev_out_data);  -- Verify that the output is incrementing data, like the input stimuli
-  proc_dp_verify_valid(g_out_latency, clk, verify_en, out_siso.ready, prev_out_ready, out_sosi.valid);                           -- Verify that the output valid fits with the output ready latency
-  proc_dp_verify_sop_and_eop(g_out_latency, clk, out_siso.ready, out_sosi.valid, out_sosi.sop, out_sosi.eop, hold_out_sop);      -- Verify that sop and eop come in pairs
-  proc_dp_verify_value(e_equal, clk, verify_done, expected_out_data, prev_out_data);                                             -- Verify that the stimuli have been applied at all
-  proc_dp_verify_sync(c_sync_period, c_sync_offset, clk, verify_en, out_sosi.sync, out_sosi.sop, out_sosi.bsn);
-
-  -- Monitoring
-  out_bsn  <= out_sosi.bsn(c_data_w-1 DOWNTO 0);
-  out_data <= out_sosi.data(c_data_w-1 DOWNTO 0);
-  out_sync <= out_sosi.sync;
-  out_val  <= out_sosi.valid;
-  out_sop  <= out_sosi.sop;
-  out_eop  <= out_sosi.eop;
-  
-  
-  ------------------------------------------------------------------------------
-  -- DUT dp_pipeline_ready
-  ------------------------------------------------------------------------------
-
-  pipeline : ENTITY work.dp_pipeline_ready
-  GENERIC MAP (
-    g_in_latency   => g_in_latency,
-    g_out_latency  => g_out_latency
-  )
-  PORT MAP (
-    rst          => rst,
-    clk          => clk,
-    -- ST sink
-    snk_out      => adapt_siso,
-    snk_in       => adapt_sosi,
-    -- ST source
-    src_in       => out_siso,
-    src_out      => out_sosi
-  );
-
-    
-END tb;
diff --git a/cores/base/dp/dp_pipeline/tb_tb_dp_pipeline.vhd b/cores/base/dp/dp_pipeline/tb_tb_dp_pipeline.vhd
deleted file mode 100644
index 44c25eb5b35a29785cc8858cafe22c48bad0cf0f..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/tb_tb_dp_pipeline.vhd
+++ /dev/null
@@ -1,42 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2013
--- 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/>.
---
--------------------------------------------------------------------------------
- 
-LIBRARY IEEE;
-USE IEEE.std_logic_1164.ALL;
-
--- > as 3
--- > run -all --> OK
-
-ENTITY tb_tb_dp_pipeline IS
-END tb_tb_dp_pipeline;
-
-
-ARCHITECTURE tb OF tb_tb_dp_pipeline IS
-  SIGNAL tb_end : STD_LOGIC := '0';  -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
-BEGIN
-
-  u_p0 : ENTITY work.tb_dp_pipeline GENERIC MAP (0);
-  u_p1 : ENTITY work.tb_dp_pipeline GENERIC MAP (1);
-  u_p2 : ENTITY work.tb_dp_pipeline GENERIC MAP (2);
-  u_p7 : ENTITY work.tb_dp_pipeline GENERIC MAP (7);
-
-END tb;
diff --git a/cores/base/dp/dp_pipeline/tb_tb_dp_pipeline_ready.vhd b/cores/base/dp/dp_pipeline/tb_tb_dp_pipeline_ready.vhd
deleted file mode 100644
index 15a68bffa37fd4c60cabf991cc33118a3df5a841..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pipeline/tb_tb_dp_pipeline_ready.vhd
+++ /dev/null
@@ -1,66 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
- 
-LIBRARY IEEE, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
-
--- > as 2
--- > run -all --> OK
-
-ENTITY tb_tb_dp_pipeline_ready IS
-END tb_tb_dp_pipeline_ready;
-
-
-ARCHITECTURE tb OF tb_tb_dp_pipeline_ready IS
-
-  CONSTANT c_nof_repeat : NATURAL := 50;
-  SIGNAL tb_end : STD_LOGIC := '0';  -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
-  
-BEGIN
-
-  --                                                               in_en,    src_in.ready, in_latency, out_latency, nof repeat,
-  -- Random flow control for different RL
-  u_rnd_rnd_0_0    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     0,          0,           c_nof_repeat);
-  u_rnd_rnd_1_0    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     1,          0,           c_nof_repeat);
-  u_rnd_rnd_0_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     0,          1,           c_nof_repeat);
-  u_rnd_rnd_2_0    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     2,          0,           c_nof_repeat);
-  u_rnd_rnd_0_2    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     0,          2,           c_nof_repeat);
-  u_rnd_rnd_2_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     2,          1,           c_nof_repeat);
-  u_rnd_rnd_1_2    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     1,          2,           c_nof_repeat);
-  u_rnd_rnd_2_2    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     2,          2,           c_nof_repeat);
-  
-  -- Other flow control for fixed RL
-  u_act_act_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_active, e_active,     1,          1,           c_nof_repeat);
-  u_act_rnd_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_active, e_random,     1,          1,           c_nof_repeat);
-  u_act_pls_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_active, e_pulse,      1,          1,           c_nof_repeat);
-                                                                                      
-  u_rnd_act_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_active,     1,          1,           c_nof_repeat);
-  u_rnd_rnd_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_random,     1,          1,           c_nof_repeat);
-  u_rnd_pls_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_random, e_pulse,      1,          1,           c_nof_repeat);
-                                                                                      
-  u_pls_act_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_pulse,  e_active,     1,          1,           c_nof_repeat);
-  u_pls_rnd_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_pulse,  e_random,     1,          1,           c_nof_repeat);
-  u_pls_pls_1_1    : ENTITY work.tb_dp_pipeline_ready GENERIC MAP (e_pulse,  e_pulse,      1,          1,           c_nof_repeat);
-  
-END tb;
diff --git a/cores/base/dp/dp_pkg/dp_stream_pkg.vhd b/cores/base/dp/dp_pkg/dp_stream_pkg.vhd
deleted file mode 100644
index 1d19e50d666f0b6ce9924ad4e52636f2d21d3fc1..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pkg/dp_stream_pkg.vhd
+++ /dev/null
@@ -1,1293 +0,0 @@
---------------------------------------------------------------------------------
---
--- Copyright (C) 2010
--- 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/>.
---
---------------------------------------------------------------------------------
- 
-LIBRARY IEEE, common_pkg_lib;
-USE IEEE.STD_LOGIC_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-
-PACKAGE dp_stream_pkg Is
-
-  ------------------------------------------------------------------------------
-  -- General DP stream record defintion
-  ------------------------------------------------------------------------------
-  
-  -- Remarks:
-  -- * Choose smallest maximum SOSI slv lengths that fit all use cases, because unconstrained record fields slv is not allowed
-  -- * The large SOSI data field width of 256b has some disadvantages:
-  --   . about 10% extra simulation time and PC memory usage compared to 72b (measured using tb_unb_tse_board)
-  --   . a 256b number has 64 hex digits in the Wave window which is awkward because of the leading zeros when typically
-  --     only 32b are used, fortunately integer representation still works OK (except 0 which is shown as blank).
-  --   However the alternatives are not attractive, because they affect the implementation of the streaming
-  --   components that use the SOSI record. Alternatives are e.g.:
-  --   . define an extra long SOSI data field ldata[255:0] in addition to the existing data[71:0] field
-  --   . use the array of SOSI records to contain wider data, all with the same SOSI control field values
-  --   . define another similar SOSI record with data[255:0].
-  --   Therefore define data width as 256b, because the disadvantages are acceptable and the benefit is great, because all
-  --   streaming components can remain as they are.
-  -- * Added sync and bsn to SOSI to have timestamp information with the data
-  -- * Added re and im to SOSI to support complex data for DSP
-  -- * The sosi fields can be labeled in diffent groups: ctrl, info and data as shown in comment at the t_dp_sosi definition.
-  --   This grouping is useful for functions that operate on a t_dp_sosi signal.
-  -- * The info fields are valid at the sop or at the eop, but typically they hold their last active value to avoid unnessary
-  --   toggling and to ease viewing in the wave window.
-  CONSTANT c_dp_stream_bsn_w      : NATURAL :=  64;  -- 64 is sufficient to count blocks of data for years
-  CONSTANT c_dp_stream_data_w     : NATURAL := 768;  -- 72 is sufficient for max word 8 * 9-bit. 576 supports half rate DDR4 bus data width. The current 768 is enough for wide single clock SLVs (e.g. headers)
-  CONSTANT c_dp_stream_dsp_data_w : NATURAL :=  64;  -- 64 is sufficient for DSP data, including complex power accumulates
-  CONSTANT c_dp_stream_empty_w    : NATURAL :=  16;  --  8 is sufficient for max 256 symbols per data word, still use 16 bit to be able to count c_dp_stream_data_w in bits
-  CONSTANT c_dp_stream_channel_w  : NATURAL :=  32;  -- 32 is sufficient for several levels of hierarchy in mapping types of streams on to channels 
-  CONSTANT c_dp_stream_error_w    : NATURAL :=  32;  -- 32 is sufficient for several levels of hierarchy in mapping error numbers, e.g. 32 different one-hot encoded errors, bit [0] = 0 = OK
-  
-  CONSTANT c_dp_stream_ok         : NATURAL := 0;  -- SOSI err field OK value
-  CONSTANT c_dp_stream_err        : NATURAL := 1;  -- SOSI err field error value /= OK
-  
-  CONSTANT c_dp_stream_rl         : NATURAL := 1;  -- SISO default data path stream ready latency RL = 1
-  
-  TYPE t_dp_siso IS RECORD  -- Source In or Sink Out
-    ready    : STD_LOGIC;   -- fine cycle based flow control using ready latency RL >= 0
-    xon      : STD_LOGIC;   -- coarse typically block based flow control using xon/xoff
-  END RECORD;
-  
-  TYPE t_dp_sosi IS RECORD  -- Source Out or Sink In
-    sync     : STD_LOGIC;                                           -- ctrl
-    bsn      : STD_LOGIC_VECTOR(c_dp_stream_bsn_w-1 DOWNTO 0);      -- info at sop      (block sequence number)
-    data     : STD_LOGIC_VECTOR(c_dp_stream_data_w-1 DOWNTO 0);     -- data
-    re       : STD_LOGIC_VECTOR(c_dp_stream_dsp_data_w-1 DOWNTO 0); -- data
-    im       : STD_LOGIC_VECTOR(c_dp_stream_dsp_data_w-1 DOWNTO 0); -- data
-    valid    : STD_LOGIC;                                           -- ctrl
-    sop      : STD_LOGIC;                                           -- ctrl
-    eop      : STD_LOGIC;                                           -- ctrl
-    empty    : STD_LOGIC_VECTOR(c_dp_stream_empty_w-1 DOWNTO 0);    -- info at eop
-    channel  : STD_LOGIC_VECTOR(c_dp_stream_channel_w-1 DOWNTO 0);  -- info at sop
-    err      : STD_LOGIC_VECTOR(c_dp_stream_error_w-1 DOWNTO 0);    -- info at eop (name field 'err' to avoid the 'error' keyword)
-  END RECORD;
- 
-  -- Initialise signal declarations with c_dp_stream_rst/rdy to ease the interpretation of slv fields with unused bits
-  CONSTANT c_dp_siso_rst   : t_dp_siso := ('0', '0');
-  CONSTANT c_dp_siso_x     : t_dp_siso := ('X', 'X');
-  CONSTANT c_dp_siso_hold  : t_dp_siso := ('0', '1');
-  CONSTANT c_dp_siso_rdy   : t_dp_siso := ('1', '1');
-  CONSTANT c_dp_siso_flush : t_dp_siso := ('1', '0');
-  CONSTANT c_dp_sosi_rst   : t_dp_sosi := ('0', (OTHERS=>'0'), (OTHERS=>'0'), (OTHERS=>'0'), (OTHERS=>'0'), '0', '0', '0', (OTHERS=>'0'), (OTHERS=>'0'), (OTHERS=>'0'));
-  CONSTANT c_dp_sosi_x     : t_dp_sosi := ('X', (OTHERS=>'X'), (OTHERS=>'X'), (OTHERS=>'X'), (OTHERS=>'X'), 'X', 'X', 'X', (OTHERS=>'X'), (OTHERS=>'X'), (OTHERS=>'X'));
-  
-  -- Use integers instead of slv for monitoring purposes (integer range limited to 31 bit plus sign bit)
-  TYPE t_dp_sosi_integer IS RECORD
-    sync     : STD_LOGIC;
-    bsn      : NATURAL;
-    data     : INTEGER;
-    re       : INTEGER;
-    im       : INTEGER;
-    valid    : STD_LOGIC;
-    sop      : STD_LOGIC;
-    eop      : STD_LOGIC;
-    empty    : NATURAL;
-    channel  : NATURAL;
-    err      : NATURAL;
-  END RECORD;
-  
-  -- Use unsigned instead of slv for monitoring purposes beyond the integer range of t_dp_sosi_integer
-  TYPE t_dp_sosi_unsigned IS RECORD
-    sync     : STD_LOGIC;
-    bsn      : UNSIGNED(c_dp_stream_bsn_w-1 DOWNTO 0);
-    data     : UNSIGNED(c_dp_stream_data_w-1 DOWNTO 0);
-    re       : UNSIGNED(c_dp_stream_dsp_data_w-1 DOWNTO 0);
-    im       : UNSIGNED(c_dp_stream_dsp_data_w-1 DOWNTO 0);
-    valid    : STD_LOGIC;
-    sop      : STD_LOGIC;
-    eop      : STD_LOGIC;
-    empty    : UNSIGNED(c_dp_stream_empty_w-1 DOWNTO 0);
-    channel  : UNSIGNED(c_dp_stream_channel_w-1 DOWNTO 0);
-    err      : UNSIGNED(c_dp_stream_error_w-1 DOWNTO 0);
-  END RECORD;
-  
-  CONSTANT c_dp_sosi_unsigned_rst  : t_dp_sosi_unsigned := ('0', (OTHERS=>'0'), (OTHERS=>'0'), (OTHERS=>'0'), (OTHERS=>'0'), '0', '0', '0', (OTHERS=>'0'), (OTHERS=>'0'), (OTHERS=>'0'));
-  CONSTANT c_dp_sosi_unsigned_ones : t_dp_sosi_unsigned := ('1',
-                                                            TO_UNSIGNED(1, c_dp_stream_bsn_w),
-                                                            TO_UNSIGNED(1, c_dp_stream_data_w),
-                                                            TO_UNSIGNED(1, c_dp_stream_dsp_data_w),
-                                                            TO_UNSIGNED(1, c_dp_stream_dsp_data_w),
-                                                            '1', '1', '1',
-                                                            TO_UNSIGNED(1, c_dp_stream_empty_w),
-                                                            TO_UNSIGNED(1, c_dp_stream_channel_w),
-                                                            TO_UNSIGNED(1, c_dp_stream_error_w));
-  
-  -- Use boolean to define whether a t_dp_siso, t_dp_sosi field is used ('1') or not ('0')
-  TYPE t_dp_siso_sl IS RECORD
-    ready    : STD_LOGIC;
-    xon      : STD_LOGIC;
-  END RECORD;
-  
-  TYPE t_dp_sosi_sl IS RECORD
-    sync     : STD_LOGIC;
-    bsn      : STD_LOGIC;
-    data     : STD_LOGIC;
-    re       : STD_LOGIC;
-    im       : STD_LOGIC;
-    valid    : STD_LOGIC;
-    sop      : STD_LOGIC;
-    eop      : STD_LOGIC;
-    empty    : STD_LOGIC;
-    channel  : STD_LOGIC;
-    err      : STD_LOGIC;
-  END RECORD;
-  
-  CONSTANT c_dp_siso_sl_rst  : t_dp_siso_sl := ('0', '0');
-  CONSTANT c_dp_siso_sl_ones : t_dp_siso_sl := ('1', '1');
-  CONSTANT c_dp_sosi_sl_rst  : t_dp_sosi_sl := ('0', '0', '0', '0', '0', '0', '0', '0', '0', '0', '0');
-  CONSTANT c_dp_sosi_sl_ones : t_dp_sosi_sl := ('1', '1', '1', '1', '1', '1', '1', '1', '1', '1', '1');
-  
-  -- Multi port or multi register array for DP stream records
-  TYPE t_dp_siso_arr IS ARRAY (INTEGER RANGE <>) OF t_dp_siso;
-  TYPE t_dp_sosi_arr IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi;
-
-  TYPE t_dp_sosi_integer_arr  IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_integer;
-  TYPE t_dp_sosi_unsigned_arr IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_unsigned;
-
-  TYPE t_dp_siso_sl_arr IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_sl;
-  TYPE t_dp_sosi_sl_arr IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_sl;
-  
-  -- Multi port or multi register slv arrays for DP stream records fields
-  TYPE t_dp_bsn_slv_arr      IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_dp_stream_bsn_w-1 DOWNTO 0);
-  TYPE t_dp_data_slv_arr     IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_dp_stream_data_w-1 DOWNTO 0);
-  TYPE t_dp_dsp_data_slv_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_dp_stream_dsp_data_w-1 DOWNTO 0);
-  TYPE t_dp_empty_slv_arr    IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_dp_stream_empty_w-1 DOWNTO 0);
-  TYPE t_dp_channel_slv_arr  IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_dp_stream_channel_w-1 DOWNTO 0);
-  TYPE t_dp_error_slv_arr    IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_dp_stream_error_w-1 DOWNTO 0);
-  
-  -- Multi-dimemsion array types with fixed LS-dimension
-  TYPE t_dp_siso_2arr_1 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_arr(0 DOWNTO 0);
-  TYPE t_dp_sosi_2arr_1 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(0 DOWNTO 0);
-
-  -- . 2 dimensional array with 2 fixed LS sosi/siso interfaces (dp_split, dp_concat)
-  TYPE t_dp_siso_2arr_2 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_arr(1 DOWNTO 0);
-  TYPE t_dp_sosi_2arr_2 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(1 DOWNTO 0);
-
-  TYPE t_dp_siso_2arr_3 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_arr(2 DOWNTO 0);
-  TYPE t_dp_sosi_2arr_3 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(2 DOWNTO 0);
-
-  TYPE t_dp_siso_2arr_4 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_arr(3 DOWNTO 0);
-  TYPE t_dp_sosi_2arr_4 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(3 DOWNTO 0);
-
-  TYPE t_dp_siso_2arr_8 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_arr(7 DOWNTO 0);
-  TYPE t_dp_sosi_2arr_8 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(7 DOWNTO 0);
-
-  TYPE t_dp_siso_2arr_9 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_arr(8 DOWNTO 0);
-  TYPE t_dp_sosi_2arr_9 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(8 DOWNTO 0);
-
-  TYPE t_dp_siso_2arr_12 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_arr(11 DOWNTO 0);
-  TYPE t_dp_sosi_2arr_12 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(11 DOWNTO 0);
- 
-  TYPE t_dp_siso_3arr_4_2 IS ARRAY (INTEGER RANGE <>) OF t_dp_siso_2arr_2(3 DOWNTO 0);
-  TYPE t_dp_sosi_3arr_4_2 IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_2arr_2(3 DOWNTO 0);
- 
-  -- 2-dimensional streaming array type:
-  -- Note:
-  --   This t_*_mat is less useful then a t_*_2arr array of arrays, because assignments can only be done per element (i.e. not per row). However for t_*_2arr
-  --   the arrays dimension must be fixed, so these t_*_2arr types are application dependent and need to be defined where used. 
-  TYPE t_dp_siso_mat IS ARRAY (INTEGER RANGE <>, INTEGER RANGE <>) OF t_dp_siso;
-  TYPE t_dp_sosi_mat IS ARRAY (INTEGER RANGE <>, INTEGER RANGE <>) OF t_dp_sosi;
-
-  -- Check sosi.valid against siso.ready
-  PROCEDURE proc_dp_siso_alert(CONSTANT c_ready_latency : IN    NATURAL;
-                               SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi            : IN    t_dp_sosi;
-                               SIGNAL   siso            : IN    t_dp_siso;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR);
-
-  -- Default RL=1
-  PROCEDURE proc_dp_siso_alert(SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi            : IN    t_dp_sosi;
-                               SIGNAL   siso            : IN    t_dp_siso;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR);
-
-  -- SOSI/SISO array version
-  PROCEDURE proc_dp_siso_alert(CONSTANT c_ready_latency : IN    NATURAL;
-                               SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi_arr        : IN    t_dp_sosi_arr;
-                               SIGNAL   siso_arr        : IN    t_dp_siso_arr;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR);
-
-  -- SOSI/SISO array version with RL=1
-  PROCEDURE proc_dp_siso_alert(SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi_arr        : IN    t_dp_sosi_arr;
-                               SIGNAL   siso_arr        : IN    t_dp_siso_arr;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR);
-
-  -- Resize functions to fit an integer or an SLV in the corresponding t_dp_sosi field width
-  -- . Use these functions to assign sosi data TO a record field
-  -- . Use the range selection [n-1 DOWNTO 0] to assign sosi data FROM a record field to an slv
-  -- . The unused sosi data field bits could remain undefined 'X', because the unused bits in the fields are not used at all. 
-  --   Typically the sosi data are treated as unsigned in the record field, so extended with '0'. However for interpretating
-  --   signed data in the simulation wave window it is easier to use sign extension in the record field. Therefore TO_DP_SDATA
-  --   and RESIZE_DP_SDATA are defined as well.
-  FUNCTION TO_DP_BSN(     n : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION TO_DP_DATA(    n : INTEGER) RETURN STD_LOGIC_VECTOR;  -- use integer to support 32 bit range, so -1 = 0xFFFFFFFF = +2**32-1
-  FUNCTION TO_DP_SDATA(   n : INTEGER) RETURN STD_LOGIC_VECTOR;  -- use integer to support 32 bit range and signed
-  FUNCTION TO_DP_UDATA(   n : INTEGER) RETURN STD_LOGIC_VECTOR;  -- alias of TO_DP_DATA()
-  FUNCTION TO_DP_DSP_DATA(n : INTEGER) RETURN STD_LOGIC_VECTOR;  -- for re and im fields, signed data
-  FUNCTION TO_DP_DSP_UDATA(n: INTEGER) RETURN STD_LOGIC_VECTOR;  -- for re and im fields, unsigned data (useful to carry indices)
-  FUNCTION TO_DP_EMPTY(   n : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION TO_DP_CHANNEL( n : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION TO_DP_ERROR(   n : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION RESIZE_DP_BSN(     vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;
-  FUNCTION RESIZE_DP_DATA(    vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;  -- set unused MSBits to '0'
-  FUNCTION RESIZE_DP_SDATA(   vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;  -- sign extend unused MSBits
-  FUNCTION RESIZE_DP_XDATA(   vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;  -- set unused MSBits to 'X'
-  FUNCTION RESIZE_DP_DSP_DATA(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;  -- sign extend unused MSBits of re and im fields
-  FUNCTION RESIZE_DP_EMPTY(   vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;
-  FUNCTION RESIZE_DP_CHANNEL( vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;
-  FUNCTION RESIZE_DP_ERROR(   vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;
-  
-  FUNCTION INCR_DP_DATA(    vec : STD_LOGIC_VECTOR; dec : INTEGER; w : NATURAL) RETURN STD_LOGIC_VECTOR;  -- unsigned vec(w-1:0) + dec
-  FUNCTION INCR_DP_SDATA(   vec : STD_LOGIC_VECTOR; dec : INTEGER; w : NATURAL) RETURN STD_LOGIC_VECTOR;  --   signed vec(w-1:0) + dec
-  FUNCTION INCR_DP_DSP_DATA(vec : STD_LOGIC_VECTOR; dec : INTEGER; w : NATURAL) RETURN STD_LOGIC_VECTOR;  --   signed vec(w-1:0) + dec
-  
-  FUNCTION REPLICATE_DP_DATA(  seq  : STD_LOGIC_VECTOR                 ) RETURN STD_LOGIC_VECTOR;  -- replicate seq as often as fits in c_dp_stream_data_w
-  FUNCTION UNREPLICATE_DP_DATA(data : STD_LOGIC_VECTOR; seq_w : NATURAL) RETURN STD_LOGIC_VECTOR;  -- unreplicate data to width seq_w, return low seq_w bits and set mismatch MSbits bits to '1'
-
-  FUNCTION TO_DP_SOSI_UNSIGNED(sync, valid, sop, eop : STD_LOGIC; bsn, data, re, im, empty, channel, err : UNSIGNED) RETURN t_dp_sosi_unsigned;
-
-  -- Keep part of head data and combine part of tail data, use the other sosi from head_sosi
-  FUNCTION func_dp_data_shift_first(head_sosi, tail_sosi : t_dp_sosi; symbol_w, nof_symbols_per_data, nof_symbols_from_tail              : NATURAL) RETURN t_dp_sosi;
-  -- Shift and combine part of previous data and this data, use the other sosi from prev_sosi
-  FUNCTION func_dp_data_shift(      prev_sosi, this_sosi : t_dp_sosi; symbol_w, nof_symbols_per_data, nof_symbols_from_this              : NATURAL) RETURN t_dp_sosi;
-  -- Shift part of tail data and account for input empty
-  FUNCTION func_dp_data_shift_last(            tail_sosi : t_dp_sosi; symbol_w, nof_symbols_per_data, nof_symbols_from_tail, input_empty : NATURAL) RETURN t_dp_sosi;
-    
-  -- Determine resulting empty if two streams are concatenated or split
-  FUNCTION func_dp_empty_concat(head_empty, tail_empty : STD_LOGIC_VECTOR; nof_symbols_per_data : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION func_dp_empty_split(input_empty, head_empty : STD_LOGIC_VECTOR; nof_symbols_per_data : NATURAL) RETURN STD_LOGIC_VECTOR;
-  
-  -- Multiplex the t_dp_sosi_arr based on the valid, assuming that at most one input is active valid.
-  FUNCTION func_dp_sosi_arr_mux(dp : t_dp_sosi_arr) RETURN t_dp_sosi;
-  
-  -- Determine the combined logical value of corresponding STD_LOGIC fields in t_dp_*_arr (for all elements or only for the mask[]='1' elements)
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_siso_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC;
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC;
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_siso_arr;                          str : STRING) RETURN STD_LOGIC;
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_sosi_arr;                          str : STRING) RETURN STD_LOGIC;
-  FUNCTION func_dp_stream_arr_or( dp : t_dp_siso_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC;
-  FUNCTION func_dp_stream_arr_or( dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC;
-  FUNCTION func_dp_stream_arr_or( dp : t_dp_siso_arr;                          str : STRING) RETURN STD_LOGIC;
-  FUNCTION func_dp_stream_arr_or( dp : t_dp_sosi_arr;                          str : STRING) RETURN STD_LOGIC;
-  
-  -- Functions to set or get a STD_LOGIC field as a STD_LOGIC_VECTOR to or from an siso or an sosi array
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_siso_arr; slv : STD_LOGIC_VECTOR; str : STRING) RETURN t_dp_siso_arr;
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_sosi_arr; slv : STD_LOGIC_VECTOR; str : STRING) RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_siso_arr; sl  : STD_LOGIC;        str : STRING) RETURN t_dp_siso_arr;
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_sosi_arr; sl  : STD_LOGIC;        str : STRING) RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_get(dp : t_dp_siso_arr;                         str : STRING) RETURN STD_LOGIC_VECTOR;
-  FUNCTION func_dp_stream_arr_get(dp : t_dp_sosi_arr;                         str : STRING) RETURN STD_LOGIC_VECTOR;
-  
-  -- Functions to select elements from two siso or two sosi arrays (sel[] = '1' selects a, sel[] = '0' selects b)
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a,                 b : t_dp_siso)     RETURN t_dp_siso_arr;
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a,                 b : t_dp_sosi)     RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_siso_arr; b : t_dp_siso)     RETURN t_dp_siso_arr;
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_sosi_arr; b : t_dp_sosi)     RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_siso;     b : t_dp_siso_arr) RETURN t_dp_siso_arr;
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_sosi;     b : t_dp_sosi_arr) RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a,                 b : t_dp_siso_arr) RETURN t_dp_siso_arr;
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a,                 b : t_dp_sosi_arr) RETURN t_dp_sosi_arr;
-
-  -- Fix reversed buses due to connecting TO to DOWNTO range arrays. 
-  FUNCTION func_dp_stream_arr_reverse_range(in_arr : t_dp_sosi_arr) RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_reverse_range(in_arr : t_dp_siso_arr) RETURN t_dp_siso_arr;
-
-  -- Functions to combinatorially hold the data fields and to set or reset the control fields in an sosi array
-  FUNCTION func_dp_stream_arr_combine_data_info_ctrl(dp : t_dp_sosi_arr; info, ctrl : t_dp_sosi) RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_set_info(              dp : t_dp_sosi_arr; info       : t_dp_sosi) RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_set_control(           dp : t_dp_sosi_arr;       ctrl : t_dp_sosi) RETURN t_dp_sosi_arr;
-  FUNCTION func_dp_stream_arr_reset_control(         dp : t_dp_sosi_arr                        ) RETURN t_dp_sosi_arr;
-  
-  -- Reset sosi ctrl and preserve the sosi data (to avoid unnecessary data toggling and to ease data view in Wave window)
-  FUNCTION func_dp_stream_reset_control(dp : t_dp_sosi) RETURN t_dp_sosi;
-  
-  -- Functions to combinatorially determine the maximum and minimum sosi bsn[w-1:0] value in the sosi array (for all elements or only for the mask[]='1' elements)
-  FUNCTION func_dp_stream_arr_bsn_max(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; w : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION func_dp_stream_arr_bsn_max(dp : t_dp_sosi_arr;                          w : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION func_dp_stream_arr_bsn_min(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; w : NATURAL) RETURN STD_LOGIC_VECTOR;
-  FUNCTION func_dp_stream_arr_bsn_min(dp : t_dp_sosi_arr;                          w : NATURAL) RETURN STD_LOGIC_VECTOR;
-  
-  -- Function to copy the BSN of one valid stream to all output streams. 
-  FUNCTION func_dp_stream_arr_copy_valid_bsn(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR) RETURN t_dp_sosi_arr;
-  
-  -- Functions to combinatorially handle channels
-  -- Note that the *_select and *_remove function are equivalent to dp_demux with g_combined=TRUE
-  FUNCTION func_dp_stream_channel_set   (st_sosi : t_dp_sosi; ch : NATURAL) RETURN t_dp_sosi;  -- select channel nr, add the channel field
-  FUNCTION func_dp_stream_channel_select(st_sosi : t_dp_sosi; ch : NATURAL) RETURN t_dp_sosi;  -- select channel nr, skip the channel field
-  FUNCTION func_dp_stream_channel_remove(st_sosi : t_dp_sosi; ch : NATURAL) RETURN t_dp_sosi;  -- skip channel nr
-  
-  -- Functions to combinatorially handle the error field
-  FUNCTION func_dp_stream_error_set(st_sosi : t_dp_sosi; n : NATURAL) RETURN t_dp_sosi;  -- force err = 0, is OK
-  
-  -- Functions to combinatorially handle the BSN field
-  FUNCTION func_dp_stream_bsn_set(st_sosi : t_dp_sosi; bsn : STD_LOGIC_VECTOR) RETURN t_dp_sosi;
-  
-  -- Functions to combine sosi fields
-  FUNCTION func_dp_stream_combine_info_and_data(info, data : t_dp_sosi) RETURN t_dp_sosi;
-  
-  -- Functions to convert sosi fields
-  FUNCTION func_dp_stream_slv_to_integer(slv_sosi : t_dp_sosi; w : NATURAL) RETURN t_dp_sosi_integer;
-
-  -- Functions to set the DATA, RE and IM field in a stream.
-  FUNCTION func_dp_stream_set_data(dp : t_dp_sosi;     slv : STD_LOGIC_VECTOR; str : STRING                         ) RETURN t_dp_sosi;
-  FUNCTION func_dp_stream_set_data(dp : t_dp_sosi_arr; slv : STD_LOGIC_VECTOR; str : STRING                         ) RETURN t_dp_sosi_arr; 
-  FUNCTION func_dp_stream_set_data(dp : t_dp_sosi_arr; slv : STD_LOGIC_VECTOR; str : STRING; mask : STD_LOGIC_VECTOR) RETURN t_dp_sosi_arr;
- 
-  -- Concatenate the data from a SOSI array into a single SOSI stream (assumes streams are in sync)
-  FUNCTION func_dp_stream_concat(snk_in_arr : t_dp_sosi_arr; data_w : NATURAL) RETURN t_dp_sosi; -- Concat SOSI_ARR data into single SOSI
-  FUNCTION func_dp_stream_concat(src_in     : t_dp_siso; nof_streams : NATURAL) RETURN t_dp_siso_arr; -- Wire single SISO to SISO_ARR
-  -- Deconcatenate data from SOSI into SOSI array
-  FUNCTION func_dp_stream_deconcat(snk_in      : t_dp_sosi; nof_streams, data_w : NATURAL) RETURN t_dp_sosi_arr; -- Deconcat SOSI data
-  FUNCTION func_dp_stream_deconcat(src_out_arr : t_dp_siso_arr) RETURN t_dp_siso; -- Wire SISO_ARR(0) to single SISO 
-  
-END dp_stream_pkg;
-
-
-PACKAGE BODY dp_stream_pkg IS
- 
-  -- Check sosi.valid against siso.ready
-  PROCEDURE proc_dp_siso_alert(CONSTANT c_ready_latency : IN    NATURAL;
-                               SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi            : IN    t_dp_sosi;
-                               SIGNAL   siso            : IN    t_dp_siso;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    ready_reg(0) <= siso.ready;
-    -- Register siso.ready in c_ready_latency registers
-    IF rising_edge(clk) THEN
-      -- Check DP sink
-      IF sosi.valid = '1' AND ready_reg(c_ready_latency) = '0' THEN
-        REPORT "RL ERROR" SEVERITY FAILURE;
-      END IF;
-      ready_reg( 1 TO c_ready_latency) <= ready_reg( 0 TO c_ready_latency-1);
-    END IF;
-  END proc_dp_siso_alert;
-
-  -- Default RL=1
-  PROCEDURE proc_dp_siso_alert(SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi            : IN    t_dp_sosi;
-                               SIGNAL   siso            : IN    t_dp_siso;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    proc_dp_siso_alert(1, clk, sosi, siso, ready_reg);
-  END proc_dp_siso_alert;
-
-  -- SOSI/SISO array version
-  PROCEDURE proc_dp_siso_alert(CONSTANT c_ready_latency : IN    NATURAL;
-                               SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi_arr        : IN    t_dp_sosi_arr;
-                               SIGNAL   siso_arr        : IN    t_dp_siso_arr;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    FOR i IN 0 TO sosi_arr'LENGTH-1 LOOP 
-      ready_reg(i*(c_ready_latency+1)) <= siso_arr(i).ready; -- SLV is used as an array: nof_streams*(0..c_ready_latency)
-    END LOOP;
-    -- Register siso.ready in c_ready_latency registers
-    IF rising_edge(clk) THEN
-      FOR i IN 0 TO sosi_arr'LENGTH-1 LOOP
-        -- Check DP sink
-        IF sosi_arr(i).valid = '1' AND ready_reg(i*(c_ready_latency+1)+1) = '0' THEN
-          REPORT "RL ERROR" SEVERITY FAILURE;
-        END IF; 
-        ready_reg(i*(c_ready_latency+1)+1 TO i*(c_ready_latency+1)+c_ready_latency) <=  ready_reg(i*(c_ready_latency+1) TO i*(c_ready_latency+1)+c_ready_latency-1);
-      END LOOP;
-    END IF;  
-  END proc_dp_siso_alert;
-
-  -- SOSI/SISO array version with RL=1
-  PROCEDURE proc_dp_siso_alert(SIGNAL   clk             : IN    STD_LOGIC;
-                               SIGNAL   sosi_arr        : IN    t_dp_sosi_arr;
-                               SIGNAL   siso_arr        : IN    t_dp_siso_arr;
-                               SIGNAL   ready_reg       : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    proc_dp_siso_alert(1, clk, sosi_arr, siso_arr, ready_reg);
-  END proc_dp_siso_alert;
- 
-  -- Resize functions to fit an integer or an SLV in the corresponding t_dp_sosi field width
-  FUNCTION TO_DP_BSN(n : NATURAL) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(TO_SVEC(n, 32), c_dp_stream_bsn_w);
-  END TO_DP_BSN;
-  
-  FUNCTION TO_DP_DATA(n : INTEGER) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(TO_SVEC(n, 32), c_dp_stream_data_w);
-  END TO_DP_DATA;
-  
-  FUNCTION TO_DP_SDATA(n : INTEGER) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_SVEC(TO_SVEC(n, 32), c_dp_stream_data_w);
-  END TO_DP_SDATA;
-  
-  FUNCTION TO_DP_UDATA(n : INTEGER) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN TO_DP_DATA(n);
-  END TO_DP_UDATA;
-  
-  FUNCTION TO_DP_DSP_DATA(n : INTEGER) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_SVEC(TO_SVEC(n, 32), c_dp_stream_dsp_data_w);
-  END TO_DP_DSP_DATA;
-  
-  FUNCTION TO_DP_DSP_UDATA(n : INTEGER) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(TO_SVEC(n, 32), c_dp_stream_dsp_data_w);
-  END TO_DP_DSP_UDATA;
-  
-  FUNCTION TO_DP_EMPTY(n : NATURAL) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN TO_UVEC(n, c_dp_stream_empty_w);
-  END TO_DP_EMPTY;
-  
-  FUNCTION TO_DP_CHANNEL(n : NATURAL) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN TO_UVEC(n, c_dp_stream_channel_w);
-  END TO_DP_CHANNEL;
-  
-  FUNCTION TO_DP_ERROR(n : NATURAL) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN TO_UVEC(n, c_dp_stream_error_w);
-  END TO_DP_ERROR;
-  
-  FUNCTION RESIZE_DP_BSN(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(vec, c_dp_stream_bsn_w);
-  END RESIZE_DP_BSN;
-  
-  FUNCTION RESIZE_DP_DATA(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(vec, c_dp_stream_data_w);
-  END RESIZE_DP_DATA;
-  
-  FUNCTION RESIZE_DP_SDATA(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_SVEC(vec, c_dp_stream_data_w);
-  END RESIZE_DP_SDATA;
-  
-  FUNCTION RESIZE_DP_XDATA(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-    VARIABLE v_vec : STD_LOGIC_VECTOR(c_dp_stream_data_w-1 DOWNTO 0) := (OTHERS=>'X');
-  BEGIN
-    v_vec(vec'LENGTH-1 DOWNTO 0) := vec;
-    RETURN v_vec;
-  END RESIZE_DP_XDATA;
-  
-  FUNCTION RESIZE_DP_DSP_DATA(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_SVEC(vec, c_dp_stream_dsp_data_w);
-  END RESIZE_DP_DSP_DATA;
-  
-  FUNCTION RESIZE_DP_EMPTY(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(vec, c_dp_stream_empty_w);
-  END RESIZE_DP_EMPTY;
-  
-  FUNCTION RESIZE_DP_CHANNEL(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(vec, c_dp_stream_channel_w);
-  END RESIZE_DP_CHANNEL;
-  
-  FUNCTION RESIZE_DP_ERROR(vec : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_UVEC(vec, c_dp_stream_error_w);
-  END RESIZE_DP_ERROR;
-  
-  FUNCTION INCR_DP_DATA(vec : STD_LOGIC_VECTOR; dec : INTEGER; w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_DP_DATA(STD_LOGIC_VECTOR(UNSIGNED(vec(w-1 DOWNTO 0)) + dec));
-  END INCR_DP_DATA;
-  
-  FUNCTION INCR_DP_SDATA(vec : STD_LOGIC_VECTOR; dec : INTEGER; w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_DP_SDATA(STD_LOGIC_VECTOR(SIGNED(vec(w-1 DOWNTO 0)) + dec));
-  END INCR_DP_SDATA;
-
-  FUNCTION INCR_DP_DSP_DATA(vec : STD_LOGIC_VECTOR; dec : INTEGER; w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-  BEGIN
-    RETURN RESIZE_DP_DSP_DATA(STD_LOGIC_VECTOR(SIGNED(vec(w-1 DOWNTO 0)) + dec));
-  END INCR_DP_DSP_DATA;  
-  
-  FUNCTION REPLICATE_DP_DATA(seq : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-    CONSTANT c_seq_w            : NATURAL := seq'LENGTH;
-    CONSTANT c_nof_replications : NATURAL := ceil_div(c_dp_stream_data_w, c_seq_w);
-    CONSTANT c_vec_w            : NATURAL := ceil_value(c_dp_stream_data_w, c_seq_w);
-    VARIABLE v_vec              : STD_LOGIC_VECTOR(c_vec_w-1 DOWNTO 0);
-  BEGIN
-    FOR I IN 0 TO c_nof_replications-1 LOOP
-      v_vec((I+1)*c_seq_w-1 DOWNTO I*c_seq_w) := seq;
-    END LOOP;
-    RETURN v_vec(c_dp_stream_data_w-1 DOWNTO 0);
-  END REPLICATE_DP_DATA;
-  
-  FUNCTION UNREPLICATE_DP_DATA(data : STD_LOGIC_VECTOR; seq_w :NATURAL) RETURN STD_LOGIC_VECTOR IS
-    CONSTANT c_data_w           : NATURAL := data'LENGTH;
-    CONSTANT c_nof_replications : NATURAL := ceil_div(c_data_w, seq_w);
-    CONSTANT c_vec_w            : NATURAL := ceil_value(c_data_w, seq_w);
-    VARIABLE v_seq              : STD_LOGIC_VECTOR(seq_w-1 DOWNTO 0);
-    VARIABLE v_data             : STD_LOGIC_VECTOR(c_vec_w-1 DOWNTO 0);
-    VARIABLE v_vec              : STD_LOGIC_VECTOR(c_vec_w-1 DOWNTO 0);
-  BEGIN
-    v_data := RESIZE_UVEC(data, c_vec_w);
-    v_seq := v_data(seq_w-1 DOWNTO 0);                                                          -- low data part is the v_seq
-    v_vec(seq_w-1 DOWNTO 0) := v_seq;                                                           -- keep v_seq at low part of return value
-    IF c_nof_replications>1 THEN
-      FOR I IN 1 TO c_nof_replications-1 LOOP
-        v_vec((I+1)*seq_w-1 DOWNTO I*seq_w) := v_data((I+1)*seq_w-1 DOWNTO I*seq_w) XOR v_seq;  -- set return bit to '1' for high part data bits that do not match low part v_seq
-      END LOOP;
-    END IF;
-    RETURN v_vec(c_data_w-1 DOWNTO 0);
-  END UNREPLICATE_DP_DATA;
-  
-  FUNCTION TO_DP_SOSI_UNSIGNED(sync, valid, sop, eop : STD_LOGIC; bsn, data, re, im, empty, channel, err : UNSIGNED) RETURN t_dp_sosi_unsigned IS
-    VARIABLE v_sosi_unsigned : t_dp_sosi_unsigned;
-  BEGIN
-    v_sosi_unsigned.sync    := sync;
-    v_sosi_unsigned.valid   := valid;
-    v_sosi_unsigned.sop     := sop;
-    v_sosi_unsigned.eop     := eop;
-    v_sosi_unsigned.bsn     := RESIZE(bsn,     c_dp_stream_bsn_w);
-    v_sosi_unsigned.data    := RESIZE(data,    c_dp_stream_data_w);
-    v_sosi_unsigned.re      := RESIZE(re,      c_dp_stream_dsp_data_w);
-    v_sosi_unsigned.im      := RESIZE(im,      c_dp_stream_dsp_data_w);
-    v_sosi_unsigned.empty   := RESIZE(empty,   c_dp_stream_empty_w);
-    v_sosi_unsigned.channel := RESIZE(channel, c_dp_stream_channel_w);
-    v_sosi_unsigned.err     := RESIZE(err,     c_dp_stream_error_w);
-    RETURN v_sosi_unsigned;
-  END TO_DP_SOSI_UNSIGNED;
-
-  -- Keep part of head data and combine part of tail data
-  FUNCTION func_dp_data_shift_first(head_sosi, tail_sosi : t_dp_sosi; symbol_w, nof_symbols_per_data, nof_symbols_from_tail : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE vN     : NATURAL := nof_symbols_per_data;
-    VARIABLE v_sosi : t_dp_sosi;
-  BEGIN
-    ASSERT nof_symbols_from_tail<vN REPORT "func_dp_data_shift_first : no symbols from head" SEVERITY FAILURE;
-    -- use the other sosi from head_sosi
-    v_sosi := head_sosi;     -- I = nof_symbols_from_tail = 0
-    FOR I IN 1 TO vN-1 LOOP  -- I > 0
-      IF nof_symbols_from_tail = I THEN
-        v_sosi.data(I*symbol_w-1 DOWNTO 0) := tail_sosi.data(vN*symbol_w-1 DOWNTO (vN-I)*symbol_w);
-      END IF;
-    END LOOP;
-    RETURN v_sosi;
-  END func_dp_data_shift_first;
-  
-  
-  -- Shift and combine part of previous data and this data,
-  FUNCTION func_dp_data_shift(prev_sosi, this_sosi : t_dp_sosi; symbol_w, nof_symbols_per_data, nof_symbols_from_this : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE vK     : NATURAL := nof_symbols_from_this;
-    VARIABLE vN     : NATURAL := nof_symbols_per_data;
-    VARIABLE v_sosi : t_dp_sosi;
-  BEGIN
-    -- use the other sosi from this_sosi if nof_symbols_from_this > 0 else use other sosi from prev_sosi
-    IF vK>0 THEN
-      v_sosi := this_sosi;
-    ELSE
-      v_sosi := prev_sosi;
-    END IF;
-    
-    -- use sosi data from both if 0 < nof_symbols_from_this < nof_symbols_per_data (i.e. 0 < I < vN)
-    IF vK<nof_symbols_per_data THEN   -- I = vK = nof_symbols_from_this < vN
-      -- Implementation using variable vK directly instead of via I in a LOOP
-      -- IF vK > 0 THEN
-      --   v_sosi.data(vN*symbol_w-1 DOWNTO vK*symbol_w)            := prev_sosi.data((vN-vK)*symbol_w-1 DOWNTO                0);
-      --   v_sosi.data(                     vK*symbol_w-1 DOWNTO 0) := this_sosi.data( vN    *symbol_w-1 DOWNTO (vN-vK)*symbol_w);
-      -- END IF;
-      -- Implementaion using LOOP vK rather than VARIABLE vK directly as index to help synthesis and avoid potential multiplier
-      v_sosi.data := prev_sosi.data;  -- I = vK = nof_symbols_from_this = 0
-      FOR I IN 1 TO vN-1 LOOP         -- I = vK = nof_symbols_from_this > 0
-        IF vK = I THEN
-          v_sosi.data(vN*symbol_w-1 DOWNTO I*symbol_w)            := prev_sosi.data((vN-I)*symbol_w-1 DOWNTO               0);
-          v_sosi.data(                     I*symbol_w-1 DOWNTO 0) := this_sosi.data( vN   *symbol_w-1 DOWNTO (vN-I)*symbol_w);
-        END IF;
-      END LOOP;
-    END IF;
-    RETURN v_sosi;
-  END func_dp_data_shift;
-  
-  
-  -- Shift part of tail data and account for input empty
-  FUNCTION func_dp_data_shift_last(tail_sosi : t_dp_sosi; symbol_w, nof_symbols_per_data, nof_symbols_from_tail, input_empty : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE vK     : NATURAL := nof_symbols_from_tail;
-    VARIABLE vL     : NATURAL := input_empty;
-    VARIABLE vN     : NATURAL := nof_symbols_per_data;
-    VARIABLE v_sosi : t_dp_sosi;
-  BEGIN
-    ASSERT vK   > 0  REPORT "func_dp_data_shift_last : no symbols from tail" SEVERITY FAILURE;
-    ASSERT vK+vL<=vN REPORT "func_dp_data_shift_last : impossible shift" SEVERITY FAILURE;
-    v_sosi := tail_sosi;
-    -- Implementation using variable vK directly instead of via I in a LOOP
-    -- IF vK > 0 THEN
-    --   v_sosi.data(vN*symbol_w-1 DOWNTO (vN-vK)*symbol_w) <= tail_sosi.data((vK+vL)*symbol_w-1 DOWNTO vL*symbol_w);
-    -- END IF;  
-    -- Implementation using LOOP vK rather than VARIABLE vK directly as index to help synthesis and avoid potential multiplier
-    -- Implementation using LOOP vL rather than VARIABLE vL directly as index to help synthesis and avoid potential multiplier
-    FOR I IN 1 TO vN-1 LOOP
-      IF vK = I THEN
-        FOR J IN 0 TO vN-1 LOOP
-          IF vL = J THEN
-            v_sosi.data(vN*symbol_w-1 DOWNTO (vN-I)*symbol_w) := tail_sosi.data((I+J)*symbol_w-1 DOWNTO J*symbol_w);
-          END IF;
-        END LOOP;
-      END IF;
-    END LOOP;
-    RETURN v_sosi;
-  END func_dp_data_shift_last;  
-
-  
-  -- Determine resulting empty if two streams are concatenated
-  -- . both empty must use the same nof symbols per data
-  FUNCTION func_dp_empty_concat(head_empty, tail_empty : STD_LOGIC_VECTOR; nof_symbols_per_data : NATURAL) RETURN STD_LOGIC_VECTOR IS
-    VARIABLE v_a, v_b, v_empty : NATURAL;
-  BEGIN
-    v_a := TO_UINT(head_empty);
-    v_b := TO_UINT(tail_empty);
-    v_empty := v_a + v_b;
-    IF v_empty >= nof_symbols_per_data THEN
-      v_empty := v_empty - nof_symbols_per_data;
-    END IF;
-    RETURN TO_UVEC(v_empty, head_empty'LENGTH);
-  END func_dp_empty_concat;
-  
-  FUNCTION func_dp_empty_split(input_empty, head_empty : STD_LOGIC_VECTOR; nof_symbols_per_data : NATURAL) RETURN STD_LOGIC_VECTOR IS
-    VARIABLE v_a, v_b, v_empty : NATURAL;
-  BEGIN
-    v_a   := TO_UINT(input_empty);
-    v_b   := TO_UINT(head_empty);
-    IF v_a >= v_b THEN
-      v_empty := v_a - v_b;
-    ELSE
-      v_empty := (nof_symbols_per_data + v_a) - v_b;
-    END IF;
-    RETURN TO_UVEC(v_empty, head_empty'LENGTH);
-  END func_dp_empty_split;
-  
-  
-  -- Multiplex the t_dp_sosi_arr based on the valid, assuming that at most one input is active valid.
-  FUNCTION func_dp_sosi_arr_mux(dp : t_dp_sosi_arr) RETURN t_dp_sosi IS
-    VARIABLE v_sosi : t_dp_sosi := c_dp_sosi_rst;
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF dp(I).valid='1' THEN
-        v_sosi := dp(I);
-        EXIT;
-      END IF;
-    END LOOP;
-    RETURN v_sosi;
-  END func_dp_sosi_arr_mux;
-
-  
-  -- Determine the combined logical value of corresponding STD_LOGIC fields in t_dp_*_arr (for all elements or only for the mask[]='1' elements)
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_siso_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC IS
-    VARIABLE v_vec : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');  -- set default v_vec such that unmasked input have no influence on operation result
-    VARIABLE v_any : STD_LOGIC := '0';
-  BEGIN
-    -- map siso field to v_vec
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='1' THEN
-        v_any := '1';
-        IF    str="READY" THEN v_vec(I) := dp(I).ready;
-        ELSIF str="XON"   THEN v_vec(I) := dp(I).xon;
-        ELSE  REPORT "Error in func_dp_stream_arr_and for t_dp_siso_arr";
-        END IF;
-      END IF;
-    END LOOP;
-    -- do operation on the selected record field
-    IF v_any='1' THEN
-      RETURN vector_and(v_vec);   -- return AND of the masked input fields
-    ELSE
-      RETURN '0';                 -- return '0' if no input was masked
-    END IF;
-  END func_dp_stream_arr_and;
-  
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC IS
-    VARIABLE v_vec : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');  -- set default v_vec such that unmasked input have no influence on operation result
-    VARIABLE v_any : STD_LOGIC := '0';
-  BEGIN
-    -- map siso field to v_vec
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='1' THEN
-        v_any := '1';
-        IF    str="VALID" THEN v_vec(I) := dp(I).valid;
-        ELSIF str="SOP"   THEN v_vec(I) := dp(I).sop;
-        ELSIF str="EOP"   THEN v_vec(I) := dp(I).eop;
-        ELSIF str="SYNC"  THEN v_vec(I) := dp(I).sync;
-        ELSE  REPORT "Error in func_dp_stream_arr_and for t_dp_sosi_arr";
-        END IF;
-      END IF;
-    END LOOP;
-    -- do operation on the selected record field
-    IF v_any='1' THEN
-      RETURN vector_and(v_vec);   -- return AND of the masked input fields
-    ELSE
-      RETURN '0';                 -- return '0' if no input was masked
-    END IF;
-  END func_dp_stream_arr_and;
-  
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_siso_arr; str : STRING) RETURN STD_LOGIC IS
-    CONSTANT c_mask : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');
-  BEGIN
-    RETURN func_dp_stream_arr_and(dp, c_mask, str);
-  END func_dp_stream_arr_and;
-  
-  FUNCTION func_dp_stream_arr_and(dp : t_dp_sosi_arr; str : STRING) RETURN STD_LOGIC IS
-    CONSTANT c_mask : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');
-  BEGIN
-    RETURN func_dp_stream_arr_and(dp, c_mask, str);
-  END func_dp_stream_arr_and;
-  
-  FUNCTION func_dp_stream_arr_or(dp : t_dp_siso_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC IS
-    VARIABLE v_vec : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'0');  -- set default v_vec such that unmasked input have no influence on operation result
-    VARIABLE v_any : STD_LOGIC := '0';
-  BEGIN
-    -- map siso field to v_vec
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='1' THEN
-        v_any := '1';
-        IF    str="READY" THEN v_vec(I) := dp(I).ready;
-        ELSIF str="XON"   THEN v_vec(I) := dp(I).xon;
-        ELSE  REPORT "Error in func_dp_stream_arr_or for t_dp_siso_arr";
-        END IF;
-      END IF;
-    END LOOP;
-    -- do operation on the selected record field
-    IF v_any='1' THEN
-      RETURN vector_or(v_vec);   -- return OR of the masked input fields
-    ELSE
-      RETURN '0';                -- return '0' if no input was masked
-    END IF;
-  END func_dp_stream_arr_or;
-  
-  FUNCTION func_dp_stream_arr_or(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; str : STRING) RETURN STD_LOGIC IS
-    VARIABLE v_vec : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'0');  -- set default v_vec such that unmasked input have no influence on operation result
-    VARIABLE v_any : STD_LOGIC := '0';
-  BEGIN
-    -- map siso field to v_vec
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='1' THEN
-        v_any := '1';
-        IF    str="VALID" THEN v_vec(I) := dp(I).valid;
-        ELSIF str="SOP"   THEN v_vec(I) := dp(I).sop;
-        ELSIF str="EOP"   THEN v_vec(I) := dp(I).eop;
-        ELSIF str="SYNC"  THEN v_vec(I) := dp(I).sync;
-        ELSE  REPORT "Error in func_dp_stream_arr_or for t_dp_sosi_arr";
-        END IF;
-      END IF;
-    END LOOP;
-    -- do operation on the selected record field
-    IF v_any='1' THEN
-      RETURN vector_or(v_vec);   -- return OR of the masked input fields
-    ELSE
-      RETURN '0';                -- return '0' if no input was masked
-    END IF;
-  END func_dp_stream_arr_or;
-  
-  FUNCTION func_dp_stream_arr_or(dp : t_dp_siso_arr; str : STRING) RETURN STD_LOGIC IS
-    CONSTANT c_mask : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');
-  BEGIN
-    RETURN func_dp_stream_arr_or(dp, c_mask, str);
-  END func_dp_stream_arr_or;
-  
-  FUNCTION func_dp_stream_arr_or(dp : t_dp_sosi_arr; str : STRING) RETURN STD_LOGIC IS
-    CONSTANT c_mask : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');
-  BEGIN
-    RETURN func_dp_stream_arr_or(dp, c_mask, str);
-  END func_dp_stream_arr_or;
-  
-  
-  -- Functions to set or get a STD_LOGIC field as a STD_LOGIC_VECTOR to or from an siso or an sosi array
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_siso_arr; slv : STD_LOGIC_VECTOR; str : STRING) RETURN t_dp_siso_arr IS
-    VARIABLE v_dp  : t_dp_siso_arr(dp'RANGE)    := dp;   -- default
-    VARIABLE v_slv : STD_LOGIC_VECTOR(dp'RANGE) := slv;  -- map to ensure same range as for dp
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF    str="READY" THEN v_dp(I).ready := v_slv(I);
-      ELSIF str="XON"   THEN v_dp(I).xon   := v_slv(I);
-      ELSE  REPORT "Error in func_dp_stream_arr_set for t_dp_siso_arr";
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_set;
-  
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_sosi_arr; slv : STD_LOGIC_VECTOR; str : STRING) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp  : t_dp_sosi_arr(dp'RANGE)    := dp;   -- default
-    VARIABLE v_slv : STD_LOGIC_VECTOR(dp'RANGE) := slv;  -- map to ensure same range as for dp
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF    str="VALID" THEN v_dp(I).valid := v_slv(I);
-      ELSIF str="SOP"   THEN v_dp(I).sop   := v_slv(I);
-      ELSIF str="EOP"   THEN v_dp(I).eop   := v_slv(I);
-      ELSIF str="SYNC"  THEN v_dp(I).sync  := v_slv(I);
-      ELSE  REPORT "Error in func_dp_stream_arr_set for t_dp_sosi_arr";
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_set;
-  
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_siso_arr; sl : STD_LOGIC; str : STRING) RETURN t_dp_siso_arr IS
-    VARIABLE v_slv : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>sl);
-  BEGIN
-    RETURN func_dp_stream_arr_set(dp, v_slv, str);
-  END func_dp_stream_arr_set;
-  
-  FUNCTION func_dp_stream_arr_set(dp : t_dp_sosi_arr; sl : STD_LOGIC; str : STRING) RETURN t_dp_sosi_arr IS
-    VARIABLE v_slv : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>sl);
-  BEGIN
-    RETURN func_dp_stream_arr_set(dp, v_slv, str);
-  END func_dp_stream_arr_set;
-  
-  FUNCTION func_dp_stream_arr_get(dp : t_dp_siso_arr; str : STRING) RETURN STD_LOGIC_VECTOR IS
-    VARIABLE v_ctrl : STD_LOGIC_VECTOR(dp'RANGE);
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF    str="READY" THEN v_ctrl(I) := dp(I).ready;
-      ELSIF str="XON"   THEN v_ctrl(I) := dp(I).xon;
-      ELSE  REPORT "Error in func_dp_stream_arr_get for t_dp_siso_arr";
-      END IF;
-    END LOOP;
-    RETURN v_ctrl;
-  END func_dp_stream_arr_get;
-  
-  FUNCTION func_dp_stream_arr_get(dp : t_dp_sosi_arr; str : STRING) RETURN STD_LOGIC_VECTOR IS
-    VARIABLE v_ctrl : STD_LOGIC_VECTOR(dp'RANGE);
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF    str="VALID" THEN v_ctrl(I) := dp(I).valid;
-      ELSIF str="SOP"   THEN v_ctrl(I) := dp(I).sop;
-      ELSIF str="EOP"   THEN v_ctrl(I) := dp(I).eop;
-      ELSIF str="SYNC"  THEN v_ctrl(I) := dp(I).sync;
-      ELSE  REPORT "Error in func_dp_stream_arr_get for t_dp_sosi_arr";
-      END IF;
-    END LOOP;
-    RETURN v_ctrl;
-  END func_dp_stream_arr_get;
-  
-  
-  -- Functions to select elements from two siso or two sosi arrays (sel[] = '1' selects a, sel[] = '0' selects b)
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a, b : t_dp_siso) RETURN t_dp_siso_arr IS
-    VARIABLE v_dp : t_dp_siso_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a;
-      ELSE
-        v_dp(I) := b;
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-  
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_siso_arr; b : t_dp_siso) RETURN t_dp_siso_arr IS
-    VARIABLE v_dp : t_dp_siso_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a(I);
-      ELSE
-        v_dp(I) := b;
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-  
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_siso; b : t_dp_siso_arr) RETURN t_dp_siso_arr IS
-    VARIABLE v_dp : t_dp_siso_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a;
-      ELSE
-        v_dp(I) := b(I);
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-  
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a, b : t_dp_siso_arr) RETURN t_dp_siso_arr IS
-    VARIABLE v_dp : t_dp_siso_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a(I);
-      ELSE
-        v_dp(I) := b(I);
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-  
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a, b : t_dp_sosi) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a;
-      ELSE
-        v_dp(I) := b;
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-  
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_sosi_arr; b : t_dp_sosi) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a(I);
-      ELSE
-        v_dp(I) := b;
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-  
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a : t_dp_sosi; b : t_dp_sosi_arr) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a;
-      ELSE
-        v_dp(I) := b(I);
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-  
-  FUNCTION func_dp_stream_arr_select(sel : STD_LOGIC_VECTOR; a, b : t_dp_sosi_arr) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(sel'RANGE);
-  BEGIN
-    FOR I IN sel'RANGE LOOP
-      IF sel(I)='1' THEN
-        v_dp(I) := a(I);
-      ELSE
-        v_dp(I) := b(I);
-      END IF;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_select;
-
-  FUNCTION func_dp_stream_arr_reverse_range(in_arr : t_dp_siso_arr) RETURN t_dp_siso_arr IS
-    VARIABLE v_to_range : t_dp_siso_arr(0 TO in_arr'HIGH);
-    VARIABLE v_downto_range : t_dp_siso_arr(in_arr'HIGH DOWNTO 0);
-  BEGIN
-    FOR i IN in_arr'RANGE LOOP
-      v_to_range(i)     := in_arr(in_arr'HIGH-i);
-      v_downto_range(i) := in_arr(in_arr'HIGH-i);
-    END LOOP;
-    IF in_arr'LEFT>in_arr'RIGHT THEN
-      RETURN v_downto_range;
-    ELSIF in_arr'LEFT<in_arr'RIGHT THEN
-      RETURN v_to_range;
-    ELSE
-      RETURN in_arr;
-    END IF;
-  END func_dp_stream_arr_reverse_range;
-
-  FUNCTION func_dp_stream_arr_reverse_range(in_arr : t_dp_sosi_arr) RETURN t_dp_sosi_arr IS
-    VARIABLE v_to_range : t_dp_sosi_arr(0 TO in_arr'HIGH);
-    VARIABLE v_downto_range : t_dp_sosi_arr(in_arr'HIGH DOWNTO 0);
-  BEGIN
-    FOR i IN in_arr'RANGE LOOP
-      v_to_range(i)     := in_arr(in_arr'HIGH-i);
-      v_downto_range(i) := in_arr(in_arr'HIGH-i);
-    END LOOP;
-    IF in_arr'LEFT>in_arr'RIGHT THEN
-      RETURN v_downto_range;
-    ELSIF in_arr'LEFT<in_arr'RIGHT THEN
-      RETURN v_to_range;
-    ELSE
-      RETURN in_arr;
-    END IF;
-  END func_dp_stream_arr_reverse_range;
-  
-  -- Functions to combinatorially hold the data fields and to set or reset the info and control fields in an sosi array
-  FUNCTION func_dp_stream_arr_combine_data_info_ctrl(dp : t_dp_sosi_arr; info, ctrl : t_dp_sosi) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(dp'RANGE) := dp;       -- hold sosi data
-  BEGIN
-    v_dp := func_dp_stream_arr_set_info(   v_dp, info);  -- set sosi info
-    v_dp := func_dp_stream_arr_set_control(v_dp, ctrl);  -- set sosi ctrl
-    RETURN v_dp;
-  END func_dp_stream_arr_combine_data_info_ctrl;
-    
-  FUNCTION func_dp_stream_arr_set_info(dp : t_dp_sosi_arr; info : t_dp_sosi) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(dp'RANGE) := dp;  -- hold sosi data
-  BEGIN
-    FOR I IN dp'RANGE LOOP                          -- set sosi info
-      v_dp(I).bsn     := info.bsn;      -- sop
-      v_dp(I).channel := info.channel;  -- sop
-      v_dp(I).empty   := info.empty;    -- eop
-      v_dp(I).err     := info.err;      -- eop
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_set_info;
-  
-  FUNCTION func_dp_stream_arr_set_control(dp : t_dp_sosi_arr; ctrl : t_dp_sosi) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(dp'RANGE) := dp;  -- hold sosi data
-  BEGIN
-    FOR I IN dp'RANGE LOOP                          -- set sosi control
-      v_dp(I).valid := ctrl.valid;
-      v_dp(I).sop   := ctrl.sop;
-      v_dp(I).eop   := ctrl.eop;
-      v_dp(I).sync  := ctrl.sync;
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_set_control;
-  
-  FUNCTION func_dp_stream_arr_reset_control(dp : t_dp_sosi_arr) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(dp'RANGE) := dp;  -- hold sosi data
-  BEGIN
-    FOR I IN dp'RANGE LOOP                          -- reset sosi control
-      v_dp(I).valid := '0';
-      v_dp(I).sop   := '0';
-      v_dp(I).eop   := '0';
-      v_dp(I).sync  := '0';
-    END LOOP;
-    RETURN v_dp;
-  END func_dp_stream_arr_reset_control;
-  
-  FUNCTION func_dp_stream_reset_control(dp : t_dp_sosi) RETURN t_dp_sosi IS
-    VARIABLE v_dp : t_dp_sosi := dp;  -- hold sosi data
-  BEGIN
-    -- reset sosi control
-    v_dp.valid := '0';
-    v_dp.sop   := '0';
-    v_dp.eop   := '0';
-    v_dp.sync  := '0';
-    RETURN v_dp;
-  END func_dp_stream_reset_control;
-  
-  -- Functions to combinatorially determine the maximum and minimum sosi bsn[w-1:0] value in the sosi array (for all elements or only for the mask[]='1' elements)
-  FUNCTION func_dp_stream_arr_bsn_max(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-    VARIABLE v_bsn : STD_LOGIC_VECTOR(w-1 DOWNTO 0) := (OTHERS=>'0');  -- init max v_bsn with minimum value
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='1' THEN
-        IF UNSIGNED(v_bsn) < UNSIGNED(dp(I).bsn(w-1 DOWNTO 0)) THEN
-          v_bsn := dp(I).bsn(w-1 DOWNTO 0);
-        END IF;
-      END IF;
-    END LOOP;
-    RETURN v_bsn;
-  END func_dp_stream_arr_bsn_max;
-  
-  FUNCTION func_dp_stream_arr_bsn_max(dp : t_dp_sosi_arr; w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-    CONSTANT c_mask : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');
-  BEGIN
-    RETURN func_dp_stream_arr_bsn_max(dp, c_mask, w);
-  END func_dp_stream_arr_bsn_max;
-  
-  FUNCTION func_dp_stream_arr_bsn_min(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR; w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-    VARIABLE v_bsn : STD_LOGIC_VECTOR(w-1 DOWNTO 0) := (OTHERS=>'1');  -- init min v_bsn with maximum value
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='1' THEN
-        IF UNSIGNED(v_bsn) > UNSIGNED(dp(I).bsn(w-1 DOWNTO 0)) THEN
-          v_bsn := dp(I).bsn(w-1 DOWNTO 0);
-        END IF;
-      END IF;
-    END LOOP;
-    RETURN v_bsn;
-  END func_dp_stream_arr_bsn_min;
-  
-  FUNCTION func_dp_stream_arr_bsn_min(dp : t_dp_sosi_arr; w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-    CONSTANT c_mask : STD_LOGIC_VECTOR(dp'RANGE) := (OTHERS=>'1');
-  BEGIN
-    RETURN func_dp_stream_arr_bsn_min(dp, c_mask, w);
-  END func_dp_stream_arr_bsn_min;
-
-  -- Function to copy the BSN number of one valid stream to all other streams. 
-  FUNCTION func_dp_stream_arr_copy_valid_bsn(dp : t_dp_sosi_arr; mask : STD_LOGIC_VECTOR) RETURN t_dp_sosi_arr IS
-    VARIABLE v_bsn : STD_LOGIC_VECTOR(c_dp_stream_bsn_w-1 DOWNTO 0) := (OTHERS=>'0');
-    VARIABLE v_dp  : t_dp_sosi_arr(dp'RANGE) := dp;  -- hold sosi data
-  BEGIN
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='1' THEN
-        v_bsn := dp(I).bsn;
-      END IF;
-    END LOOP;
-    FOR I IN dp'RANGE LOOP
-      v_dp(I).bsn := v_bsn;
-    END LOOP;  
-    RETURN v_dp;
-  END func_dp_stream_arr_copy_valid_bsn;
- 
-  
-  -- Functions to combinatorially handle channels
-  FUNCTION func_dp_stream_channel_set(st_sosi : t_dp_sosi; ch : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE v_rec : t_dp_sosi := st_sosi;
-  BEGIN
-    v_rec.channel := TO_UVEC(ch, c_dp_stream_channel_w);
-    RETURN v_rec;
-  END func_dp_stream_channel_set;
-  
-  FUNCTION func_dp_stream_channel_select(st_sosi : t_dp_sosi; ch : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE v_rec : t_dp_sosi := st_sosi;
-  BEGIN
-    IF UNSIGNED(st_sosi.channel)/=ch THEN
-      v_rec.valid := '0';
-      v_rec.sop   := '0';
-      v_rec.eop   := '0';
-    END IF;
-    RETURN v_rec;
-  END func_dp_stream_channel_select;
-  
-  FUNCTION func_dp_stream_channel_remove(st_sosi : t_dp_sosi; ch : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE v_rec : t_dp_sosi := st_sosi;
-  BEGIN
-    IF UNSIGNED(st_sosi.channel)=ch THEN
-      v_rec.valid := '0';
-      v_rec.sop   := '0';
-      v_rec.eop   := '0';
-    END IF;
-    RETURN v_rec;
-  END func_dp_stream_channel_remove;
-  
-  
-  FUNCTION func_dp_stream_error_set(st_sosi : t_dp_sosi; n : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE v_rec : t_dp_sosi := st_sosi;
-  BEGIN
-    v_rec.err := TO_UVEC(n, c_dp_stream_error_w);
-    RETURN v_rec;
-  END func_dp_stream_error_set;
-  
-  
-  FUNCTION func_dp_stream_bsn_set(st_sosi : t_dp_sosi; bsn : STD_LOGIC_VECTOR) RETURN t_dp_sosi IS
-    VARIABLE v_rec : t_dp_sosi := st_sosi;
-  BEGIN
-    v_rec.bsn := RESIZE_DP_BSN(bsn);
-    RETURN v_rec;
-  END func_dp_stream_bsn_set;
-  
-    
-  FUNCTION func_dp_stream_combine_info_and_data(info, data : t_dp_sosi) RETURN t_dp_sosi IS
-    VARIABLE v_rec : t_dp_sosi := data;  -- Sosi data fields
-  BEGIN
-    -- Combine sosi data with the sosi info fields
-    v_rec.sync    := info.sync AND data.sop;  -- force sync only active at data.sop
-    v_rec.bsn     := info.bsn;
-    v_rec.channel := info.channel;
-    v_rec.empty   := info.empty;
-    v_rec.err     := info.err;
-    RETURN v_rec;
-  END func_dp_stream_combine_info_and_data;
-  
-  
-  FUNCTION func_dp_stream_slv_to_integer(slv_sosi : t_dp_sosi; w : NATURAL) RETURN t_dp_sosi_integer IS
-    VARIABLE v_rec : t_dp_sosi_integer;
-  BEGIN
-    v_rec.sync     := slv_sosi.sync;
-    v_rec.bsn      := TO_UINT(slv_sosi.bsn(30 DOWNTO 0));         -- NATURAL'width = 31 bit
-    v_rec.data     := TO_SINT(slv_sosi.data(w-1 DOWNTO 0));
-    v_rec.re       := TO_SINT(slv_sosi.re(w-1 DOWNTO 0));
-    v_rec.im       := TO_SINT(slv_sosi.im(w-1 DOWNTO 0));
-    v_rec.valid    := slv_sosi.valid;
-    v_rec.sop      := slv_sosi.sop;
-    v_rec.eop      := slv_sosi.eop;
-    v_rec.empty    := TO_UINT(slv_sosi.empty);
-    v_rec.channel  := TO_UINT(slv_sosi.channel);
-    v_rec.err      := TO_UINT(slv_sosi.err);
-    RETURN v_rec;
-  END func_dp_stream_slv_to_integer;
-
-  FUNCTION func_dp_stream_set_data(dp : t_dp_sosi; slv : STD_LOGIC_VECTOR; str : STRING) RETURN t_dp_sosi IS
-    VARIABLE v_dp : t_dp_sosi := dp;   
-  BEGIN 
-      IF    str="DATA" THEN v_dp.data := RESIZE_DP_DATA(slv);
-      ELSIF str="DSP"  THEN v_dp.re   := RESIZE_DP_DSP_DATA(slv);
-                            v_dp.im   := RESIZE_DP_DSP_DATA(slv);
-      ELSIF str="RE"  THEN  v_dp.re   := RESIZE_DP_DSP_DATA(slv);
-      ELSIF str="IM"  THEN  v_dp.im   := RESIZE_DP_DSP_DATA(slv);
-      ELSIF str="ALL" THEN  v_dp.data := RESIZE_DP_DATA(slv);    
-                            v_dp.re   := RESIZE_DP_DSP_DATA(slv);
-                            v_dp.im   := RESIZE_DP_DSP_DATA(slv);
-      ELSE  REPORT "Error in func_dp_stream_set_data for t_dp_sosi";
-      END IF;
-    RETURN v_dp;
-  END;
-
-  FUNCTION func_dp_stream_set_data(dp : t_dp_sosi_arr; slv : STD_LOGIC_VECTOR; str : STRING) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(dp'RANGE) := dp;   
-  BEGIN 
-    FOR I IN dp'RANGE LOOP
-      v_dp(I) := func_dp_stream_set_data(dp(I), slv, str);
-    END LOOP;
-    RETURN v_dp;
-  END;
-
-  FUNCTION func_dp_stream_set_data(dp : t_dp_sosi_arr; slv : STD_LOGIC_VECTOR; str : STRING; mask : STD_LOGIC_VECTOR) RETURN t_dp_sosi_arr IS
-    VARIABLE v_dp : t_dp_sosi_arr(dp'RANGE) := dp;   
-  BEGIN 
-    FOR I IN dp'RANGE LOOP
-      IF mask(I)='0' THEN
-        v_dp(I) := func_dp_stream_set_data(dp(I), slv, str);
-      END IF; 
-    END LOOP;
-    RETURN v_dp;
-  END;
-
-  -- Concatenate the data (and complex fields) from a SOSI array into a single SOSI stream (assumes streams are in sync)
-  FUNCTION func_dp_stream_concat(snk_in_arr : t_dp_sosi_arr; data_w : NATURAL) RETURN t_dp_sosi IS
-    VARIABLE v_src_out      : t_dp_sosi := snk_in_arr(0);
-    VARIABLE v_compl_data_w : NATURAL   := data_w/2;
-  BEGIN
-    FOR i IN snk_in_arr'RANGE LOOP
-      v_src_out.data((i+1)*        data_w-1 DOWNTO i*        data_w) := snk_in_arr(i).data(      data_w-1 DOWNTO 0);
-      v_src_out.re(  (i+1)*v_compl_data_w-1 DOWNTO i*v_compl_data_w) := snk_in_arr(i).re(v_compl_data_w-1 DOWNTO 0);
-      v_src_out.im(  (i+1)*v_compl_data_w-1 DOWNTO i*v_compl_data_w) := snk_in_arr(i).im(v_compl_data_w-1 DOWNTO 0);
-    END LOOP;
-    RETURN v_src_out;
-  END;
-
-  FUNCTION func_dp_stream_concat(src_in : t_dp_siso; nof_streams : NATURAL) RETURN t_dp_siso_arr IS -- Wire single SISO to SISO_ARR
-    VARIABLE v_snk_out_arr : t_dp_siso_arr(nof_streams-1 DOWNTO 0);
-  BEGIN
-    FOR i IN v_snk_out_arr'RANGE LOOP
-      v_snk_out_arr(i) := src_in;
-    END LOOP;
-    RETURN v_snk_out_arr;
-  END;
-
-  -- Deconcatenate data from SOSI into SOSI array
-  FUNCTION func_dp_stream_deconcat(snk_in : t_dp_sosi; nof_streams, data_w : NATURAL) RETURN t_dp_sosi_arr IS
-    VARIABLE v_src_out_arr  : t_dp_sosi_arr(nof_streams-1 DOWNTO 0);
-    VARIABLE v_compl_data_w : NATURAL := data_w/2;
-  BEGIN
-    FOR i IN v_src_out_arr'RANGE LOOP
-      v_src_out_arr(i) := snk_in;
-      v_src_out_arr(i).data := (OTHERS=>'0');
-      v_src_out_arr(i).re   := (OTHERS=>'0');
-      v_src_out_arr(i).im   := (OTHERS=>'0');
-      v_src_out_arr(i).data(        data_w-1 DOWNTO 0) := snk_in.data((i+1)*        data_w-1 DOWNTO i*        data_w);
-      v_src_out_arr(i).re(  v_compl_data_w-1 DOWNTO 0) := snk_in.re  ((i+1)*v_compl_data_w-1 DOWNTO i*v_compl_data_w);
-      v_src_out_arr(i).im(  v_compl_data_w-1 DOWNTO 0) := snk_in.im  ((i+1)*v_compl_data_w-1 DOWNTO i*v_compl_data_w);
-    END LOOP;
-    RETURN v_src_out_arr;
-  END;
-
-  FUNCTION func_dp_stream_deconcat(src_out_arr : t_dp_siso_arr) RETURN t_dp_siso IS -- Wire SISO_ARR(0) to single SISO
-  BEGIN
-    RETURN src_out_arr(0);
-  END;
-
-END dp_stream_pkg;
-
diff --git a/cores/base/dp/dp_pkg/dp_stream_stimuli.vhd b/cores/base/dp/dp_pkg/dp_stream_stimuli.vhd
deleted file mode 100644
index 3510fa0e2b0725c92c1c463e84a5b18032006af7..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pkg/dp_stream_stimuli.vhd
+++ /dev/null
@@ -1,185 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2015
--- 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 dp_stream_stimuli generates as stream of packets with counter data.
--- Description:
---
--- Remark:
--- . The stimuli empty = 0 because the data in proc_dp_gen_block_data() is
---   generated with one symbol per data (because symbol_w = data_w).
---
--- Usage:
--- . See tb_dp_example_no_dut for usage example
---
-
-LIBRARY IEEE, common_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE common_pkg_lib.common_lfsr_sequences_pkg.ALL;
-USE common_pkg_lib.tb_common_pkg.ALL;
-USE work.dp_stream_pkg.ALL;
-USE work.tb_dp_pkg.ALL;
-
-
-ENTITY dp_stream_stimuli IS
-  GENERIC (
-    g_instance_nr    : NATURAL := 0;
-    -- flow control
-    g_random_w       : NATURAL := 15;                       -- use different random width for stimuli and for verify to have different random sequences
-    g_pulse_active   : NATURAL := 1;
-    g_pulse_period   : NATURAL := 2;
-    g_flow_control   : t_dp_flow_control_enum := e_active;  -- always active, random or pulse flow control
-    -- initializations
-    g_sync_period    : NATURAL := 10;
-    g_sync_offset    : NATURAL := 0;
-    g_data_init      : NATURAL := 0;    -- choose some easy to recognize and unique value, data will increment at every valid
-    g_bsn_init       : STD_LOGIC_VECTOR(c_dp_stream_bsn_w-1 DOWNTO 0) := TO_DP_BSN(0);  -- X"0877665544332211", bsn will increment at every sop
-    g_err_init       : NATURAL := 247;  -- choose some easy to recognize and unique value
-    g_err_incr       : NATURAL := 1;    -- when 0 keep fixed at init value, when 1 increment at every sop
-    g_channel_init   : NATURAL := 5;    -- choose some easy to recognize and unique value
-    g_channel_incr   : NATURAL := 1;    -- when 0 keep fixed at init value, when 1 increment at every sop
-    -- specific
-    g_in_dat_w       : NATURAL := 32;
-    g_nof_repeat     : NATURAL := 5;
-    g_pkt_len        : NATURAL := 16;
-    g_pkt_gap        : NATURAL := 4
-  );
-  PORT (
-    rst               : IN  STD_LOGIC;
-    clk               : IN  STD_LOGIC;
-  
-    -- Generate stimuli
-    src_in            : IN  t_dp_siso := c_dp_siso_rdy;
-    src_out           : OUT t_dp_sosi;
-
-    -- End of stimuli
-    last_snk_in       : OUT t_dp_sosi;   -- expected verify_snk_in after end of stimuli 
-    last_snk_in_evt   : OUT STD_LOGIC;   -- trigger verify to verify the last_snk_in 
-    tb_end            : OUT STD_LOGIC    -- signal end of tb as far as this dp_stream_stimuli is concerned
-  );
-END dp_stream_stimuli;
-
-
-ARCHITECTURE str OF dp_stream_stimuli IS
-  
-  SIGNAL random          : STD_LOGIC_VECTOR(g_random_w-1 DOWNTO 0) := TO_UVEC(g_instance_nr, g_random_w);  -- use different initialization to have different random sequences per stream
-  SIGNAL pulse           : STD_LOGIC;
-  SIGNAL pulse_en        : STD_LOGIC := '1';
-  
-  SIGNAL stimuli_en      : STD_LOGIC := '1';
-  SIGNAL src_out_data    : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-  SIGNAL i_src_out       : t_dp_sosi;
-  
-BEGIN
-
-  src_out <= i_src_out;
-  
-  ------------------------------------------------------------------------------
-  -- STREAM CONTROL
-  ------------------------------------------------------------------------------
-  
-  random <= func_common_random(random) WHEN rising_edge(clk);
-  
-  proc_common_gen_duty_pulse(g_pulse_active, g_pulse_period, '1', rst, clk, pulse_en, pulse);
-
-  stimuli_en <= '1'                 WHEN g_flow_control=e_active ELSE
-                random(random'HIGH) WHEN g_flow_control=e_random ELSE
-                pulse               WHEN g_flow_control=e_pulse;
-                       
-  ------------------------------------------------------------------------------
-  -- DATA GENERATION
-  ------------------------------------------------------------------------------
-  
-  -- Generate data path input data
-  p_stimuli_st : PROCESS
-    VARIABLE v_sosi : t_dp_sosi := c_dp_sosi_rst;
-    VARIABLE v_last : t_dp_sosi := c_dp_sosi_rst;
-  BEGIN
-    -- Initialisations
-    last_snk_in <= c_dp_sosi_rst;
-    last_snk_in_evt <= '0';
-    tb_end <= '0';
-    
-    -- Adjust initial sosi field values by -1 to compensate for auto increment
-    v_sosi.bsn     := INCR_UVEC(g_bsn_init,                    -1);
-    v_sosi.channel := INCR_UVEC(TO_DP_CHANNEL(g_channel_init), -g_channel_incr);
-    v_sosi.data    := INCR_UVEC(TO_DP_DATA(g_data_init),       -g_pkt_len);
-    v_sosi.err     := INCR_UVEC(TO_DP_ERROR(g_err_init),       -g_err_incr);
-    
-    i_src_out <= c_dp_sosi_rst;
-    proc_common_wait_until_low(clk, rst);
-    proc_common_wait_some_cycles(clk, 5);
-
-    -- Generate g_nof_repeat packets
-    FOR I IN 0 TO g_nof_repeat-1 LOOP
-      -- Auto increment v_sosi field values for this packet
-      v_sosi.bsn     := INCR_UVEC(v_sosi.bsn, 1);
-      v_sosi.sync    := sel_a_b((UNSIGNED(v_sosi.bsn) MOD g_sync_period) = g_sync_offset, '1', '0');  -- insert sync starting at BSN=g_sync_offset and with period g_sync_period
-      v_sosi.channel := INCR_UVEC(v_sosi.channel, g_channel_incr);
-      v_sosi.data    := INCR_UVEC(v_sosi.data, g_pkt_len);
-      v_sosi.data    := RESIZE_DP_DATA(v_sosi.data(g_in_dat_w-1 DOWNTO 0));  -- wrap when >= 2**g_in_dat_w
-      v_sosi.err     := INCR_UVEC(v_sosi.err, g_err_incr);
-      
-      -- Send packet
-      proc_dp_gen_block_data(g_in_dat_w, TO_UINT(v_sosi.data), g_pkt_len, TO_UINT(v_sosi.channel), TO_UINT(v_sosi.err), v_sosi.sync, v_sosi.bsn, clk, stimuli_en, src_in, i_src_out);
-      
-      -- Insert optional gap between the packets
-      proc_common_wait_some_cycles(clk, g_pkt_gap);
-      
-      -- Update v_last.sync
-      IF v_sosi.sync='1' THEN v_last.sync := '1'; END IF;
-    END LOOP;
-
-    -- Update v_last control
-    IF g_nof_repeat>0 THEN
-      v_last.sop := '1';
-      v_last.eop := '1';
-      v_last.valid := '1';
-    END IF;
-    
-    -- Determine and keep last expected sosi field values after end of stimuli
-    -- . e_qual
-    v_last.bsn     := STD_LOGIC_VECTOR( UNSIGNED(g_bsn_init) + g_nof_repeat-1);
-    v_last.channel := TO_DP_CHANNEL(g_channel_init           + (g_nof_repeat-1)*g_channel_incr);
-    v_last.err     := TO_DP_ERROR(g_err_init                 + (g_nof_repeat-1)*g_err_incr);
-    -- . account for g_pkt_len
-    v_last.data    := INCR_UVEC(v_sosi.data, g_pkt_len-1);
-    v_last.data    := RESIZE_DP_DATA(v_last.data(g_in_dat_w-1 DOWNTO 0));  -- wrap when >= 2**g_in_dat_w
-    last_snk_in <= v_last;
-    
-    -- Signal end of stimuli
-    proc_common_wait_some_cycles(clk, 100);  -- latency from stimuli to verify depends on the flow control, so wait sufficiently long for last packet to have passed through
-    proc_common_gen_pulse(clk, last_snk_in_evt);
-    proc_common_wait_some_cycles(clk, 50);
-    tb_end <= '1';
-    WAIT;
-  END PROCESS;
-    
-  ------------------------------------------------------------------------------
-  -- Auxiliary
-  ------------------------------------------------------------------------------
-  
-  -- Map to slv to ease monitoring in wave window
-  src_out_data <= i_src_out.data(g_in_dat_w-1 DOWNTO 0);
-  
-END str;
diff --git a/cores/base/dp/dp_pkg/dp_stream_verify.vhd b/cores/base/dp/dp_pkg/dp_stream_verify.vhd
deleted file mode 100644
index db4c7cb561f312409e6450a00ecab0b2386f08df..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pkg/dp_stream_verify.vhd
+++ /dev/null
@@ -1,200 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2015
--- 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 dp_stream_verify verifies the stream of packets with counter data that
---   are generated by dp_stimuli_st.
--- Description:
---   The component can verify a stream:
---   . The sosi control fields are verified conform the bus specifications
---     eg. considering the RL, no missing eop, etc.
---   . The sosi data fields are verified based on their previous value under
---     the assumption that they contain incrementing data. Whether a field
---     is checked depends on verify_snk_in_enable.
---  
---   The component also checks whether the stream is active at all. A
---   pulse in verify_expected_snk_in_evt triggers the verification of the
---   corresponding field in snk_in using the expected_snk_in as reference.
---
--- Usage:
--- . See tb_dp_example_no_dut for usage example
---
-
-LIBRARY IEEE, common_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE common_pkg_lib.common_lfsr_sequences_pkg.ALL;
-USE common_pkg_lib.tb_common_pkg.ALL;
-USE work.dp_stream_pkg.ALL;
-USE work.tb_dp_pkg.ALL;
-
-
-ENTITY dp_stream_verify IS
-  GENERIC (
-    g_instance_nr         : NATURAL := 0;
-    -- flow control
-    g_random_w            : NATURAL := 14;                       -- use different random width for stimuli and for verify to have different random sequences
-    g_pulse_active        : NATURAL := 1;
-    g_pulse_period        : NATURAL := 2;
-    g_flow_control        : t_dp_flow_control_enum := e_active;  -- always active, random or pulse flow control
-    -- initializations
-    g_sync_period         : NATURAL := 10;
-    g_sync_offset         : NATURAL := 7;
-    g_snk_in_cnt_max      : t_dp_sosi_unsigned := c_dp_sosi_unsigned_rst;  -- default 0 is no wrap
-    g_snk_in_cnt_gap      : t_dp_sosi_unsigned := c_dp_sosi_unsigned_ones; -- default only accept increment +1
-    -- specific
-    g_in_dat_w            : NATURAL := 32;
-    g_pkt_len             : NATURAL := 16
-  );
-  PORT (
-    rst                        : IN  STD_LOGIC;
-    clk                        : IN  STD_LOGIC;
-  
-    -- Verify data
-    snk_out                    : OUT t_dp_siso;
-    snk_in                     : IN  t_dp_sosi;
-
-    -- During stimuli
-    verify_snk_in_enable       : IN  t_dp_sosi_sl;  -- enable to verify that the snk_in fields are incrementing 
-    
-    -- End of stimuli
-    expected_snk_in            : IN  t_dp_sosi;          -- expected snk_in at verify_expected_snk_in_evt
-    verify_expected_snk_in_evt : IN  t_dp_sosi_sl   -- trigger to verify the expected_snk_in 
-  );
-END dp_stream_verify;
-
-
-ARCHITECTURE tb OF dp_stream_verify IS
-
-  CONSTANT c_rl                       : NATURAL := 1;
-  CONSTANT c_no_dut                   : BOOLEAN:= TRUE;
-  
-  SIGNAL random                     : STD_LOGIC_VECTOR(g_random_w-1 DOWNTO 0) := TO_UVEC(g_instance_nr, g_random_w);  -- use different initialization to have different random sequences per stream
-  SIGNAL pulse                      : STD_LOGIC;
-  SIGNAL pulse_en                   : STD_LOGIC := '1';
-  
-  SIGNAL i_snk_out                  : t_dp_siso := c_dp_siso_rdy;
-  SIGNAL prev_snk_out               : t_dp_siso;
-  SIGNAL hold_snk_in_data           : STD_LOGIC_VECTOR(c_dp_stream_data_w-1 DOWNTO 0);  -- used to hold valid data for verify at verify_expected_snk_in_evt
-  SIGNAL snk_in_data                : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-  SIGNAL prev_snk_in                : t_dp_sosi;
-  
-  SIGNAL hold_snk_in_sop            : STD_LOGIC := '0';
-  SIGNAL detected_snk_in_ctrl       : t_dp_sosi_sl := c_dp_sosi_sl_rst;
-  SIGNAL verify_snk_in_increment    : t_dp_sosi_sl := c_dp_sosi_sl_rst;
-  SIGNAL verify_snk_in_ctrl         : t_dp_sosi_sl := c_dp_sosi_sl_rst;
-
-  SIGNAL exp_size                   : NATURAL;
-  SIGNAL cnt_size                   : NATURAL;
-  
-BEGIN
-
-  snk_out <= i_snk_out;
-
-  ------------------------------------------------------------------------------
-  -- STREAM CONTROL
-  ------------------------------------------------------------------------------
-  
-  random <= func_common_random(random) WHEN rising_edge(clk);
-  
-  proc_common_gen_duty_pulse(g_pulse_active, g_pulse_period, '1', rst, clk, pulse_en, pulse);
-
-  i_snk_out.ready <= '1'                 WHEN g_flow_control=e_active  ELSE
-                     random(random'HIGH) WHEN g_flow_control=e_random  ELSE
-                     pulse               WHEN g_flow_control=e_pulse;
-  
-  ------------------------------------------------------------------------------
-  -- DATA VERIFICATION
-  ------------------------------------------------------------------------------  
-  
-  -- Detect first sync, sop, eop, valid
-  detected_snk_in_ctrl.sync  <= '1' WHEN snk_in.sync='1'  AND rising_edge(clk);
-  detected_snk_in_ctrl.valid <= '1' WHEN snk_in.valid='1' AND rising_edge(clk);
-  detected_snk_in_ctrl.sop   <= '1' WHEN snk_in.sop='1'   AND rising_edge(clk);
-  detected_snk_in_ctrl.eop   <= '1' WHEN snk_in.eop='1'   AND rising_edge(clk);
-  
-  -- Verify that the stimuli have been applied at all so at least one active sosi sync, sop, eop, valid field has been detected
-  proc_dp_verify_value("snk_in.sync",             clk, verify_expected_snk_in_evt.sync,    expected_snk_in.sync,    detected_snk_in_ctrl.sync);
-  proc_dp_verify_value("snk_in.sop",              clk, verify_expected_snk_in_evt.sop,     expected_snk_in.sop,     detected_snk_in_ctrl.sop);
-  proc_dp_verify_value("snk_in.eop",              clk, verify_expected_snk_in_evt.eop,     expected_snk_in.eop,     detected_snk_in_ctrl.eop);
-  proc_dp_verify_value("snk_in.valid",            clk, verify_expected_snk_in_evt.valid,   expected_snk_in.valid,   detected_snk_in_ctrl.valid);
-  
-  -- Verify that the last sosi data, bsn, channel and err fields are correct
-  proc_dp_verify_value("snk_in.data",    e_equal, clk, verify_expected_snk_in_evt.data,    expected_snk_in.data,    hold_snk_in_data);
-  proc_dp_verify_value("snk_in.bsn",     e_equal, clk, verify_expected_snk_in_evt.bsn,     expected_snk_in.bsn,     snk_in.bsn);
-  proc_dp_verify_value("snk_in.channel", e_equal, clk, verify_expected_snk_in_evt.channel, expected_snk_in.channel, snk_in.channel);
-  proc_dp_verify_value("snk_in.err",     e_equal, clk, verify_expected_snk_in_evt.err,     expected_snk_in.err,     snk_in.err);
-  
-  -- Verify that the output is incrementing data, like the input stimuli
-  p_verify_snk_in_increment : PROCESS(verify_snk_in_enable, detected_snk_in_ctrl)
-  BEGIN
-    verify_snk_in_increment         <= verify_snk_in_enable;
-    verify_snk_in_increment.data    <= verify_snk_in_enable.data    AND detected_snk_in_ctrl.valid;
-    verify_snk_in_increment.re      <= verify_snk_in_enable.re      AND detected_snk_in_ctrl.valid;
-    verify_snk_in_increment.im      <= verify_snk_in_enable.im      AND detected_snk_in_ctrl.valid;
-    verify_snk_in_increment.bsn     <= verify_snk_in_enable.bsn     AND detected_snk_in_ctrl.sop;
-    verify_snk_in_increment.channel <= verify_snk_in_enable.channel AND detected_snk_in_ctrl.sop;
-    verify_snk_in_increment.empty   <= verify_snk_in_enable.empty   AND detected_snk_in_ctrl.eop;
-    verify_snk_in_increment.err     <= verify_snk_in_enable.err     AND detected_snk_in_ctrl.eop;
-  END PROCESS;
-  
-  proc_dp_verify_data("snk_in.data",    c_rl, g_snk_in_cnt_max.data,    g_snk_in_cnt_gap.data,    clk, verify_snk_in_increment.data,    i_snk_out.ready, snk_in.valid, snk_in.data,    prev_snk_in.data);
-  proc_dp_verify_data("snk_in.re",      c_rl, g_snk_in_cnt_max.re,      g_snk_in_cnt_gap.re,      clk, verify_snk_in_increment.re,      i_snk_out.ready, snk_in.valid, snk_in.re,      prev_snk_in.re);
-  proc_dp_verify_data("snk_in.im",      c_rl, g_snk_in_cnt_max.im,      g_snk_in_cnt_gap.im,      clk, verify_snk_in_increment.im,      i_snk_out.ready, snk_in.valid, snk_in.im,      prev_snk_in.im);
-  proc_dp_verify_data("snk_in.bsn",     c_rl, g_snk_in_cnt_max.bsn,     g_snk_in_cnt_gap.bsn,     clk, verify_snk_in_increment.bsn,     i_snk_out.ready, snk_in.sop,   snk_in.bsn,     prev_snk_in.bsn);
-  proc_dp_verify_data("snk_in.channel", c_rl, g_snk_in_cnt_max.channel, g_snk_in_cnt_gap.channel, clk, verify_snk_in_increment.channel, i_snk_out.ready, snk_in.sop,   snk_in.channel, prev_snk_in.channel);
-  proc_dp_verify_data("snk_in.empty",   c_rl, g_snk_in_cnt_max.empty,   g_snk_in_cnt_gap.empty,   clk, verify_snk_in_increment.empty,   i_snk_out.ready, snk_in.eop,   snk_in.empty,   prev_snk_in.empty);
-  proc_dp_verify_data("snk_in.err",     c_rl, g_snk_in_cnt_max.err,     g_snk_in_cnt_gap.err,     clk, verify_snk_in_increment.err,     i_snk_out.ready, snk_in.eop,   snk_in.err,     prev_snk_in.err);
-  
-  -- Verify that the snk_in control fields are correct
-  p_verify_snk_in_ctrl: PROCESS(snk_in, verify_snk_in_enable)
-  BEGIN
-    verify_snk_in_ctrl.sync  <= snk_in.sync  AND verify_snk_in_enable.valid AND verify_snk_in_enable.sync;
-    verify_snk_in_ctrl.sop   <= snk_in.sop   AND verify_snk_in_enable.valid AND verify_snk_in_enable.sop AND verify_snk_in_enable.eop;
-    verify_snk_in_ctrl.eop   <= snk_in.eop   AND verify_snk_in_enable.valid AND verify_snk_in_enable.sop AND verify_snk_in_enable.eop;
-    verify_snk_in_ctrl.valid <= snk_in.valid AND verify_snk_in_enable.valid;
-  END PROCESS;
-  
-  -- Verify that the output sync occurs when expected
-  proc_dp_verify_sync(g_sync_period, g_sync_offset, clk, detected_snk_in_ctrl.sop, verify_snk_in_ctrl.sync, verify_snk_in_ctrl.sop, snk_in.bsn);
-  
-  -- Verify output packet ctrl
-  proc_dp_verify_sop_and_eop(clk, verify_snk_in_ctrl.valid, verify_snk_in_ctrl.sop, verify_snk_in_ctrl.eop, hold_snk_in_sop);
-  
-  -- Verify output packet block size
-  exp_size <= g_pkt_len;
-  
-  proc_dp_verify_block_size(exp_size, clk, verify_snk_in_ctrl.valid, verify_snk_in_ctrl.sop, verify_snk_in_ctrl.eop, cnt_size);
-
-  -- Verify output ready latency
-  proc_dp_verify_valid(clk, detected_snk_in_ctrl.valid, i_snk_out.ready, prev_snk_out.ready, verify_snk_in_ctrl.valid);
-    
-  ------------------------------------------------------------------------------
-  -- Auxiliary
-  ------------------------------------------------------------------------------
-  
-  -- Map to slv to ease monitoring in wave window
-  snk_in_data  <= snk_in.data(g_in_dat_w-1 DOWNTO 0);
-  
-  hold_snk_in_data <= snk_in.data WHEN snk_in.valid='1';
-  
-END tb;
diff --git a/cores/base/dp/dp_pkg/hdllib.cfg b/cores/base/dp/dp_pkg/hdllib.cfg
deleted file mode 100644
index 12f4b46bfa651daddb71f635882831a7909c2eac..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pkg/hdllib.cfg
+++ /dev/null
@@ -1,20 +0,0 @@
-hdl_lib_name = dp_pkg
-hdl_library_clause_name = dp_pkg_lib
-hdl_lib_uses_synth = common_pkg
-hdl_lib_uses_sim = 
-hdl_lib_technology = 
-
-synth_files =
-    dp_stream_pkg.vhd
-    tb_dp_pkg.vhd
-    dp_stream_stimuli.vhd
-    dp_stream_verify.vhd
-    
-test_bench_files = 
-
-regression_test_vhdl = 
-    
-[modelsim_project_file]
-
-
-[quartus_project_file]
diff --git a/cores/base/dp/dp_pkg/tb_dp_pkg.vhd b/cores/base/dp/dp_pkg/tb_dp_pkg.vhd
deleted file mode 100644
index 2dadc92566dc25b3b8ff42bc671d99a047a16f77..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_pkg/tb_dp_pkg.vhd
+++ /dev/null
@@ -1,2413 +0,0 @@
--------------------------------------------------------------------------------
---
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE common_pkg_lib.common_lfsr_sequences_pkg.ALL;
-USE common_pkg_lib.tb_common_pkg.ALL;
-USE work.dp_stream_pkg.ALL;
-
-
-PACKAGE tb_dp_pkg IS
-
-  ------------------------------------------------------------------------------
-  -- Purpose:
-  --
-  -- Test bench package for applying stimuli to a streaming data path. The
-  -- input is counter data, the output is verified and an error is reported
-  -- if a counter value is missing or duplicate.
-  --
-  -- Description:
-  --
-  -- The test is divided into intervals marked by sync to start a new subtest
-  -- named by state. New subtests can be added by adding an extra sync interval
-  -- and state name to this package. In each subtest the streaming interface
-  -- DUT can be verified for different situations by manipulating:
-  -- . cnt_en    : cnt_en not always active when in_ready is asserted
-  -- . out_ready : out_ready not always active
-  --
-  -- Remarks:
-  -- . See e.g. tb_dp_pipeline.vhd for how to use the procedures.
-  -- . To run all stimuli in Modelsim do:
-  --   > as 10
-  --   > run 400 us
-  ------------------------------------------------------------------------------
-
-  CONSTANT clk_period         : TIME := 10 ns;  -- 100 MHz
-  CONSTANT c_dp_sync_interval : NATURAL := 3000;
-  CONSTANT c_dp_test_interval : NATURAL := 100;
-  CONSTANT c_dp_nof_toggle    : NATURAL := 40;
-  CONSTANT c_dp_nof_both      : NATURAL := 50;
-
-  -- The test bench uses other field widths than the standard t_dp_sosi record field widths, the assumptions are:
-  -- . c_dp_data_w < c_dp_stream_data_w
-  -- . c_dp_data_w > c_dp_stream_empty_w
-  -- . c_dp_data_w > c_dp_stream_channel_w
-  -- . c_dp_data_w > c_dp_stream_error_w
-  CONSTANT c_dp_data_w            : NATURAL := c_word_w;  -- =32, choose wide enough to avoid out_data wrap around issue for p_verify
-  CONSTANT c_dp_bsn_w             : NATURAL := c_dp_data_w;  -- c_dp_stream_bsn_w;
-  CONSTANT c_dp_empty_w           : NATURAL := c_dp_stream_empty_w;
-  CONSTANT c_dp_channel_w         : NATURAL := c_dp_stream_channel_w;
-  CONSTANT c_dp_channel_user_w    : NATURAL := c_dp_stream_channel_w/2;     -- support some bits for mux input user streams channel widths
-  CONSTANT c_dp_channel_mux_w     : NATURAL :=(c_dp_stream_channel_w+1)/2;  -- support rest bits for the nof input ports of a mux
-  CONSTANT c_dp_error_w           : NATURAL := c_dp_stream_error_w;
-
-  TYPE t_dp_data_arr IS ARRAY (NATURAL RANGE <>) OF STD_LOGIC_VECTOR(c_dp_data_w-1 DOWNTO 0);
-  
-  -- The state name tells what kind of test is done in the sync interval
-  TYPE t_dp_state_enum IS (
-    s_idle,
-    s_both_active,
-    s_pull_down_out_ready,
-    s_pull_down_cnt_en,
-    s_toggle_out_ready,
-    s_toggle_cnt_en,
-    s_toggle_both,
-    s_pulse_cnt_en,
-    s_chirp_out_ready,
-    s_random,
-    s_done
-  );
-
-  TYPE t_dp_value_enum IS (
-    e_equal,
-    e_at_least
-  );
-  
-  -- always active, random or pulse flow control
-  TYPE t_dp_flow_control_enum IS (
-    e_active,
-    e_random,
-    e_pulse    
-  );
-  
-  TYPE t_dp_flow_control_enum_arr IS ARRAY (NATURAL RANGE <>) OF t_dp_flow_control_enum;
-  
-  CONSTANT c_dp_flow_control_enum_arr : t_dp_flow_control_enum_arr := (e_active, e_random, e_pulse);  -- array all possible values that can be iterated over
-  
-  ------------------------------------------------------------------------------
-  -- Stream source functions
-  ------------------------------------------------------------------------------
-  
-  -- Block data generator with feedforward throttle control
-  -- !!! old style: sync before sop
-  -- !!! used by tb_dp_packetizing, do not use for new DP components
-  PROCEDURE proc_dp_gen_block_data(CONSTANT c_nof_block_per_sync : IN    NATURAL;
-                                   CONSTANT c_block_size         : IN    NATURAL;
-                                   CONSTANT c_gap_size           : IN    NATURAL;
-                                   CONSTANT c_throttle_num       : IN    NATURAL;
-                                   CONSTANT c_throttle_den       : IN    NATURAL;
-                                   SIGNAL   rst                  : IN    STD_LOGIC;
-                                   SIGNAL   clk                  : IN    STD_LOGIC;
-                                   SIGNAL   sync_nr              : INOUT NATURAL;
-                                   SIGNAL   block_nr             : INOUT NATURAL;
-                                   SIGNAL   cnt_sync             : OUT   STD_LOGIC;
-                                   SIGNAL   cnt_val              : OUT   STD_LOGIC;
-                                   SIGNAL   cnt_dat              : INOUT STD_LOGIC_VECTOR);
-                                   
-  -- Block data generator with ready flow control and symbols counter
-  PROCEDURE proc_dp_gen_block_data(CONSTANT c_ready_latency  : IN  NATURAL;    -- 0, 1 are supported by proc_dp_stream_ready_latency()
-                                   CONSTANT c_use_data       : IN  BOOLEAN;    -- when TRUE use data field, else use re, im fields, and keep unused fields at 'X'
-                                   CONSTANT c_data_w         : IN  NATURAL;    -- data width for the data, re and im fields
-                                   CONSTANT c_symbol_w       : IN  NATURAL;    -- c_data_w/c_symbol_w must be an integer
-                                   CONSTANT c_symbol_init    : IN  NATURAL;    -- init counter for symbols in data field
-                                   CONSTANT c_symbol_re_init : IN  NATURAL;    -- init counter for symbols in re field
-                                   CONSTANT c_symbol_im_init : IN  NATURAL;    -- init counter for symbols in im field
-                                   CONSTANT c_nof_symbols    : IN  NATURAL;    -- nof symbols per frame for the data, re and im fields
-                                   CONSTANT c_channel        : IN  NATURAL;    -- channel field
-                                   CONSTANT c_error          : IN  NATURAL;    -- error field
-                                   CONSTANT c_sync           : IN  STD_LOGIC;  -- when '1' issue sync pulse during this block
-                                   CONSTANT c_bsn            : IN  STD_LOGIC_VECTOR;  -- bsn field
-                                   SIGNAL   clk              : IN  STD_LOGIC;
-                                   SIGNAL   in_en            : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                                   SIGNAL   src_in           : IN  t_dp_siso;
-                                   SIGNAL   src_out          : OUT t_dp_sosi);
-                                   
-  PROCEDURE proc_dp_gen_block_data(CONSTANT c_data_w         : IN  NATURAL;    -- data width for the data field
-                                   CONSTANT c_symbol_init    : IN  NATURAL;    -- init counter for the data in the data field
-                                   CONSTANT c_nof_symbols    : IN  NATURAL;    -- nof symbols per frame for the data fields
-                                   CONSTANT c_channel        : IN  NATURAL;    -- channel field
-                                   CONSTANT c_error          : IN  NATURAL;    -- error field
-                                   CONSTANT c_sync           : IN  STD_LOGIC;  -- when '1' issue sync pulse during this block
-                                   CONSTANT c_bsn            : IN  STD_LOGIC_VECTOR;  -- bsn field
-                                   SIGNAL   clk              : IN  STD_LOGIC;
-                                   SIGNAL   in_en            : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                                   SIGNAL   src_in           : IN  t_dp_siso;
-                                   SIGNAL   src_out          : OUT t_dp_sosi);
-                                   
-  -- Handle stream ready signal, only support RL=0 or 1.
-  PROCEDURE proc_dp_stream_ready_latency(CONSTANT c_latency : IN  NATURAL;
-                                         SIGNAL   clk       : IN  STD_LOGIC;
-                                         SIGNAL   ready     : IN  STD_LOGIC;
-                                         SIGNAL   in_en     : IN  STD_LOGIC;  -- when '1' then active output when ready
-                                         CONSTANT c_sync    : IN  STD_LOGIC;
-                                         CONSTANT c_valid   : IN  STD_LOGIC;
-                                         CONSTANT c_sop     : IN  STD_LOGIC;
-                                         CONSTANT c_eop     : IN  STD_LOGIC;
-                                         SIGNAL   out_sync  : OUT STD_LOGIC;
-                                         SIGNAL   out_valid : OUT STD_LOGIC;
-                                         SIGNAL   out_sop   : OUT STD_LOGIC;
-                                         SIGNAL   out_eop   : OUT STD_LOGIC);
-                                         
-  -- Initialize the data per symbol
-  FUNCTION func_dp_data_init(c_data_w, c_symbol_w, init : NATURAL) RETURN STD_LOGIC_VECTOR;
-  
-  -- Increment the data per symbol
-  FUNCTION func_dp_data_incr(c_data_w, c_symbol_w : NATURAL; data : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;
-  
-  -- Generate a counter data with valid
-  PROCEDURE proc_dp_gen_data(CONSTANT c_ready_latency : IN  NATURAL;    -- 0, 1 are supported by proc_dp_stream_ready_latency()
-                             CONSTANT c_data_w        : IN  NATURAL;
-                             CONSTANT c_data_init     : IN  NATURAL;
-                             SIGNAL   rst             : IN  STD_LOGIC;
-                             SIGNAL   clk             : IN  STD_LOGIC;
-                             SIGNAL   in_en           : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                             SIGNAL   src_in          : IN  t_dp_siso;
-                             SIGNAL   src_out         : OUT t_dp_sosi);
-
-  -- As above but with counter max
-  PROCEDURE proc_dp_gen_data(CONSTANT c_ready_latency   : IN  NATURAL; 
-                             CONSTANT c_data_w          : IN  NATURAL;
-                             CONSTANT c_data_init       : IN  NATURAL;
-                             CONSTANT c_data_max        : IN  NATURAL; 
-                             SIGNAL   rst             : IN  STD_LOGIC;
-                             SIGNAL   clk             : IN  STD_LOGIC;
-                             SIGNAL   in_en           : IN  STD_LOGIC;
-                             SIGNAL   src_in          : IN  t_dp_siso;
-                             SIGNAL   src_out         : OUT t_dp_sosi);
-   
-  -- Generate a frame with symbols counter
-  PROCEDURE proc_dp_gen_frame(CONSTANT c_ready_latency : IN  NATURAL;    -- 0, 1 are supported by proc_dp_stream_ready_latency()
-                              CONSTANT c_data_w        : IN  NATURAL;
-                              CONSTANT c_symbol_w      : IN  NATURAL;    -- c_data_w/c_symbol_w must be an integer
-                              CONSTANT c_symbol_init   : IN  NATURAL;
-                              CONSTANT c_nof_symbols   : IN  NATURAL;
-                              CONSTANT c_bsn           : IN  NATURAL;
-                              CONSTANT c_sync          : IN  STD_LOGIC;
-                              SIGNAL   clk             : IN  STD_LOGIC;
-                              SIGNAL   in_en           : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                              SIGNAL   src_in          : IN  t_dp_siso;
-                              SIGNAL   src_out         : OUT t_dp_sosi);
-
-  -- Input data counter
-  PROCEDURE proc_dp_cnt_dat(SIGNAL rst     : IN    STD_LOGIC;
-                            SIGNAL clk     : IN    STD_LOGIC;
-                            SIGNAL in_en   : IN    STD_LOGIC;
-                            SIGNAL cnt_dat : INOUT STD_LOGIC_VECTOR);
-
-  PROCEDURE proc_dp_cnt_dat(SIGNAL rst     : IN    STD_LOGIC;
-                            SIGNAL clk     : IN    STD_LOGIC;
-                            SIGNAL in_en   : IN    STD_LOGIC;
-                            SIGNAL cnt_val : INOUT STD_LOGIC;
-                            SIGNAL cnt_dat : INOUT STD_LOGIC_VECTOR);
-                            
-  -- Transmit data
-  PROCEDURE proc_dp_tx_data(CONSTANT c_ready_latency : IN    NATURAL;
-                            SIGNAL   rst             : IN    STD_LOGIC;
-                            SIGNAL   clk             : IN    STD_LOGIC;
-                            SIGNAL   cnt_val         : IN    STD_LOGIC;
-                            SIGNAL   cnt_dat         : IN    STD_LOGIC_VECTOR;
-                            SIGNAL   tx_data         : INOUT t_dp_data_arr;
-                            SIGNAL   tx_val          : INOUT STD_LOGIC_VECTOR;
-                            SIGNAL   out_data        : OUT   STD_LOGIC_VECTOR;
-                            SIGNAL   out_val         : OUT   STD_LOGIC);
-  
-  -- Transmit data control (use for sop, eop)
-  PROCEDURE proc_dp_tx_ctrl(CONSTANT c_offset : IN  NATURAL;
-                            CONSTANT c_period : IN  NATURAL;
-                            SIGNAL   data     : IN  STD_LOGIC_VECTOR;
-                            SIGNAL   valid    : IN  STD_LOGIC;
-                            SIGNAL   ctrl     : OUT STD_LOGIC);
-                            
-  -- Define sync interval
-  PROCEDURE proc_dp_sync_interval(SIGNAL clk  : IN  STD_LOGIC;
-                                  SIGNAL sync : OUT STD_LOGIC);
-
-  -- Stimuli for cnt_en
-  PROCEDURE proc_dp_count_en(SIGNAL rst    : IN    STD_LOGIC;
-                             SIGNAL clk    : IN    STD_LOGIC;
-                             SIGNAL sync   : IN    STD_LOGIC;
-                             SIGNAL lfsr   : INOUT STD_LOGIC_VECTOR;
-                             SIGNAL state  : OUT   t_dp_state_enum;
-                             SIGNAL done   : OUT   STD_LOGIC;
-                             SIGNAL tb_end : OUT   STD_LOGIC;
-                             SIGNAL cnt_en : OUT   STD_LOGIC);
-
-  ------------------------------------------------------------------------------
-  -- Stream sink functions
-  ------------------------------------------------------------------------------
-  
-  -- Stimuli for out_ready
-  PROCEDURE proc_dp_out_ready(SIGNAL rst       : IN    STD_LOGIC;
-                              SIGNAL clk       : IN    STD_LOGIC;
-                              SIGNAL sync      : IN    STD_LOGIC;
-                              SIGNAL lfsr      : INOUT STD_LOGIC_VECTOR;
-                              SIGNAL out_ready : OUT   STD_LOGIC);
-                              
-  -- DUT output verify enable
-  PROCEDURE proc_dp_verify_en(CONSTANT c_delay   : IN  NATURAL;
-                              SIGNAL   rst       : IN  STD_LOGIC;
-                              SIGNAL   clk       : IN  STD_LOGIC;
-                              SIGNAL   sync      : IN  STD_LOGIC;
-                              SIGNAL   verify_en : OUT STD_LOGIC);
-                              
-  PROCEDURE proc_dp_verify_en(CONSTANT c_continuous : IN  BOOLEAN;
-                              SIGNAL   clk          : IN  STD_LOGIC;
-                              SIGNAL   valid        : IN  STD_LOGIC;
-                              SIGNAL   sop          : IN  STD_LOGIC;
-                              SIGNAL   eop          : IN  STD_LOGIC;
-                              SIGNAL   verify_en    : OUT STD_LOGIC);
-                              
-  -- Run and verify for some cycles
-  PROCEDURE proc_dp_verify_run_some_cycles(CONSTANT nof_pre_clk    : IN   NATURAL;
-                                           CONSTANT nof_verify_clk : IN   NATURAL;
-                                           CONSTANT nof_post_clk   : IN   NATURAL;
-                                           SIGNAL   clk            : IN   STD_LOGIC;
-                                           SIGNAL   verify_en      : OUT  STD_LOGIC);
-                                           
-  -- Verify the expected value
-  PROCEDURE proc_dp_verify_value(CONSTANT c_str : IN STRING;
-                                 CONSTANT mode  : IN t_dp_value_enum;
-                                 SIGNAL   clk   : IN STD_LOGIC;
-                                 SIGNAL   en    : IN STD_LOGIC;
-                                 SIGNAL   exp   : IN STD_LOGIC_VECTOR;  
-                                 SIGNAL   res   : IN STD_LOGIC_VECTOR);
-                                 
-  PROCEDURE proc_dp_verify_value(CONSTANT mode : IN t_dp_value_enum;
-                                 SIGNAL   clk  : IN STD_LOGIC;
-                                 SIGNAL   en   : IN STD_LOGIC;
-                                 SIGNAL   exp  : IN STD_LOGIC_VECTOR;  
-                                 SIGNAL   res  : IN STD_LOGIC_VECTOR);
-                                
-  PROCEDURE proc_dp_verify_value(CONSTANT c_str : IN STRING;
-                                 SIGNAL   clk   : IN STD_LOGIC;
-                                 SIGNAL   en    : IN STD_LOGIC;
-                                 SIGNAL   exp   : IN STD_LOGIC;  
-                                 SIGNAL   res   : IN STD_LOGIC);
-                                 
-  -- Verify output global and local BSN
-  -- . incrementing or replicated global BSN
-  -- . incrementing local BSN that starts at 1
-  PROCEDURE proc_dp_verify_bsn(CONSTANT c_use_local_bsn             : IN    BOOLEAN;    -- use local BSN or only use global BSN
-                               CONSTANT c_global_bsn_increment      : IN    POSITIVE;   -- increment per global BSN
-                               CONSTANT c_nof_replicated_global_bsn : IN    POSITIVE;   -- number of replicated global BSN
-                               CONSTANT c_block_per_sync            : IN    POSITIVE;   -- of sop/eop blocks per sync interval
-                               SIGNAL   clk                         : IN    STD_LOGIC;
-                               SIGNAL   out_sync                    : IN    STD_LOGIC;
-                               SIGNAL   out_sop                     : IN    STD_LOGIC;
-                               SIGNAL   out_bsn                     : IN    STD_LOGIC_VECTOR;
-                               SIGNAL   verify_en                   : INOUT STD_LOGIC;  -- initialize '0', becomes '1' when bsn verification starts
-                               SIGNAL   cnt_replicated_global_bsn   : INOUT NATURAL;
-                               SIGNAL   prev_out_bsn_global         : INOUT STD_LOGIC_VECTOR;
-                               SIGNAL   prev_out_bsn_local          : INOUT STD_LOGIC_VECTOR);
-                               
-  -- Verify incrementing data
-  -- . wrap at c_out_data_max when >0, else no wrap when c_out_data_max=0
-  -- . default increment by +1, but also allow an increment by +c_out_data_gap
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_ready_latency : IN    NATURAL;
-                                CONSTANT c_out_data_max  : IN    UNSIGNED;
-                                CONSTANT c_out_data_gap  : IN    UNSIGNED;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_ready       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-                                
-  -- Verify the DUT incrementing output data that wraps in range 0 ... c_out_data_max
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_ready_latency : IN    NATURAL;
-                                CONSTANT c_out_data_max  : IN    UNSIGNED;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_ready       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-                                
-  -- Verify the DUT incrementing output data, fixed increment +1
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_ready_latency : IN    NATURAL;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_ready       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;  -- by using sop or eop proc_dp_verify_data() can also be used to verify other SOSI fields like bsn, error, channel, empty
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-                                
-  -- Verify incrementing data with RL > 0 or no flow control, support wrap at maximum and increment gap
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_out_data_max  : IN    UNSIGNED;
-                                CONSTANT c_out_data_gap  : IN    UNSIGNED;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-  
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_out_data_max  : IN    NATURAL;
-                                CONSTANT c_out_data_gap  : IN    NATURAL;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-                                
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_out_data_max  : IN    NATURAL;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-                                
-  -- Verify incrementing data with RL > 0 or no flow control, fixed increment +1
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-                                
-  -- Verify the DUT output symbols
-  PROCEDURE proc_dp_verify_symbols(CONSTANT c_ready_latency : IN    NATURAL;
-                                   CONSTANT c_data_w        : IN    NATURAL;
-                                   CONSTANT c_symbol_w      : IN    NATURAL;
-                                   SIGNAL   clk             : IN    STD_LOGIC;
-                                   SIGNAL   verify_en       : IN    STD_LOGIC;
-                                   SIGNAL   out_ready       : IN    STD_LOGIC;
-                                   SIGNAL   out_val         : IN    STD_LOGIC;
-                                   SIGNAL   out_eop         : IN    STD_LOGIC;
-                                   SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                   SIGNAL   out_empty       : IN    STD_LOGIC_VECTOR;
-                                   SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR);
-                                   
-  -- Verify the DUT output data with empty
-  PROCEDURE proc_dp_verify_data_empty(CONSTANT c_ready_latency : IN    NATURAL;
-                                      CONSTANT c_last_word     : IN    NATURAL;
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   verify_en       : IN    STD_LOGIC;
-                                      SIGNAL   out_ready       : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop_1       : INOUT STD_LOGIC;
-                                      SIGNAL   out_eop_2       : INOUT STD_LOGIC;
-                                      SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                      SIGNAL   out_data_1      : INOUT STD_LOGIC_VECTOR;
-                                      SIGNAL   out_data_2      : INOUT STD_LOGIC_VECTOR;
-                                      SIGNAL   out_data_3      : INOUT STD_LOGIC_VECTOR;
-                                      SIGNAL   out_empty       : IN    STD_LOGIC_VECTOR;
-                                      SIGNAL   out_empty_1     : INOUT STD_LOGIC_VECTOR);
-                                      
-  PROCEDURE proc_dp_verify_other_sosi(CONSTANT c_str       : IN STRING;
-                                      CONSTANT c_exp_data  : IN STD_LOGIC_VECTOR;
-                                      SIGNAL   clk         : IN STD_LOGIC;
-                                      SIGNAL   verify_en   : IN STD_LOGIC;
-                                      SIGNAL   res_data    : IN STD_LOGIC_VECTOR);
-                                      
-  PROCEDURE proc_dp_verify_valid(CONSTANT c_ready_latency : IN    NATURAL;
-                                 SIGNAL   clk             : IN    STD_LOGIC;
-                                 SIGNAL   verify_en       : IN    STD_LOGIC;
-                                 SIGNAL   out_ready       : IN    STD_LOGIC;
-                                 SIGNAL   prev_out_ready  : INOUT STD_LOGIC_VECTOR;
-                                 SIGNAL   out_val         : IN    STD_LOGIC);
-                                 
-  PROCEDURE proc_dp_verify_valid(SIGNAL   clk             : IN    STD_LOGIC;
-                                 SIGNAL   verify_en       : IN    STD_LOGIC;
-                                 SIGNAL   out_ready       : IN    STD_LOGIC;
-                                 SIGNAL   prev_out_ready  : INOUT STD_LOGIC;
-                                 SIGNAL   out_val         : IN    STD_LOGIC);
-                                 
-  -- Verify the DUT output sync
-  PROCEDURE proc_dp_verify_sync(CONSTANT c_sync_period : IN    NATURAL;
-                                CONSTANT c_sync_offset : IN    NATURAL;
-                                SIGNAL   clk           : IN    STD_LOGIC;
-                                SIGNAL   verify_en     : IN    STD_LOGIC;
-                                SIGNAL   sync          : IN    STD_LOGIC;
-                                SIGNAL   sop           : IN    STD_LOGIC;
-                                SIGNAL   bsn           : IN    STD_LOGIC_VECTOR);
-                                
-  -- Verify the DUT output sop and eop
-  PROCEDURE proc_dp_verify_sop_and_eop(CONSTANT c_ready_latency : IN    NATURAL;
-                                       CONSTANT c_verify_valid  : IN    BOOLEAN;
-                                       SIGNAL   clk             : IN    STD_LOGIC;
-                                       SIGNAL   out_ready       : IN    STD_LOGIC;
-                                       SIGNAL   out_val         : IN    STD_LOGIC;
-                                       SIGNAL   out_sop         : IN    STD_LOGIC;
-                                       SIGNAL   out_eop         : IN    STD_LOGIC;
-                                       SIGNAL   hold_sop        : INOUT STD_LOGIC);
-                                       
-  PROCEDURE proc_dp_verify_sop_and_eop(CONSTANT c_ready_latency : IN    NATURAL;
-                                       SIGNAL   clk             : IN    STD_LOGIC;
-                                       SIGNAL   out_ready       : IN    STD_LOGIC;
-                                       SIGNAL   out_val         : IN    STD_LOGIC;
-                                       SIGNAL   out_sop         : IN    STD_LOGIC;
-                                       SIGNAL   out_eop         : IN    STD_LOGIC;
-                                       SIGNAL   hold_sop        : INOUT STD_LOGIC);
-                                       
-  PROCEDURE proc_dp_verify_sop_and_eop(SIGNAL clk      : IN    STD_LOGIC;
-                                       SIGNAL out_val  : IN    STD_LOGIC;
-                                       SIGNAL out_sop  : IN    STD_LOGIC;
-                                       SIGNAL out_eop  : IN    STD_LOGIC;
-                                       SIGNAL hold_sop : INOUT STD_LOGIC);
-                                       
-  PROCEDURE proc_dp_verify_block_size(CONSTANT c_ready_latency : IN    NATURAL;
-                                      SIGNAL   alt_size        : IN    NATURAL;     -- alternative size (eg. use exp_size'last_value)
-                                      SIGNAL   exp_size        : IN    NATURAL;     -- expected size
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   out_ready       : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_sop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   cnt_size        : INOUT NATURAL);
-                                      
-  PROCEDURE proc_dp_verify_block_size(CONSTANT c_ready_latency : IN    NATURAL;
-                                      SIGNAL   exp_size        : IN    NATURAL;     -- expected size
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   out_ready       : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_sop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   cnt_size        : INOUT NATURAL);
-                                      
-  PROCEDURE proc_dp_verify_block_size(SIGNAL alt_size : IN    NATURAL;     -- alternative size (eg. use exp_size'last_value)
-                                      SIGNAL exp_size : IN    NATURAL;     -- expected size
-                                      SIGNAL clk      : IN    STD_LOGIC;
-                                      SIGNAL out_val  : IN    STD_LOGIC;
-                                      SIGNAL out_sop  : IN    STD_LOGIC;
-                                      SIGNAL out_eop  : IN    STD_LOGIC;
-                                      SIGNAL cnt_size : INOUT NATURAL);
-                                      
-  PROCEDURE proc_dp_verify_block_size(SIGNAL exp_size : IN    NATURAL;     -- expected size
-                                      SIGNAL clk      : IN    STD_LOGIC;
-                                      SIGNAL out_val  : IN    STD_LOGIC;
-                                      SIGNAL out_sop  : IN    STD_LOGIC;
-                                      SIGNAL out_eop  : IN    STD_LOGIC;
-                                      SIGNAL cnt_size : INOUT NATURAL);
-                                       
-  -- Verify the DUT output invalid between frames
-  PROCEDURE proc_dp_verify_gap_invalid(SIGNAL clk     : IN    STD_LOGIC;
-                                       SIGNAL in_val  : IN    STD_LOGIC;
-                                       SIGNAL in_sop  : IN    STD_LOGIC;
-                                       SIGNAL in_eop  : IN    STD_LOGIC;
-                                       SIGNAL out_gap : INOUT STD_LOGIC);  -- declare initial gap signal = '1'
-                                       
-  -- Verify the DUT output control (use for sop, eop)
-  PROCEDURE proc_dp_verify_ctrl(CONSTANT c_offset  : IN NATURAL;
-                                CONSTANT c_period  : IN NATURAL;
-                                CONSTANT c_str     : IN STRING;
-                                SIGNAL   clk       : IN STD_LOGIC;
-                                SIGNAL   verify_en : IN STD_LOGIC;
-                                SIGNAL   data      : IN STD_LOGIC_VECTOR;
-                                SIGNAL   valid     : IN STD_LOGIC;
-                                SIGNAL   ctrl      : IN STD_LOGIC);
-                                
-  -- Wait for stream valid
-  PROCEDURE proc_dp_stream_valid(SIGNAL clk      : IN  STD_LOGIC;
-                                 SIGNAL in_valid : IN  STD_LOGIC);
-  
-  -- Wait for stream valid AND sop
-  PROCEDURE proc_dp_stream_valid_sop(SIGNAL clk      : IN  STD_LOGIC;
-                                     SIGNAL in_valid : IN  STD_LOGIC;
-                                     SIGNAL in_sop   : IN  STD_LOGIC);
-  
-  -- Wait for stream valid AND eop
-  PROCEDURE proc_dp_stream_valid_eop(SIGNAL clk      : IN  STD_LOGIC;
-                                     SIGNAL in_valid : IN  STD_LOGIC;
-                                     SIGNAL in_eop   : IN  STD_LOGIC);
-  
-END tb_dp_pkg;
-
-
-PACKAGE BODY tb_dp_pkg IS
-
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Block data generator with feedforward throttle control
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_gen_block_data(CONSTANT c_nof_block_per_sync : IN    NATURAL;
-                                   CONSTANT c_block_size         : IN    NATURAL;
-                                   CONSTANT c_gap_size           : IN    NATURAL;
-                                   CONSTANT c_throttle_num       : IN    NATURAL;
-                                   CONSTANT c_throttle_den       : IN    NATURAL;
-                                   SIGNAL   rst                  : IN    STD_LOGIC;
-                                   SIGNAL   clk                  : IN    STD_LOGIC;
-                                   SIGNAL   sync_nr              : INOUT NATURAL;
-                                   SIGNAL   block_nr             : INOUT NATURAL;
-                                   SIGNAL   cnt_sync             : OUT   STD_LOGIC;
-                                   SIGNAL   cnt_val              : OUT   STD_LOGIC;
-                                   SIGNAL   cnt_dat              : INOUT STD_LOGIC_VECTOR) IS
-    CONSTANT c_start_delay : NATURAL := 10;
-    VARIABLE v_throttle    : NATURAL;
-  BEGIN
-    sync_nr  <= 0;
-    block_nr <= 0;
-    
-    cnt_sync <= '0';    
-    cnt_val  <= '0';
-    cnt_dat  <= (cnt_dat'RANGE=>'1');  -- -1, so first valid cnt_dat starts at 0
-    
-    -- allow some clock cycles before start after rst release
-    WAIT UNTIL rst='0';
-    FOR I IN 0 TO c_start_delay-1 LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- output first sync
-    cnt_sync <= '1';
-    WAIT UNTIL rising_edge(clk);
-    cnt_sync <= '0';
-    FOR I IN 1 TO c_gap_size-1 LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    WHILE TRUE LOOP
-      -- output block
-      IF c_throttle_num >= c_throttle_den THEN
-        -- no need to throttle, so cnt_val active during whole data block
-        FOR I IN 0 TO c_block_size-1 LOOP
-          cnt_val <= '1';
-          cnt_dat <= INCR_UVEC(cnt_dat, 1);
-          WAIT UNTIL rising_edge(clk);
-        END LOOP;
-      ELSE
-        -- throttle cnt_val, so c_throttle_num active cnt_val cycles per c_throttle_den cycles
-        FOR I IN 0 TO c_block_size/c_throttle_num-1 LOOP
-          FOR J IN 0 TO c_throttle_num-1 LOOP
-            cnt_val <= '1';
-            cnt_dat <= INCR_UVEC(cnt_dat, 1);
-            WAIT UNTIL rising_edge(clk);
-          END LOOP;
-          FOR J IN 0 TO c_throttle_den-c_throttle_num-1 LOOP
-            cnt_val <= '0';
-            WAIT UNTIL rising_edge(clk);
-          END LOOP;
-        END LOOP;
-      END IF;
-      cnt_val <= '0';
-      -- output sync for next block at first sample of gap
-      IF block_nr>0 AND ((block_nr + 1) MOD c_nof_block_per_sync)=0 THEN
-        cnt_sync <= '1';
-        sync_nr  <= sync_nr+1;
-      END IF;
-      WAIT UNTIL rising_edge(clk);
-      -- output rest of the gap
-      cnt_sync <= '0';
-      FOR I IN 1 TO c_gap_size-1 LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-      -- next block
-      block_nr <= block_nr+1;
-    END LOOP;    
-  END proc_dp_gen_block_data;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Block data generator with ready flow control and symbols counter
-  -- . dependent on in_en and src_in.ready
-  -- . optional sync pulse at end of frame 
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_gen_block_data(CONSTANT c_ready_latency  : IN  NATURAL;    -- 0, 1 are supported by proc_dp_stream_ready_latency()
-                                   CONSTANT c_use_data       : IN  BOOLEAN;    -- when TRUE use data field, else use re, im fields, and keep unused fields at 'X'
-                                   CONSTANT c_data_w         : IN  NATURAL;    -- data width for the data, re and im fields
-                                   CONSTANT c_symbol_w       : IN  NATURAL;    -- c_data_w/c_symbol_w must be an integer
-                                   CONSTANT c_symbol_init    : IN  NATURAL;    -- init counter for symbols in data field
-                                   CONSTANT c_symbol_re_init : IN  NATURAL;    -- init counter for symbols in re field
-                                   CONSTANT c_symbol_im_init : IN  NATURAL;    -- init counter for symbols in im field
-                                   CONSTANT c_nof_symbols    : IN  NATURAL;    -- nof symbols per frame for the data, re and im fields
-                                   CONSTANT c_channel        : IN  NATURAL;    -- channel field
-                                   CONSTANT c_error          : IN  NATURAL;    -- error field
-                                   CONSTANT c_sync           : IN  STD_LOGIC;  -- when '1' issue sync pulse during this block
-                                   CONSTANT c_bsn            : IN  STD_LOGIC_VECTOR;  -- bsn field
-                                   SIGNAL   clk              : IN  STD_LOGIC;
-                                   SIGNAL   in_en            : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                                   SIGNAL   src_in           : IN  t_dp_siso;
-                                   SIGNAL   src_out          : OUT t_dp_sosi) IS
-    CONSTANT c_nof_symbols_per_data : NATURAL := c_data_w/c_symbol_w;
-    CONSTANT c_div                  : NATURAL := c_nof_symbols   / c_nof_symbols_per_data;
-    CONSTANT c_mod                  : NATURAL := c_nof_symbols MOD c_nof_symbols_per_data;
-    CONSTANT c_empty                : NATURAL := sel_a_b(c_mod, c_nof_symbols_per_data - c_mod, 0);
-    CONSTANT c_nof_data             : NATURAL := sel_a_b(c_mod, 1, 0) + c_div;
-    VARIABLE v_data                 : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0):= func_dp_data_init(c_data_w, c_symbol_w, c_symbol_init);
-    VARIABLE v_re                   : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0):= func_dp_data_init(c_data_w, c_symbol_w, c_symbol_re_init);
-    VARIABLE v_im                   : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0):= func_dp_data_init(c_data_w, c_symbol_w, c_symbol_im_init);
-  BEGIN
-    src_out <= c_dp_sosi_rst;
-    IF src_in.xon='1' THEN
-      -- Generate this block
-      src_out.bsn     <= RESIZE_DP_BSN(c_bsn);
-      src_out.empty   <= TO_DP_EMPTY(c_empty);
-      src_out.channel <= TO_DP_CHANNEL(c_channel);
-      src_out.err     <= TO_DP_ERROR(c_error);
-      IF c_use_data=TRUE  THEN src_out.data  <= RESIZE_DP_DATA(v_data);   END IF;
-      IF c_use_data=FALSE THEN src_out.re    <= RESIZE_DP_DSP_DATA(v_re); END IF;
-      IF c_use_data=FALSE THEN src_out.im    <= RESIZE_DP_DSP_DATA(v_im); END IF;
-      IF c_nof_data>1 THEN
-        -- . sop
-        proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, c_sync, '1', '1', '0', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-        -- . valid
-        FOR I IN 1 TO c_nof_data-2 LOOP
-          v_data := func_dp_data_incr(c_data_w, c_symbol_w, v_data);
-          v_re   := func_dp_data_incr(c_data_w, c_symbol_w, v_re);
-          v_im   := func_dp_data_incr(c_data_w, c_symbol_w, v_im);
-          IF c_use_data=TRUE  THEN src_out.data <= RESIZE_DP_DATA(v_data);   END IF;
-          IF c_use_data=FALSE THEN src_out.re   <= RESIZE_DP_DSP_DATA(v_re); END IF;
-          IF c_use_data=FALSE THEN src_out.im   <= RESIZE_DP_DSP_DATA(v_im); END IF;
-          proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, '0', '1', '0', '0', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-        END LOOP;
-        
-        -- . eop
-        v_data := func_dp_data_incr(c_data_w, c_symbol_w, v_data);
-        v_re   := func_dp_data_incr(c_data_w, c_symbol_w, v_re);
-        v_im   := func_dp_data_incr(c_data_w, c_symbol_w, v_im);
-        IF c_use_data=TRUE  THEN src_out.data <= RESIZE_DP_DATA(v_data);   END IF;
-        IF c_use_data=FALSE THEN src_out.re   <= RESIZE_DP_DSP_DATA(v_re); END IF;
-        IF c_use_data=FALSE THEN src_out.im   <= RESIZE_DP_DSP_DATA(v_im); END IF;
-        proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, '0', '1', '0', '1', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-      ELSE
-        -- . sop and eop, frame has only one word
-        proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, c_sync, '1', '1', '1', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-      END IF;
-    ELSE
-      -- Skip this block
-      proc_common_wait_some_cycles(clk, c_nof_data);
-    END IF;
-  END proc_dp_gen_block_data;
-  
-  
-  PROCEDURE proc_dp_gen_block_data(CONSTANT c_data_w         : IN  NATURAL;    -- data width for the data field
-                                   CONSTANT c_symbol_init    : IN  NATURAL;    -- init counter for the data in the data field
-                                   CONSTANT c_nof_symbols    : IN  NATURAL;    -- nof symbols per frame for the data fields
-                                   CONSTANT c_channel        : IN  NATURAL;    -- channel field
-                                   CONSTANT c_error          : IN  NATURAL;    -- error field
-                                   CONSTANT c_sync           : IN  STD_LOGIC;  -- when '1' issue sync pulse during this block
-                                   CONSTANT c_bsn            : IN  STD_LOGIC_VECTOR;  -- bsn field
-                                   SIGNAL   clk              : IN  STD_LOGIC;
-                                   SIGNAL   in_en            : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                                   SIGNAL   src_in           : IN  t_dp_siso;
-                                   SIGNAL   src_out          : OUT t_dp_sosi) IS
-  BEGIN
-    proc_dp_gen_block_data(1, TRUE, c_data_w, c_data_w, c_symbol_init, 0, 0, c_nof_symbols, c_channel, c_error, c_sync, c_bsn, clk, in_en, src_in, src_out);
-  END proc_dp_gen_block_data;
-                            
-         
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Handle stream ready signal
-  -- . output active when src_in is ready and in_en='1'
-  -- . only support RL=0 or 1, support for RL>1 requires keeping previous ready information in a STD_LOGIC_VECTOR(RL-1 DOWNTO 0).
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_stream_ready_latency(CONSTANT c_latency : IN  NATURAL;
-                                         SIGNAL   clk       : IN  STD_LOGIC;
-                                         SIGNAL   ready     : IN  STD_LOGIC;
-                                         SIGNAL   in_en     : IN  STD_LOGIC;
-                                         CONSTANT c_sync    : IN  STD_LOGIC;
-                                         CONSTANT c_valid   : IN  STD_LOGIC;
-                                         CONSTANT c_sop     : IN  STD_LOGIC;
-                                         CONSTANT c_eop     : IN  STD_LOGIC;
-                                         SIGNAL   out_sync  : OUT STD_LOGIC;
-                                         SIGNAL   out_valid : OUT STD_LOGIC;
-                                         SIGNAL   out_sop   : OUT STD_LOGIC;
-                                         SIGNAL   out_eop   : OUT STD_LOGIC) IS
-  BEGIN
-    -- Default no output
-    out_sync  <= '0';
-    out_valid <= '0';
-    out_sop   <= '0';
-    out_eop   <= '0';
-    
-    -- Skip cycles until in_en='1'
-    WHILE in_en='0' LOOP
-      WAIT UNTIL rising_edge(clk);
-    END LOOP;
-    
-    -- Active output when ready
-    -- . RL = 0
-    IF c_latency=0 THEN
-      -- show the available output until acknowledge
-      out_sync  <= c_sync;
-      out_valid <= c_valid;
-      out_sop   <= c_sop;
-      out_eop   <= c_eop;
-      WAIT UNTIL rising_edge(clk);
-      WHILE ready /= '1' LOOP
-        WAIT UNTIL rising_edge(clk);
-      END LOOP;
-      -- ready has acknowledged the valid output
-    END IF;
-    
-    -- . RL = 1
-    IF c_latency=1 THEN
-      -- no valid output until request
-      WHILE ready /= '1' LOOP
-        WAIT UNTIL rising_edge(clk);
-      END LOOP;
-      -- ready has requested this valid output
-      out_sync  <= c_sync;
-      out_valid <= c_valid;
-      out_sop   <= c_sop;
-      out_eop   <= c_eop;
-      WAIT UNTIL rising_edge(clk);
-    END IF;
-    
-    -- Return with no active output
-    out_sync  <= '0';
-    out_valid <= '0';
-    out_sop   <= '0';
-    out_eop   <= '0';
-  END proc_dp_stream_ready_latency;
-
-  
-  ------------------------------------------------------------------------------
-  -- FUNCTION: Initialize the data per symbol
-  -- . use big endian
-  -- . if c_data_w=32, c_symbol_w=8, init=3 then return 0x03040506
-  ------------------------------------------------------------------------------
-  FUNCTION func_dp_data_init(c_data_w, c_symbol_w, init : NATURAL) RETURN STD_LOGIC_VECTOR IS
-    CONSTANT c_nof_symbols_per_data : NATURAL := c_data_w/c_symbol_w;
-    VARIABLE v_data                 : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0);
-    VARIABLE v_sym                  : STD_LOGIC_VECTOR(c_symbol_w-1 DOWNTO 0);
-  BEGIN
-    v_data := (OTHERS=>'0');
-    v_sym  := TO_UVEC(init, c_symbol_w);
-    FOR I IN c_nof_symbols_per_data-1 DOWNTO 0 LOOP
-      v_data((I+1)*c_symbol_w-1 DOWNTO I*c_symbol_w) := v_sym;
-      v_sym := INCR_UVEC(v_sym, 1);
-    END LOOP;
-    RETURN v_data;
-  END func_dp_data_init;
-  
-  
-  ------------------------------------------------------------------------------
-  -- FUNCTION: Increment the data per symbol
-  -- . use big endian
-  -- . if c_data_w=32, c_symbol_w=8 then 0x00010203 returns 0x04050607
-  -- . the actual data'LENGTH must be >= c_data_w, unused bits become 0
-  -- . c_data_w/c_symbol_w must be an integer
-  ------------------------------------------------------------------------------
-  FUNCTION func_dp_data_incr(c_data_w, c_symbol_w : NATURAL; data : STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
-    CONSTANT c_nof_symbols_per_data : NATURAL := c_data_w/c_symbol_w;
-    VARIABLE v_data                 : STD_LOGIC_VECTOR(data'LENGTH-1 DOWNTO 0);
-    VARIABLE v_sym                  : STD_LOGIC_VECTOR(c_symbol_w-1 DOWNTO 0);
-  BEGIN
-    v_data := (OTHERS=>'0');
-    v_sym  := data(c_symbol_w-1 DOWNTO 0);
-    FOR I IN c_nof_symbols_per_data-1 DOWNTO 0 LOOP
-      v_sym := INCR_UVEC(v_sym, 1);
-      v_data((I+1)*c_symbol_w-1 DOWNTO I*c_symbol_w) := v_sym;
-    END LOOP;
-    RETURN v_data;
-  END func_dp_data_incr;
-    
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Generate counter data with valid
-  -- . Output counter data dependent on in_en and src_in.ready
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_gen_data(CONSTANT c_ready_latency : IN  NATURAL;    -- 0, 1 are supported by proc_dp_stream_ready_latency()
-                             CONSTANT c_data_w        : IN  NATURAL;
-                             CONSTANT c_data_init     : IN  NATURAL;
-                             SIGNAL   rst             : IN  STD_LOGIC;
-                             SIGNAL   clk             : IN  STD_LOGIC;
-                             SIGNAL   in_en           : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                             SIGNAL   src_in          : IN  t_dp_siso;
-                             SIGNAL   src_out         : OUT t_dp_sosi) IS
-    VARIABLE v_data : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0):= TO_UVEC(c_data_init, c_data_w);
-  BEGIN
-    src_out      <= c_dp_sosi_rst;
-    src_out.data <= RESIZE_DP_DATA(v_data);
-    IF rst='0' THEN
-      WAIT UNTIL rising_edge(clk);
-      WHILE TRUE LOOP
-        src_out.data <= RESIZE_DP_DATA(v_data);
-        proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, '0', '1', '0', '0', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-        v_data := INCR_UVEC(v_data, 1);
-      END LOOP;
-    END IF;
-  END proc_dp_gen_data;
-
-
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Generate counter data with valid
-  -- . Output counter data dependent on in_en and src_in.ready
-  -- . with maximum count value
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_gen_data(CONSTANT c_ready_latency   : IN  NATURAL; 
-                             CONSTANT c_data_w          : IN  NATURAL;
-                             CONSTANT c_data_init       : IN  NATURAL;
-                             CONSTANT c_data_max        : IN  NATURAL; 
-                             SIGNAL   rst               : IN  STD_LOGIC;
-                             SIGNAL   clk               : IN  STD_LOGIC;
-                             SIGNAL   in_en             : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                             SIGNAL   src_in            : IN  t_dp_siso;
-                             SIGNAL   src_out           : OUT t_dp_sosi) IS
-    VARIABLE v_cnt     : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0):= TO_UVEC(c_data_init, c_data_w);
-  BEGIN
-    src_out         <= c_dp_sosi_rst;
-    src_out.data    <= RESIZE_DP_DATA(v_cnt);
-    IF rst='0' THEN
-      WAIT UNTIL rising_edge(clk);
-      WHILE TRUE LOOP
-        src_out.data    <= RESIZE_DP_DATA(v_cnt);
-        proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, '0', '1', '0', '0', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-        IF TO_UINT(v_cnt)=c_data_max THEN
-          v_cnt := TO_UVEC(c_data_init, c_data_w);
-        ELSE
-          v_cnt := INCR_UVEC(v_cnt, 1);
-        END IF;
-      END LOOP;
-    END IF;
-  END proc_dp_gen_data;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Generate a frame with symbols counter
-  -- . dependent on in_en and src_in.ready
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_gen_frame(CONSTANT c_ready_latency : IN  NATURAL;    -- 0, 1 are supported by proc_dp_stream_ready_latency()
-                              CONSTANT c_data_w        : IN  NATURAL;
-                              CONSTANT c_symbol_w      : IN  NATURAL;    -- c_data_w/c_symbol_w must be an integer
-                              CONSTANT c_symbol_init   : IN  NATURAL;
-                              CONSTANT c_nof_symbols   : IN  NATURAL;
-                              CONSTANT c_bsn           : IN  NATURAL;
-                              CONSTANT c_sync          : IN  STD_LOGIC;
-                              SIGNAL   clk             : IN  STD_LOGIC;
-                              SIGNAL   in_en           : IN  STD_LOGIC;  -- when '0' then no valid output even when src_in is ready
-                              SIGNAL   src_in          : IN  t_dp_siso;
-                              SIGNAL   src_out         : OUT t_dp_sosi) IS
-    CONSTANT c_nof_symbols_per_data : NATURAL := c_data_w/c_symbol_w;
-    CONSTANT c_div                  : NATURAL := c_nof_symbols   / c_nof_symbols_per_data;
-    CONSTANT c_mod                  : NATURAL := c_nof_symbols MOD c_nof_symbols_per_data;
-    CONSTANT c_empty                : NATURAL := sel_a_b(c_mod, c_nof_symbols_per_data - c_mod, 0);
-    CONSTANT c_nof_data             : NATURAL := sel_a_b(c_mod, 1, 0) + c_div;
-    VARIABLE v_data                 : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0):= func_dp_data_init(c_data_w, c_symbol_w, c_symbol_init);
-  BEGIN
-    src_out       <= c_dp_sosi_rst;
-    src_out.bsn   <= TO_DP_BSN(c_bsn);
-    src_out.empty <= TO_DP_EMPTY(c_empty);
-    src_out.data  <= RESIZE_DP_DATA(v_data);
-    IF c_nof_data>1 THEN
-      -- . sop
-      proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, c_sync, '1', '1', '0', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-      -- . valid
-      FOR I IN 1 TO c_nof_data-2 LOOP
-        v_data := func_dp_data_incr(c_data_w, c_symbol_w, v_data);
-        src_out.data <= RESIZE_DP_DATA(v_data);
-        proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, '0', '1', '0', '0', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-      END LOOP;
-      -- . eop
-      v_data := func_dp_data_incr(c_data_w, c_symbol_w, v_data);
-      src_out.data <= RESIZE_DP_DATA(v_data);
-      proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, '0', '1', '0', '1', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-    ELSE
-      -- . sop and eop, frame has only one word
-      proc_dp_stream_ready_latency(c_ready_latency, clk, src_in.ready, in_en, c_sync, '1', '1', '1', src_out.sync, src_out.valid, src_out.sop, src_out.eop);
-    END IF;
-    src_out.sync  <= '0';
-    src_out.valid <= '0';
-    src_out.sop   <= '0';
-    src_out.eop   <= '0';
-  END proc_dp_gen_frame;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Input data counter
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_cnt_dat(SIGNAL rst     : IN    STD_LOGIC;
-                            SIGNAL clk     : IN    STD_LOGIC;
-                            SIGNAL in_en   : IN    STD_LOGIC;
-                            SIGNAL cnt_dat : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    IF rst='1' THEN
-      cnt_dat <= (cnt_dat'RANGE=>'0');
-    ELSIF rising_edge(clk) THEN
-      IF in_en='1' THEN
-        cnt_dat <= STD_LOGIC_VECTOR(UNSIGNED(cnt_dat)+1);
-      END IF;
-    END IF;
-  END proc_dp_cnt_dat;
-  
-  PROCEDURE proc_dp_cnt_dat(SIGNAL rst     : IN    STD_LOGIC;
-                            SIGNAL clk     : IN    STD_LOGIC;
-                            SIGNAL in_en   : IN    STD_LOGIC;
-                            SIGNAL cnt_val : INOUT STD_LOGIC;
-                            SIGNAL cnt_dat : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    IF rst='1' THEN
-      cnt_val <= '0';
-      cnt_dat <= (cnt_dat'RANGE=>'0');
-    ELSIF rising_edge(clk) THEN
-      cnt_val <= '0';
-      IF in_en='1' THEN
-        cnt_val <= '1';
-        cnt_dat <= STD_LOGIC_VECTOR(UNSIGNED(cnt_dat)+1);
-      END IF;
-    END IF;
-  END proc_dp_cnt_dat;
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Transmit data
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_tx_data(CONSTANT c_ready_latency : IN    NATURAL;
-                            SIGNAL   rst             : IN    STD_LOGIC;
-                            SIGNAL   clk             : IN    STD_LOGIC;
-                            SIGNAL   cnt_val         : IN    STD_LOGIC;
-                            SIGNAL   cnt_dat         : IN    STD_LOGIC_VECTOR;
-                            SIGNAL   tx_data         : INOUT t_dp_data_arr;
-                            SIGNAL   tx_val          : INOUT STD_LOGIC_VECTOR;
-                            SIGNAL   out_data        : OUT   STD_LOGIC_VECTOR;
-                            SIGNAL   out_val         : OUT   STD_LOGIC) IS
-    CONSTANT c_void : NATURAL := sel_a_b(c_ready_latency, 1, 0);  -- used to avoid empty range VHDL warnings when c_ready_latency=0
-  BEGIN
-    -- TX data array for output ready latency [c_ready_latency], index [0] for zero latency combinatorial
-    tx_data(0) <= cnt_dat;
-    tx_val( 0) <= cnt_val;
-    
-    IF rst='1' THEN
-      tx_data(1 TO c_ready_latency+c_void) <= (1 TO c_ready_latency+c_void=>(OTHERS=>'0'));
-      tx_val( 1 TO c_ready_latency+c_void) <= (1 TO c_ready_latency+c_void=>'0');
-    ELSIF rising_edge(clk) THEN
-      tx_data(1 TO c_ready_latency+c_void) <= tx_data(0 TO c_ready_latency+c_void-1);
-      tx_val( 1 TO c_ready_latency+c_void) <= tx_val( 0 TO c_ready_latency+c_void-1);
-    END IF;
-    
-    out_data <= tx_data(c_ready_latency);
-    out_val  <= tx_val(c_ready_latency);
-  END proc_dp_tx_data;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Transmit data control (use for sop, eop)
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_tx_ctrl(CONSTANT c_offset : IN  NATURAL;
-                            CONSTANT c_period : IN  NATURAL;
-                            SIGNAL   data     : IN  STD_LOGIC_VECTOR;
-                            SIGNAL   valid    : IN  STD_LOGIC;
-                            SIGNAL   ctrl     : OUT STD_LOGIC) IS
-    VARIABLE v_data : INTEGER;
-  BEGIN
-    v_data := TO_UINT(data);
-    ctrl <= '0';
-    IF valid='1' AND ((v_data-c_offset) MOD c_period)=0 THEN
-      ctrl <= '1';
-    END IF;
-  END proc_dp_tx_ctrl;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Define test sync interval
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_sync_interval(SIGNAL clk  : IN  STD_LOGIC;
-                                  SIGNAL sync : OUT STD_LOGIC) IS
-  BEGIN
-    sync <= '0';
-    FOR I IN 1 TO c_dp_sync_interval-1 LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    sync <= '1';
-    WAIT UNTIL rising_edge(clk);
-  END proc_dp_sync_interval;
-
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Stimuli for cnt_en
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_count_en(SIGNAL rst    : IN    STD_LOGIC;
-                             SIGNAL clk    : IN    STD_LOGIC;
-                             SIGNAL sync   : IN    STD_LOGIC;
-                             SIGNAL lfsr   : INOUT STD_LOGIC_VECTOR;
-                             SIGNAL state  : OUT   t_dp_state_enum;
-                             SIGNAL done   : OUT   STD_LOGIC;
-                             SIGNAL tb_end : OUT   STD_LOGIC;
-                             SIGNAL cnt_en : OUT   STD_LOGIC) IS
-  BEGIN
-    -- The counter operates at zero latency
-    state <= s_idle;
-    done <= '0';
-    tb_end <= '0';
-    cnt_en <= '0';
-    WAIT UNTIL rst='0';
-    WAIT UNTIL rising_edge(clk);
-    -- The cnt_val may be asserted for every active in_ready, but als support
-    -- cnt_val not asserted for every asserted in_ready.
-
-    ----------------------------------------------------------------------------
-    -- Interval 1
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_both_active;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 2
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_pull_down_out_ready;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 3
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_pull_down_cnt_en;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1 cycle
-    cnt_en <= '0';
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 2 cycle
-    cnt_en <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 3 cycle
-    cnt_en <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 4 cycle
-    cnt_en <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 5 cycle
-    cnt_en <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 6 cycle
-    cnt_en <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 7 cycle
-    cnt_en <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 4
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_toggle_out_ready;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 5
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_toggle_cnt_en;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1-1 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1-2 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    -- . 2-1 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 2-2 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1-3 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    -- . 3-1 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    -- . 2-3 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    -- . 3-2 toggle
-    cnt_en <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      cnt_en <= '1';
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    ----------------------------------------------------------------------------
-    -- Interval 6
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_toggle_both;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    FOR I IN 1 TO c_dp_nof_both LOOP
-      cnt_en <= '0';
-      FOR J IN 1 TO I LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-      cnt_en <= '1';
-      FOR J IN I TO c_dp_nof_both LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    END LOOP;
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 7
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_pulse_cnt_en;
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    FOR I IN 1 TO 15 LOOP
-      FOR J IN 1 TO 15 LOOP
-        cnt_en <= '0';
-        FOR K IN 1 TO I LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-        cnt_en <= '1';
-        WAIT UNTIL rising_edge(clk);
-      END LOOP;
-      FOR J IN 1 TO 20 LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    END LOOP;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    ----------------------------------------------------------------------------
-    -- Interval 8
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_chirp_out_ready;
-    cnt_en <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    ----------------------------------------------------------------------------
-    -- Interval 9
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_random;
-    cnt_en <= '1';
-    
-    FOR I IN 0 TO c_dp_sync_interval - c_dp_test_interval LOOP
-      lfsr <= func_common_random(lfsr);
-      cnt_en <= lfsr(lfsr'HIGH);
-      WAIT UNTIL rising_edge(clk);
-    END LOOP;
-    
-    ----------------------------------------------------------------------------
-    -- Done
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    state <= s_done;
-    WAIT UNTIL rising_edge(clk);
-    cnt_en <= '0';
-    
-    -- pulse done
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    done <= '1';
-    WAIT UNTIL rising_edge(clk);
-    done <= '0';
-    
-    ----------------------------------------------------------------------------
-    -- Testbench end
-    ----------------------------------------------------------------------------
-    -- set tb_end
-    WAIT UNTIL sync='1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    tb_end <= '1';
-    WAIT;
-  END proc_dp_count_en;
-
-
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Stimuli for out_ready
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_out_ready(SIGNAL rst       : IN    STD_LOGIC;
-                              SIGNAL clk       : IN    STD_LOGIC;
-                              SIGNAL sync      : IN    STD_LOGIC;
-                              SIGNAL lfsr      : INOUT STD_LOGIC_VECTOR;
-                              SIGNAL out_ready : OUT   STD_LOGIC) IS
-  BEGIN
-    out_ready <= '0';
-    WAIT UNTIL rst='0';
-    WAIT UNTIL rising_edge(clk);
-
-    ----------------------------------------------------------------------------
-    -- Interval 1 : Assert both cnt_en and out_ready
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 2 : Make out_ready low for 1 or more cycles
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1 cycle
-    out_ready <= '0';
-    WAIT UNTIL rising_edge(clk);
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 2 cycle
-    out_ready <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 3 cycle
-    out_ready <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 4 cycle
-    out_ready <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 5 cycle
-    out_ready <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 6 cycle
-    out_ready <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    -- . 7 cycle
-    out_ready <= '0';
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    WAIT UNTIL rising_edge(clk);
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    ----------------------------------------------------------------------------
-    -- Interval 3
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 4 : Toggle out_ready for 1 or more cycles
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1-1 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1-2 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 2-1 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 2-2 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 1-3 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    -- . 3-1 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 2-3 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . 3-2 toggle
-    out_ready <= '0';
-    FOR I IN 1 TO c_dp_nof_toggle LOOP
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '0';
-      WAIT UNTIL rising_edge(clk);
-      WAIT UNTIL rising_edge(clk);
-      out_ready <= '1';
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 5
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 6
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    FOR I IN 1 TO c_dp_nof_both LOOP
-      out_ready <= '0';
-      FOR J IN I TO c_dp_nof_both LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-      out_ready <= '1';
-      FOR J IN 1 TO I LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    END LOOP;
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 7
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    ----------------------------------------------------------------------------
-    -- Interval 8 : Chirp out_ready
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-
-    -- . slow toggle
-    out_ready <= '0';
-    FOR I IN 0 TO c_dp_nof_toggle LOOP
-      out_ready <= '0';
-      FOR J IN 0 TO I LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-      out_ready <= '1';
-      FOR J IN 0 TO I LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    END LOOP;
-    out_ready <= '1';
-    FOR I IN 0 TO c_dp_test_interval LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    ----------------------------------------------------------------------------
-    -- Interval 9 : Random
-    ----------------------------------------------------------------------------
-    WAIT UNTIL sync='1';
-    out_ready <= '1';
-    
-    FOR I IN 0 TO c_dp_sync_interval - c_dp_test_interval LOOP
-      lfsr <= func_common_random(lfsr);
-      out_ready <= lfsr(lfsr'HIGH);
-      WAIT UNTIL rising_edge(clk);
-    END LOOP;
-    
-    ----------------------------------------------------------------------------
-    -- Done
-    ----------------------------------------------------------------------------
-    WAIT;
-  END proc_dp_out_ready;
-
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: DUT output verify enable
-  ------------------------------------------------------------------------------
- 
-  -- Fixed delay until verify_en active
-  PROCEDURE proc_dp_verify_en(CONSTANT c_delay   : IN  NATURAL;
-                              SIGNAL   rst       : IN  STD_LOGIC;
-                              SIGNAL   clk       : IN  STD_LOGIC;
-                              SIGNAL   sync      : IN  STD_LOGIC;
-                              SIGNAL   verify_en : OUT STD_LOGIC) IS
-  BEGIN
-    verify_en <= '0';
-    WAIT UNTIL rst='0';
-    WAIT UNTIL rising_edge(clk);
-    
-    WAIT UNTIL sync='1';
-    -- Use c_delay delay before enabling the p_verify.
-    FOR I IN 0 TO c_delay LOOP WAIT UNTIL rising_edge(clk); END LOOP;
-    
-    verify_en <= '1';
-    WAIT;
-  END proc_dp_verify_en;
-  
-  
-  -- Dynamicly depend on first valid data to make verify_en active
-  PROCEDURE proc_dp_verify_en(CONSTANT c_continuous : IN  BOOLEAN;
-                              SIGNAL   clk          : IN  STD_LOGIC;
-                              SIGNAL   valid        : IN  STD_LOGIC;
-                              SIGNAL   sop          : IN  STD_LOGIC;
-                              SIGNAL   eop          : IN  STD_LOGIC;
-                              SIGNAL   verify_en    : OUT STD_LOGIC) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF c_continuous=TRUE THEN
-        -- Verify across frames (so enable data verify after the first data has been output)
-        IF valid='1' THEN
-          verify_en <= '1';
-        END IF;
-      ELSE
-        -- Verify only per frame (so re-enable data verify after the every sop)
-        IF eop='1' THEN
-          verify_en <= '0';
-        ELSIF sop='1' THEN
-          verify_en <= '1';
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_en;
-  
-  -- Run and verify for some cycles
-  PROCEDURE proc_dp_verify_run_some_cycles(CONSTANT nof_pre_clk    : IN   NATURAL;
-                                           CONSTANT nof_verify_clk : IN   NATURAL;
-                                           CONSTANT nof_post_clk   : IN   NATURAL;
-                                           SIGNAL   clk            : IN   STD_LOGIC;
-                                           SIGNAL   verify_en      : OUT  STD_LOGIC) IS
-  BEGIN
-    proc_common_wait_some_cycles(clk, nof_pre_clk);
-    verify_en <= '1';
-    proc_common_wait_some_cycles(clk, nof_verify_clk);
-    verify_en <= '0';
-    proc_common_wait_some_cycles(clk, nof_post_clk);
-  END proc_dp_verify_run_some_cycles;
-    
-
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the expected value
-  ------------------------------------------------------------------------------
-  --  e.g. to check that a test has ran at all
-  PROCEDURE proc_dp_verify_value(CONSTANT c_str : IN STRING;
-                                 CONSTANT mode  : IN t_dp_value_enum;
-                                 SIGNAL   clk   : IN STD_LOGIC;
-                                 SIGNAL   en    : IN STD_LOGIC;
-                                 SIGNAL   exp   : IN STD_LOGIC_VECTOR;  
-                                 SIGNAL   res   : IN STD_LOGIC_VECTOR) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF en='1' THEN
-        IF mode = e_equal AND UNSIGNED(res) /= UNSIGNED(exp) THEN
-          REPORT "DP : Wrong " & c_str & " result value" SEVERITY ERROR;
-        END IF;
-        IF mode = e_at_least AND UNSIGNED(res) < UNSIGNED(exp) THEN
-          REPORT "DP : Wrong " & c_str & " result value too small" SEVERITY ERROR;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_value;
-
-  PROCEDURE proc_dp_verify_value(CONSTANT mode : IN t_dp_value_enum;
-                                 SIGNAL   clk  : IN STD_LOGIC;
-                                 SIGNAL   en   : IN STD_LOGIC;
-                                 SIGNAL   exp  : IN STD_LOGIC_VECTOR;  
-                                 SIGNAL   res  : IN STD_LOGIC_VECTOR) IS
-  BEGIN
-    proc_dp_verify_value("", mode, clk, en, exp, res);
-  END proc_dp_verify_value;
-  
-  PROCEDURE proc_dp_verify_value(CONSTANT c_str : IN STRING;
-                                 SIGNAL   clk   : IN STD_LOGIC;
-                                 SIGNAL   en    : IN STD_LOGIC;
-                                 SIGNAL   exp   : IN STD_LOGIC;  
-                                 SIGNAL   res   : IN STD_LOGIC) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF en='1' THEN
-        IF res /= exp THEN
-          REPORT "DP : Wrong " & c_str & " result value" SEVERITY ERROR;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_value;
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify output global and local BSN
-  ------------------------------------------------------------------------------
-  -- Verify BSN:
-  -- . incrementing or replicated global BSN
-  -- . incrementing local BSN that starts at 1
-  --
-  --               _              _              _              _             
-  --  sync      __| |____________| |____________| |____________| |____________
-  --               _    _    _    _    _    _    _    _    _    _    _    _
-  --   sop      __| |__| |__| |__| |__| |__| |__| |__| |__| |__| |__| |__| |__  c_block_per_sync = 3
-  --
-  -- c_use_local_bsn = FALSE:
-  --                                                                            c_nof_replicated_global_bsn = 1
-  --        bsn    3    4    5    6    7    8    9    10   11   12   13   14    c_global_bsn_increment = 1
-  --        bsn    3    5    7    9   11   13   15    17   19   21   22   23    c_global_bsn_increment = 2
-  --
-  -- c_use_local_bsn = TRUE:
-  --
-  -- global bsn    3              4              5               6              c_global_bsn_increment = 1, c_nof_replicated_global_bsn = 1
-  -- global bsn    3              6              9              12              c_global_bsn_increment = 3, c_nof_replicated_global_bsn = 1
-  -- global bsn    3              3              9               9              c_global_bsn_increment = 6, c_nof_replicated_global_bsn = 2
-  --  local bsn    -    1    2    -    1    2    -    1    2     -    1    2    range 1:c_block_per_sync-1
-  --        
-  -- The verify_en should initially be set to '0' and gets enabled when
-  -- sufficient BSN history is available to do the verification.
-  --
-  PROCEDURE proc_dp_verify_bsn(CONSTANT c_use_local_bsn             : IN    BOOLEAN;    -- use local BSN or only use global BSN
-                               CONSTANT c_global_bsn_increment      : IN    POSITIVE;   -- increment per global BSN
-                               CONSTANT c_nof_replicated_global_bsn : IN    POSITIVE;   -- number of replicated global BSN
-                               CONSTANT c_block_per_sync            : IN    POSITIVE;   -- of sop/eop blocks per sync interval
-                               SIGNAL   clk                         : IN    STD_LOGIC;
-                               SIGNAL   out_sync                    : IN    STD_LOGIC;
-                               SIGNAL   out_sop                     : IN    STD_LOGIC;
-                               SIGNAL   out_bsn                     : IN    STD_LOGIC_VECTOR;
-                               SIGNAL   verify_en                   : INOUT STD_LOGIC;  -- initialize '0', becomes '1' when bsn verification starts
-                               SIGNAL   cnt_replicated_global_bsn   : INOUT NATURAL;
-                               SIGNAL   prev_out_bsn_global         : INOUT STD_LOGIC_VECTOR;
-                               SIGNAL   prev_out_bsn_local          : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      -- out_sop must be active, because only then out_bsn will differ from the previous out_bsn
-      IF out_sop='1' THEN
-        IF c_use_local_bsn=FALSE THEN
-          ------------------------------------------------------------------
-          -- Only use global BSN
-          ------------------------------------------------------------------
-          prev_out_bsn_global <= out_bsn;
-          -- verify
-          IF  out_sync='1' THEN
-            verify_en <= '1';
-          END IF;
-          IF verify_en='1' THEN
-            ASSERT UNSIGNED(out_bsn) = UNSIGNED(prev_out_bsn_global)+c_global_bsn_increment REPORT "DP : Wrong BSN increment" SEVERITY ERROR;
-          END IF;
-        ELSE
-          ------------------------------------------------------------------
-          -- Use global and local BSN
-          ------------------------------------------------------------------
-          IF out_sync='1' THEN
-            prev_out_bsn_global <= out_bsn;
-            IF UNSIGNED(out_bsn) /= UNSIGNED(prev_out_bsn_global) THEN
-              verify_en <= '1';                -- wait until after last replicated global bsn
-              cnt_replicated_global_bsn <= 0;
-            ELSE
-              cnt_replicated_global_bsn <= cnt_replicated_global_bsn + 1;
-            END IF;
-            prev_out_bsn_local <= TO_UVEC(0, prev_out_bsn_global'LENGTH);
-          ELSE
-            prev_out_bsn_local <= out_bsn;
-          END IF;
-          -- verify
-          IF verify_en='1' THEN
-            IF out_sync='1' THEN
-              IF UNSIGNED(out_bsn) /= UNSIGNED(prev_out_bsn_global) THEN
-                ASSERT cnt_replicated_global_bsn=c_nof_replicated_global_bsn-1 REPORT "DP : Wrong number of replicated global BSN" SEVERITY ERROR;
-                ASSERT UNSIGNED(out_bsn)=UNSIGNED(prev_out_bsn_global)+c_global_bsn_increment REPORT "DP : Wrong global BSN increment" SEVERITY ERROR;
-              ELSE
-                ASSERT UNSIGNED(out_bsn)=UNSIGNED(prev_out_bsn_global) REPORT "DP : Wrong replicated global BSN" SEVERITY ERROR;
-              END IF;
-              ASSERT UNSIGNED(prev_out_bsn_local)=c_block_per_sync-1 REPORT "DP : Wrong last local BSN in sync interval" SEVERITY ERROR;
-            ELSE
-              ASSERT UNSIGNED(out_bsn)=UNSIGNED(prev_out_bsn_local)+1 REPORT "DP : Wrong local BSN increment" SEVERITY ERROR;
-            END IF;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_bsn;
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output data
-  ------------------------------------------------------------------------------
-  
-  -- Verify incrementing data
-  -- . wrap at c_out_data_max when >0, else no wrap when c_out_data_max=0
-  -- . default increment by 1, but also allow an increment by c_out_data_gap
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_ready_latency : IN    NATURAL;
-                                CONSTANT c_out_data_max  : IN    UNSIGNED;
-                                CONSTANT c_out_data_gap  : IN    UNSIGNED;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_ready       : IN    STD_LOGIC;  -- only needed when c_ready_latency = 0
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      -- out_val must be active, because only the out_data will it differ from the previous out_data
-      IF out_val='1' THEN
-        -- for ready_latency > 0 out_val indicates new data
-        -- for ready_latency = 0 out_val only indicates new data when it is confirmed by out_ready
-        IF c_ready_latency/=0 OR (c_ready_latency=0 AND out_ready='1') THEN
-          IF c_out_data_max=0 THEN
-            prev_out_data <= out_data;                           -- no wrap detection
-          ELSIF UNSIGNED(out_data)<c_out_data_max THEN
-            prev_out_data <= out_data;                           -- no wrap
-          ELSE
-            prev_out_data <= TO_SVEC(-1, prev_out_data'LENGTH);  -- do wrap
-          END IF;
-          IF verify_en='1' THEN
-            IF UNSIGNED(out_data) /= UNSIGNED(prev_out_data)+1 AND                               -- check increment +1
-               UNSIGNED(out_data) /= UNSIGNED(prev_out_data)+c_out_data_gap AND                  -- increment +c_out_data_gap
-               UNSIGNED(out_data) /= UNSIGNED(prev_out_data)+c_out_data_gap-c_out_data_max THEN  -- increment +c_out_data_gap wrapped
-              REPORT "DP : Wrong out_data " & c_str & " count" SEVERITY ERROR;
-            END IF;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_data;
-  
-  -- Verify incrementing data that wraps in range 0 ... c_out_data_max
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_ready_latency : IN    NATURAL;
-                                CONSTANT c_out_data_max  : IN    UNSIGNED;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_ready       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    proc_dp_verify_data(c_str, c_ready_latency, c_out_data_max, TO_UNSIGNED(1,1), clk, verify_en, out_ready, out_val, out_data, prev_out_data);
-  END proc_dp_verify_data;
-  
-  -- Verify incrementing data
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_ready_latency : IN    NATURAL;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_ready       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    proc_dp_verify_data(c_str, c_ready_latency, TO_UNSIGNED(0,1), TO_UNSIGNED(1,1), clk, verify_en, out_ready, out_val, out_data, prev_out_data);
-  END proc_dp_verify_data;
-  
-  -- Verify incrementing data with RL > 0 or no flow control
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_out_data_max  : IN    UNSIGNED;
-                                CONSTANT c_out_data_gap  : IN    UNSIGNED;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    -- Use out_val as void signal to pass on to unused out_ready, because a signal input can not connect a constant or variable
-    proc_dp_verify_data(c_str, 1, c_out_data_max, c_out_data_gap, clk, verify_en, out_val, out_val, out_data, prev_out_data);
-  END proc_dp_verify_data;
-  
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_out_data_max  : IN    NATURAL;
-                                CONSTANT c_out_data_gap  : IN    NATURAL;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-    CONSTANT c_data_w : NATURAL := out_data'LENGTH;
-  BEGIN
-    proc_dp_verify_data(c_str, TO_UNSIGNED(c_out_data_max, c_data_w), TO_UNSIGNED(c_out_data_gap, c_data_w), clk, verify_en, out_val, out_data, prev_out_data);
-  END proc_dp_verify_data;
-  
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                CONSTANT c_out_data_max  : IN    NATURAL;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-    CONSTANT c_data_w : NATURAL := out_data'LENGTH;
-  BEGIN
-    proc_dp_verify_data(c_str, TO_UNSIGNED(c_out_data_max, c_data_w), TO_UNSIGNED(1, 1), clk, verify_en, out_val, out_data, prev_out_data);
-  END proc_dp_verify_data;
-  
-  PROCEDURE proc_dp_verify_data(CONSTANT c_str           : IN    STRING;
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   out_val         : IN    STD_LOGIC;
-                                SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-  BEGIN
-    -- Use out_val as void signal to pass on to unused out_ready, because a signal input can not connect a constant or variable
-    proc_dp_verify_data(c_str, 1, TO_UNSIGNED(0,1), TO_UNSIGNED(1,1), clk, verify_en, out_val, out_val, out_data, prev_out_data);
-  END proc_dp_verify_data;
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify incrementing symbols in data
-  -- . for c_data_w = c_symbol_w proc_dp_verify_symbols() = proc_dp_verify_data()
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_verify_symbols(CONSTANT c_ready_latency : IN    NATURAL;
-                                   CONSTANT c_data_w        : IN    NATURAL;
-                                   CONSTANT c_symbol_w      : IN    NATURAL;
-                                   SIGNAL   clk             : IN    STD_LOGIC;
-                                   SIGNAL   verify_en       : IN    STD_LOGIC;
-                                   SIGNAL   out_ready       : IN    STD_LOGIC;
-                                   SIGNAL   out_val         : IN    STD_LOGIC;
-                                   SIGNAL   out_eop         : IN    STD_LOGIC;
-                                   SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                   SIGNAL   out_empty       : IN    STD_LOGIC_VECTOR;
-                                   SIGNAL   prev_out_data   : INOUT STD_LOGIC_VECTOR) IS
-    CONSTANT c_nof_symbols_per_data : NATURAL := c_data_w/c_symbol_w;  -- must be an integer
-    CONSTANT c_empty_w              : NATURAL := ceil_log2(c_nof_symbols_per_data);
-    VARIABLE v_data                 : STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0);
-    VARIABLE v_symbol               : STD_LOGIC_VECTOR(c_symbol_w-1 DOWNTO 0);
-    VARIABLE v_empty                : NATURAL;
-  BEGIN
-    IF rising_edge(clk) THEN
-      -- out_val must be active, because only the out_data will it differ from the previous out_data
-      IF out_val='1' THEN
-        -- for ready_latency > 0 out_val indicates new data
-        -- for ready_latency = 0 out_val only indicates new data when it is confirmed by out_ready
-        IF c_ready_latency/=0 OR (c_ready_latency=0 AND out_ready='1') THEN
-          prev_out_data <= out_data;
-          IF verify_en='1' THEN
-            v_data  := prev_out_data(c_data_w-1 DOWNTO 0);
-            FOR I IN 0 TO c_nof_symbols_per_data-1 LOOP
-              v_data((I+1)*c_symbol_w-1 DOWNTO I*c_symbol_w) := INCR_UVEC(v_data((I+1)*c_symbol_w-1 DOWNTO I*c_symbol_w), c_nof_symbols_per_data);  -- increment each symbol
-            END LOOP;
-            IF out_eop='0' THEN
-              IF UNSIGNED(out_data) /= UNSIGNED(v_data) THEN
-                REPORT "DP : Wrong out_data symbols count" SEVERITY ERROR;
-              END IF;
-            ELSE
-              v_empty := TO_UINT(out_empty(c_empty_w-1 DOWNTO 0));
-              IF UNSIGNED(out_data(c_data_w-1 DOWNTO v_empty*c_symbol_w)) /= UNSIGNED(v_data(c_data_w-1 DOWNTO v_empty*c_symbol_w)) THEN
-                REPORT "DP : Wrong out_data symbols count at eop" SEVERITY ERROR;
-              END IF;
-              IF v_empty>0 THEN
-                -- adjust prev_out_data for potentially undefined empty symbols in out_data
-                v_symbol := v_data((v_empty+1)*c_symbol_w-1 DOWNTO v_empty*c_symbol_w);  -- last valid symbol
-                FOR I IN 0 TO c_nof_symbols_per_data-1 LOOP
-                  v_data((I+1)*c_symbol_w-1 DOWNTO I*c_symbol_w) := v_symbol;   -- put the last valid symbol at the end of the v_data
-                  v_symbol := INCR_UVEC(v_symbol, -1);                          -- decrement each symbol towards the beginning of v_data
-                END LOOP;
-                prev_out_data <= v_data;
-              END IF;
-            END IF;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_symbols;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output data with empty
-  -- . account for stream empty
-  -- . support last word replace (e.g. by a CRC instead of the count, or use
-  --   c_last_word=out_data for no replace)
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_verify_data_empty(CONSTANT c_ready_latency : IN    NATURAL;
-                                      CONSTANT c_last_word     : IN    NATURAL;
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   verify_en       : IN    STD_LOGIC;
-                                      SIGNAL   out_ready       : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop_1       : INOUT STD_LOGIC;
-                                      SIGNAL   out_eop_2       : INOUT STD_LOGIC;
-                                      SIGNAL   out_data        : IN    STD_LOGIC_VECTOR;
-                                      SIGNAL   out_data_1      : INOUT STD_LOGIC_VECTOR;
-                                      SIGNAL   out_data_2      : INOUT STD_LOGIC_VECTOR;
-                                      SIGNAL   out_data_3      : INOUT STD_LOGIC_VECTOR;
-                                      SIGNAL   out_empty       : IN    STD_LOGIC_VECTOR;
-                                      SIGNAL   out_empty_1     : INOUT STD_LOGIC_VECTOR) IS
-    VARIABLE v_last_word    : STD_LOGIC_VECTOR(out_data'RANGE);
-    VARIABLE v_ref_data     : STD_LOGIC_VECTOR(out_data'RANGE);
-    VARIABLE v_empty_data   : STD_LOGIC_VECTOR(out_data'RANGE);
-  BEGIN
-    IF rising_edge(clk) THEN
-      -- out_val must be active, because only then out_data will differ from the previous out_data
-      IF out_val='1' THEN
-        -- for ready_latency > 0 out_val indicates new data
-        -- for ready_latency = 0 out_val only indicates new data when it is confirmed by out_ready
-        IF c_ready_latency/=0 OR (c_ready_latency=0 AND out_ready='1') THEN
-          -- default expected data
-          out_data_1  <= out_data;
-          out_data_2  <= out_data_1;
-          out_data_3  <= out_data_2;
-          out_empty_1 <= out_empty;
-          out_eop_1   <= out_eop;
-          out_eop_2   <= out_eop_1;
-          IF verify_en='1' THEN
-            -- assume sufficient valid cycles between eop and sop, so no need to check for out_sop with regard to eop empty
-            IF out_eop='0' AND out_eop_1='0' AND out_eop_2='0'THEN
-              -- verify out_data from eop-n to eop-2 and from eop+1 to eop+n, n>2
-              v_ref_data := INCR_UVEC(out_data_2, 1);
-              IF UNSIGNED(out_data_1) /= UNSIGNED(v_ref_data) THEN
-                REPORT "DP : Wrong out_data count" SEVERITY ERROR;
-              END IF;
-            ELSE
-              -- the empty and crc replace affect data at eop_1 and eop, so need to check data from eop-2 to eop-1 to eop to eop+1
-              v_last_word := TO_UVEC(c_last_word, out_data'LENGTH);
-              IF out_eop='1' THEN
-                -- verify out_data at eop
-                CASE TO_INTEGER(UNSIGNED(out_empty)) IS
-                  WHEN 0 => v_empty_data := v_last_word;
-                  WHEN 1 => v_empty_data := v_last_word(3*c_byte_w-1 DOWNTO 0) & c_slv0(1*c_byte_w-1 DOWNTO 0);
-                  WHEN 2 => v_empty_data := v_last_word(2*c_byte_w-1 DOWNTO 0) & c_slv0(2*c_byte_w-1 DOWNTO 0);
-                  WHEN 3 => v_empty_data := v_last_word(1*c_byte_w-1 DOWNTO 0) & c_slv0(3*c_byte_w-1 DOWNTO 0);
-                  WHEN OTHERS => NULL;
-                END CASE;
-                IF UNSIGNED(out_data) /= UNSIGNED(v_empty_data) THEN
-                  REPORT "DP : Wrong out_data count at eop" SEVERITY ERROR;
-                END IF;
-              ELSIF out_eop_1='1' THEN
-                -- verify out_data from eop-2 to eop-1
-                v_ref_data := INCR_UVEC(out_data_3, 1);
-                CASE TO_INTEGER(UNSIGNED(out_empty_1)) IS
-                  WHEN 0 => v_empty_data := v_ref_data;
-                  WHEN 1 => v_empty_data := v_ref_data(4*c_byte_w-1 DOWNTO 1*c_byte_w) & v_last_word(4*c_byte_w-1 DOWNTO 3*c_byte_w);
-                  WHEN 2 => v_empty_data := v_ref_data(4*c_byte_w-1 DOWNTO 2*c_byte_w) & v_last_word(4*c_byte_w-1 DOWNTO 2*c_byte_w);
-                  WHEN 3 => v_empty_data := v_ref_data(4*c_byte_w-1 DOWNTO 3*c_byte_w) & v_last_word(4*c_byte_w-1 DOWNTO 1*c_byte_w);
-                  WHEN OTHERS => NULL;
-                END CASE;
-                IF UNSIGNED(out_data_2) /= UNSIGNED(v_empty_data) THEN
-                  REPORT "DP : Wrong out_data count at eop-1" SEVERITY ERROR;
-                END IF;
-                -- verify out_data from eop-2 to eop+1
-                v_ref_data := INCR_UVEC(out_data_3, 3);
-                IF UNSIGNED(out_data) /= UNSIGNED(v_ref_data) THEN
-                  REPORT "DP : Wrong out_data count at eop+1" SEVERITY ERROR;
-                END IF;
-              END IF;
-            END IF;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_data_empty;  
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output other SOSI data
-  -- . Suited to verify the empty, error, channel fields assuming that these
-  --   are treated in the same way in parallel to the SOSI data.
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_verify_other_sosi(CONSTANT c_str       : IN STRING;
-                                      CONSTANT c_exp_data  : IN STD_LOGIC_VECTOR;    -- use constant to support assignment via FUNCTION return value
-                                      SIGNAL   clk         : IN STD_LOGIC;
-                                      SIGNAL   verify_en   : IN STD_LOGIC;
-                                      SIGNAL   res_data    : IN STD_LOGIC_VECTOR) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF verify_en='1' THEN
-        IF    c_str="bsn" THEN
-          IF UNSIGNED(c_exp_data(c_dp_bsn_w-1 DOWNTO 0))/=UNSIGNED(res_data(c_dp_bsn_w-1 DOWNTO 0)) THEN
-            REPORT "DP : Wrong sosi.bsn value" SEVERITY ERROR;
-          END IF;
-        ELSIF c_str="empty" THEN
-          IF UNSIGNED(c_exp_data(c_dp_empty_w-1 DOWNTO 0))/=UNSIGNED(res_data(c_dp_empty_w-1 DOWNTO 0)) THEN
-            REPORT "DP : Wrong sosi.empty value" SEVERITY ERROR;
-          END IF;
-        ELSIF c_str="channel" THEN
-          IF UNSIGNED(c_exp_data(c_dp_channel_user_w-1 DOWNTO 0))/=UNSIGNED(res_data(c_dp_channel_user_w-1 DOWNTO 0)) THEN
-            REPORT "DP : Wrong sosi.channel value" SEVERITY ERROR;
-          END IF;
-        ELSIF c_str="error" THEN
-          IF UNSIGNED(c_exp_data(c_dp_error_w-1 DOWNTO 0))/=UNSIGNED(res_data(c_dp_error_w-1 DOWNTO 0)) THEN
-            REPORT "DP : Wrong sosi.error value" SEVERITY ERROR;
-          END IF;
-        ELSE
-          REPORT "proc_dp_verify_other_sosi : Unknown sosi." & c_str & "field" SEVERITY FAILURE;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_other_sosi;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output valid
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_verify_valid(CONSTANT c_ready_latency : IN    NATURAL;
-                                 SIGNAL   clk             : IN    STD_LOGIC;
-                                 SIGNAL   verify_en       : IN    STD_LOGIC;
-                                 SIGNAL   out_ready       : IN    STD_LOGIC;
-                                 SIGNAL   prev_out_ready  : INOUT STD_LOGIC_VECTOR;
-                                 SIGNAL   out_val         : IN    STD_LOGIC) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      -- for ready_latency > 0 out_val may only be asserted after out_ready
-      -- for ready_latency = 0 out_val may always be asserted
-      prev_out_ready <= (prev_out_ready'RANGE=>'0');
-      IF c_ready_latency/=0 THEN
-        IF c_ready_latency=1 THEN
-          prev_out_ready(0) <= out_ready;
-        ELSE
-          prev_out_ready    <= out_ready & prev_out_ready(0 TO c_ready_latency-1);
-        END IF;
-        IF verify_en='1' AND out_val='1' THEN
-          IF prev_out_ready(c_ready_latency-1)/='1' THEN
-            REPORT "DP : Wrong ready latency between out_ready and out_val" SEVERITY ERROR;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_valid;
-  
-  PROCEDURE proc_dp_verify_valid(SIGNAL   clk             : IN    STD_LOGIC;
-                                 SIGNAL   verify_en       : IN    STD_LOGIC;
-                                 SIGNAL   out_ready       : IN    STD_LOGIC;
-                                 SIGNAL   prev_out_ready  : INOUT STD_LOGIC;
-                                 SIGNAL   out_val         : IN    STD_LOGIC) IS
-  BEGIN
-    -- Can not reuse:
-    --   proc_dp_verify_valid(1, clk, verify_en, out_ready, prev_out_ready, out_val);
-    -- because prev_out_ready needs to map from STD_LOGIC to STD_LOGIC_VECTOR. Therefore copy paste code for RL=1:
-    IF rising_edge(clk) THEN
-      -- for ready_latency = 1 out_val may only be asserted after out_ready
-      prev_out_ready <= out_ready;
-      IF verify_en='1' AND out_val='1' THEN
-        IF prev_out_ready/='1' THEN
-          REPORT "DP : Wrong ready latency between out_ready and out_val" SEVERITY ERROR;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_valid;
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output sync
-  -- . sync is defined such that it can only be active at sop
-  -- . assume that the sync occures priodically at bsn MOD c_sync_period = c_sync_offset
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_verify_sync(CONSTANT c_sync_period   : IN    NATURAL;    -- BSN sync period
-                                CONSTANT c_sync_offset   : IN    NATURAL;    -- BSN sync offset
-                                SIGNAL   clk             : IN    STD_LOGIC;
-                                SIGNAL   verify_en       : IN    STD_LOGIC;
-                                SIGNAL   sync            : IN    STD_LOGIC;
-                                SIGNAL   sop             : IN    STD_LOGIC;
-                                SIGNAL   bsn             : IN    STD_LOGIC_VECTOR) IS
-    CONSTANT c_bsn_w         : NATURAL := sel_a_b(bsn'LENGTH>31, 31, bsn'LENGTH);  -- use maximally 31 bit of BSN slv to allow calculations with integers
-    VARIABLE v_expected_sync : BOOLEAN;
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF verify_en='1' THEN
-        v_expected_sync := (TO_UINT(bsn(c_bsn_w-1 DOWNTO 0))-c_sync_offset) MOD c_sync_period = 0;
-        -- Check for unexpected sync
-        IF sync='1' THEN
-          ASSERT v_expected_sync = TRUE
-            REPORT "Error: Unexpected sync at BSN" SEVERITY ERROR;
-          ASSERT sop = '1'
-            REPORT "Error: Unexpected sync at inactive sop" SEVERITY ERROR;
-        END IF;
-        -- Check for missing sync
-        IF sop='1' AND v_expected_sync=TRUE THEN
-          ASSERT sync = '1'
-            REPORT "Error: Missing sync" SEVERITY ERROR;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_sync;
-  
-
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output sop and eop
-  ------------------------------------------------------------------------------
-  -- sop and eop in pairs, valid during packet and invalid between packets
-  PROCEDURE proc_dp_verify_sop_and_eop(CONSTANT c_ready_latency : IN    NATURAL;
-                                       CONSTANT c_verify_valid  : IN    BOOLEAN;
-                                       SIGNAL   clk             : IN    STD_LOGIC;
-                                       SIGNAL   out_ready       : IN    STD_LOGIC;
-                                       SIGNAL   out_val         : IN    STD_LOGIC;
-                                       SIGNAL   out_sop         : IN    STD_LOGIC;
-                                       SIGNAL   out_eop         : IN    STD_LOGIC;
-                                       SIGNAL   hold_sop        : INOUT STD_LOGIC) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF out_val='0' THEN
-        IF out_sop='1' THEN REPORT "DP : Wrong active sop during invalid" SEVERITY ERROR; END IF;
-        IF out_eop='1' THEN REPORT "DP : Wrong active eop during invalid" SEVERITY ERROR; END IF;
-      ELSE
-        -- for ready_latency > 0 out_val indicates new data
-        -- for ready_latency = 0 out_val only indicates new data when it is confirmed by out_ready
-        IF c_ready_latency/=0 OR (c_ready_latency=0 AND out_ready='1') THEN
-          IF out_sop='1' THEN
-            hold_sop <= '1';
-            IF hold_sop='1' THEN
-              REPORT "DP : Unexpected sop without eop" SEVERITY ERROR;
-            END IF;
-          END IF;
-          IF out_eop='1' THEN
-            hold_sop <= '0';
-            IF hold_sop='0' AND out_sop='0' THEN
-              REPORT "DP : Unexpected eop without sop" SEVERITY ERROR;
-            END IF;
-          END IF;
-          -- out_val='1'
-          IF c_verify_valid=TRUE AND out_sop='0' AND hold_sop='0' THEN
-            REPORT "DP : Unexpected valid in gap between eop and sop" SEVERITY ERROR;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_sop_and_eop;
-  
-  PROCEDURE proc_dp_verify_sop_and_eop(CONSTANT c_ready_latency : IN    NATURAL;
-                                       SIGNAL   clk             : IN    STD_LOGIC;
-                                       SIGNAL   out_ready       : IN    STD_LOGIC;
-                                       SIGNAL   out_val         : IN    STD_LOGIC;
-                                       SIGNAL   out_sop         : IN    STD_LOGIC;
-                                       SIGNAL   out_eop         : IN    STD_LOGIC;
-                                       SIGNAL   hold_sop        : INOUT STD_LOGIC) IS
-  BEGIN
-    proc_dp_verify_sop_and_eop(c_ready_latency, TRUE, clk, out_ready, out_val, out_sop, out_eop, hold_sop);
-  END proc_dp_verify_sop_and_eop;
-  
-  PROCEDURE proc_dp_verify_sop_and_eop(SIGNAL   clk      : IN    STD_LOGIC;
-                                       SIGNAL   out_val  : IN    STD_LOGIC;
-                                       SIGNAL   out_sop  : IN    STD_LOGIC;
-                                       SIGNAL   out_eop  : IN    STD_LOGIC;
-                                       SIGNAL   hold_sop : INOUT STD_LOGIC) IS
-  BEGIN
-    -- Use out_val as void signal to pass on to unused out_ready, because a signal input can not connect a constant or variable
-    proc_dp_verify_sop_and_eop(1, TRUE, clk, out_val, out_val, out_sop, out_eop, hold_sop);
-  END proc_dp_verify_sop_and_eop;
-  
-  PROCEDURE proc_dp_verify_block_size(CONSTANT c_ready_latency : IN    NATURAL;
-                                      SIGNAL   alt_size        : IN    NATURAL;     -- alternative size
-                                      SIGNAL   exp_size        : IN    NATURAL;     -- expected size 
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   out_ready       : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_sop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   cnt_size        : INOUT NATURAL) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF out_val='1' THEN
-        -- for ready_latency > 0 out_val indicates new data
-        -- for ready_latency = 0 out_val only indicates new data when it is confirmed by out_ready
-        IF c_ready_latency/=0 OR (c_ready_latency=0 AND out_ready='1') THEN
-          IF out_sop='1' THEN
-            cnt_size <= 1;
-          ELSIF out_eop='1' THEN
-            cnt_size <= 0;
-            IF cnt_size/=alt_size-1 AND cnt_size/=exp_size-1 THEN
-              REPORT "DP : Unexpected block size" SEVERITY ERROR;
-            END IF;
-          ELSE
-            cnt_size <= cnt_size+1;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_block_size;
-  
-  PROCEDURE proc_dp_verify_block_size(CONSTANT c_ready_latency : IN    NATURAL;
-                                      SIGNAL   exp_size        : IN    NATURAL;
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   out_ready       : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_sop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   cnt_size        : INOUT NATURAL) IS
-  BEGIN
-    proc_dp_verify_block_size(c_ready_latency, exp_size, exp_size, clk, out_ready, out_val, out_sop, out_eop, cnt_size);
-  END proc_dp_verify_block_size;
-    
-  PROCEDURE proc_dp_verify_block_size(SIGNAL   alt_size        : IN    NATURAL;     -- alternative size
-                                      SIGNAL   exp_size        : IN    NATURAL;     -- expected size   
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_sop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   cnt_size        : INOUT NATURAL) IS
-  BEGIN
-    -- Use out_val as void signal to pass on to unused out_ready, because a signal input can not connect a constant or variable
-    proc_dp_verify_block_size(1, alt_size, exp_size, clk, out_val, out_val, out_sop, out_eop, cnt_size);
-  END proc_dp_verify_block_size;
-  
-  PROCEDURE proc_dp_verify_block_size(SIGNAL   exp_size        : IN    NATURAL;
-                                      SIGNAL   clk             : IN    STD_LOGIC;
-                                      SIGNAL   out_val         : IN    STD_LOGIC;
-                                      SIGNAL   out_sop         : IN    STD_LOGIC;
-                                      SIGNAL   out_eop         : IN    STD_LOGIC;
-                                      SIGNAL   cnt_size        : INOUT NATURAL) IS
-  BEGIN
-    -- Use out_val as void signal to pass on to unused out_ready, because a signal input can not connect a constant or variable
-    proc_dp_verify_block_size(1, exp_size, exp_size, clk, out_val, out_val, out_sop, out_eop, cnt_size);
-  END proc_dp_verify_block_size;
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output invalid between frames
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_verify_gap_invalid(SIGNAL clk     : IN    STD_LOGIC;
-                                       SIGNAL in_val  : IN    STD_LOGIC;
-                                       SIGNAL in_sop  : IN    STD_LOGIC;
-                                       SIGNAL in_eop  : IN    STD_LOGIC;
-                                       SIGNAL out_gap : INOUT STD_LOGIC) IS
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF in_eop='1' THEN
-        out_gap <= '1';
-      ELSIF in_sop='1' THEN
-        out_gap <= '0';
-      ELSIF in_val='1' AND out_gap='1' THEN
-        REPORT "DP : Wrong valid in gap between eop and sop" SEVERITY ERROR;
-      END IF;
-    END IF;
-  END proc_dp_verify_gap_invalid;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Verify the DUT output control (use for sop, eop)
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_verify_ctrl(CONSTANT c_offset  : IN NATURAL;
-                                CONSTANT c_period  : IN NATURAL;
-                                CONSTANT c_str     : IN STRING;
-                                SIGNAL   clk       : IN STD_LOGIC;
-                                SIGNAL   verify_en : IN STD_LOGIC;
-                                SIGNAL   data      : IN STD_LOGIC_VECTOR;
-                                SIGNAL   valid     : IN STD_LOGIC;
-                                SIGNAL   ctrl      : IN STD_LOGIC) IS
-    VARIABLE v_data : INTEGER;
-  BEGIN
-    IF rising_edge(clk) THEN
-      IF verify_en='1' THEN
-        v_data := TO_UINT(data);
-        IF ((v_data-c_offset) MOD c_period)=0 THEN
-          IF valid='1' AND ctrl/='1' THEN
-            REPORT "DP : Wrong data control, missing " & c_str SEVERITY ERROR;
-          END IF;
-        ELSE
-          IF ctrl='1' THEN
-            REPORT "DP : Wrong data control, unexpected " & c_str SEVERITY ERROR;
-          END IF;
-        END IF;
-      END IF;
-    END IF;
-  END proc_dp_verify_ctrl;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Wait for stream valid
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_stream_valid(SIGNAL clk      : IN  STD_LOGIC;
-                                 SIGNAL in_valid : IN  STD_LOGIC) IS
-  BEGIN
-    WAIT UNTIL rising_edge(clk);
-    WHILE in_valid /= '1' LOOP
-      WAIT UNTIL rising_edge(clk);
-    END LOOP;
-  END proc_dp_stream_valid;
-  
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Wait for stream valid AND sop
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_stream_valid_sop(SIGNAL clk      : IN  STD_LOGIC;
-                                     SIGNAL in_valid : IN  STD_LOGIC;
-                                     SIGNAL in_sop   : IN  STD_LOGIC) IS
-  BEGIN
-    WAIT UNTIL rising_edge(clk);
-    WHILE in_valid /= '1' AND in_sop /= '1' LOOP
-      WAIT UNTIL rising_edge(clk);
-    END LOOP;
-  END proc_dp_stream_valid_sop;
-
-  
-  ------------------------------------------------------------------------------
-  -- PROCEDURE: Wait for stream valid AND eop
-  ------------------------------------------------------------------------------
-  PROCEDURE proc_dp_stream_valid_eop(SIGNAL clk      : IN  STD_LOGIC;
-                                     SIGNAL in_valid : IN  STD_LOGIC;
-                                     SIGNAL in_eop   : IN  STD_LOGIC) IS
-  BEGIN
-    WAIT UNTIL rising_edge(clk);
-    WHILE in_valid /= '1' AND in_eop /= '1' LOOP
-      WAIT UNTIL rising_edge(clk);
-    END LOOP;
-  END proc_dp_stream_valid_eop;
-  
-END tb_dp_pkg;
diff --git a/cores/base/dp/dp_repack_data/dp_repack_data.vhd b/cores/base/dp/dp_repack_data/dp_repack_data.vhd
deleted file mode 100644
index 0e052cb06330c2c48656f8bd71e297e8d375931b..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_repack_data/dp_repack_data.vhd
+++ /dev/null
@@ -1,748 +0,0 @@
---------------------------------------------------------------------------------
---
--- Copyright (C) 2015
--- 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 dp_repack_data works both as packer and as unpacker.
---
--- Block diagram:
---
--- A) Functional
---   The drawing shows g_in_nof_words=4 and g_out_nof_words=2 as example:
---
---                dp_repack_in               dp_repack_out
---                     ___                        ___
---                    |   |      pack_sosi       |   |--> src_out
---                    | 3 |--------------------->| 1 |
---                    |   |                      |   |
---                    | 2 | ^                    |   | ^
---                    |   | |valid               |   | |shift
---                    | 1 | |flush               | 0 | |
---                    |   | |                    |   | |
---                    | 0 |                      |   |
---   snk_in        -->|___|      pack_siso       |___|
---   snk_out.ready <--     <---------------------     <-- src_in.ready
---   snk_out.xon   <------------------------------------- src_in.xon
---
---
--- B) Flow control
---
---      RL=1                        RL=1               RL=1
---        .                           .                  .
---        .        /-----------------------------------------\
---        .        |                  .           _____  .   |
---        .        |   /------\     nxt_r        |     | r   |
---        .        \-->|      |---*-------*----->|p_reg|-----*---> src_out
---        .            |      |   |       |      |_____|
---     snk_in -------->|p_comb|<--|-------|--------------*-------- src_in
---                     |      |   |       |              |
---                     |      |   |       v              |
---                     |      |   |   /-------\          |
---                     |      |   |   |p_flow |          |
---                     \------/   |   \-------/          |
---                                |       |              |
---           nxt_r.hold_out.valid |       |              |
---                                v       |              |
---                                /|      |r_snk_out     |
---                               |0|------/              |
---    snk_out <------------------| |                     |
---                               |1|---------------------/
---                                \|
---
--- Description:
---   The dp_repack_data repacks g_in_nof_words of width g_in_dat_w into
---   g_out_nof_words of width g_out_dat_w.
---
--- . g_in_bypass, g_out_bypass
---   The dp_repack_in and dp_repack_out can be bypassed to save logic and to
---   avoid the pipeline stage. Default both are FALSE, but they can be set
---   TRUE if:
---
---   . g_in_bypass =TRUE if g_in_nof_words=g_out_nof_words or g_in_nof_words=1
---   . g_out_bypass=TRUE if g_in_nof_words=g_out_nof_words or g_out_nof_words=1
---
---   Both the dp_repack_in and dp_repack_out stage do work correctly independent
---   of the g_*_bypass setting. When g_*_bypass=FALSE then they merely
---   add a transparant pipeline delay. It is important that they also work for
---   g_*_bypass=FALSE because that gives confidence that their implementation
---   structure is ok.
---
--- . g_in_nof_words and input block size
---   The input block size in words is indicated by snk_in.sop and snk_in.eop.
---   Each subsection of g_in_nof_words is packed into g_out_nof_words. The
---   input block size does not have to be a multiple of g_in_nof_words. When
---   the snk_in.eop occurs the last repack is initiated without need for input
---   data padding. If the block length is an integer multiple of
---   g_in_nof_words then the dp_repack_data introduces no gaps between blocks.
---   If the block length is a fractional multiple of g_in_nof_words then there
---   will be a gap after the block due to that the dp_repack_in needs to
---   shift up the last subsection for the 'missing' input words.
---
--- . g_in_dat_w*g_in_nof_words <, =, > g_in_dat_w*g_in_nof_words
---   . = : no subsection zero padding
---   . < : the subsections will be zero padded
---   . > : then the input must have sufficient zero padded bits per
---         subsection that can be stripped without data loss.
---
--- . Resolution of the empty field
---   The g_in_symbol_w is used to define the resolution of snk_in.empty and
---   the g_out_symbol_w is used to define the resolution of src_out.empty. If
---   they are 1 then the resolution is in number of bits, because the symbol
---   size is then 1 bit. Their value has no effect on the packed data it self,
---   only on the meaning of the empty field. Hence if the empty field is not
---   used, then the setting of g_in_symbol_w and g_out_symbol_w is dont care.
---
--- Remarks:
--- . Originally reused from LOFAR rad_repack.vhd and rad_repack(rtl).vhd. This
---   dp_repack_data still uses the shift in input register in and the shift out
---   output register, but no longer the intermediate buffer register.
---   Using shift in and shift out may ease timing closure because the routing
---   is more local compared to using a demultiplexer to put the input data in
---   the input register and a multiplexer to get the data directly from the
---   output register. For the demultiplexer / multiplexer it would be possible
---   to only use one internal register.
---   Using shift up is sufficient, the shift down option is not needed. With
---   shift up the data is input a [0] and output the high index.
---   Instead of requiring an snk_in.valid duty cycle this dp_repack_data uses
---   snk_out.ready flow control and can handle src_in.ready flow control.
---
--- . To pack ETH/IP/UDP header slv of 14 + 20 + 8 = 42 octets into 32 bit words
---   use:
---     u_dp_repack_data : ENTITY .dp_repack_data
---     GENERIC MAP (
---       g_in_bypass         => TRUE,
---       g_in_dat_w          => 8 * 42,
---       g_in_nof_words      => 1,
---       g_in_symbol_w       => 8,
---       g_out_bypass        => FALSE,
---       g_out_dat_w         => 32,
---       g_out_nof_words     => 11,
---       g_out_symbol_w      => 8
---     )
---   The src_out.empty will be 2, because:
---     (g_out_dat_w*g_out_nof_words-g_in_dat_w*g_in_nof_words)/g_out_symbol_w
---      = (32*11 - 42*8*1)/ 8 = 2 octet symbols
---       
--- Design steps:
--- * In total the development took 5 days. On day 3 I was in distress because
---   I could not get it to work so I needed to rethink. After changing to the
---   new flow control scheme that uses nxt_r the design was gradually improved
---   by getting the dp_repack_data instances in tb_tb_dp_repack_data to work one
---   by one. First only for e_active stimuli and later also for e_random and
---   e_pulse. Initially about 80 % of the functionality was implemented but
---   and subsequently each feature was verified starting with the basic 
---   features and then themore detailed features. This step by step approach
---   makes that the bugs appear one by one instead of all together. Without a
---   step by step approach the bugs are too big to solve.
---   . First cases with g_in_nof_words=1 and g_out_nof_words were made to work
---     for different g_pkt_len <, =, > g_in_nof_words.
---   . Then the empty functionality for g_pkt_len MOD g_in_nof_words /= 0 was
---     added.
---   . Tried g_out_dat_w=1 which makes dp_repack_data a serializer/deserializer.
---   . Then apply external flow control using c_dp_flow_control_enum_arr in
---     the tb_tb_dp_repack_data was verified resulting in small corrections.
---   . Then verified g_in_dat_w * g_in_nof_words > or < g_out_dat_w *
---     g_out_nof_words which require padding in the subsection. The > case
---     occurs for packing and the < case then occurs for unpacking.
---   . Added g_bypass to force using wires instead of a void dp_repack_in or
---     dp_repack_out stage.
---   . Verified g_in_symbol_w and g_out_symbol_w /= 1.
--- * The development used the tb_dp_repack_data testbench that does a pack and
---   an unpack to be able to verify the data. The c_no_unpack and
---   c_enable_repack_in and c_enable_repack_out parameters in the tb are
---   useful to be able to isolate a component for debugging.
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ENTITY dp_repack_in IS
-  GENERIC (
-    g_bypass          : BOOLEAN := FALSE;
-    g_in_dat_w        : NATURAL;
-    g_in_nof_words    : NATURAL;
-    g_in_symbol_w     : NATURAL := 1  -- default 1 for snk_in.empty in nof bits, else use power of 2
-  );
-  PORT (
-    rst              : IN  STD_LOGIC;
-    clk              : IN  STD_LOGIC;
-
-    snk_out          : OUT t_dp_siso;
-    snk_in           : IN  t_dp_sosi;
-
-    src_in           : IN  t_dp_siso;
-    src_out          : OUT t_dp_sosi
-  );
-END dp_repack_in;
-
-
-ARCHITECTURE rtl OF dp_repack_in IS
-
-  CONSTANT c_in_buf_dat_w      : NATURAL := g_in_dat_w * g_in_nof_words;
-  CONSTANT c_bit_cnt_max       : NATURAL := c_in_buf_dat_w;
-  CONSTANT c_in_empty_lo       : NATURAL := true_log2(g_in_symbol_w);
-
-  TYPE t_dat_arr  IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-
-  TYPE t_reg IS RECORD
-    dat_arr       : t_dat_arr(g_in_nof_words-1 DOWNTO 0);     -- internally use dat_arr[] to represent v.src_out.data
-    src_out       : t_dp_sosi;                                -- sosi output
-    hold_out      : t_dp_sosi;                                -- hold snk_in.sync/sop/eop until end of section and then hold valid src_out until src_in.ready
-    flush         : STD_LOGIC;                                -- shift when snk_in.valid or flush in case the last subsection has < g_in_nof_words
-    dat_bit_cnt   : NATURAL RANGE 0 TO c_bit_cnt_max;         -- actual nof bits in subsection
-    pack_bit_cnt  : NATURAL RANGE 0 TO c_bit_cnt_max;         -- count nof bits in subsection
-  END RECORD;
-
-  SIGNAL data_vec   : STD_LOGIC_VECTOR(c_in_buf_dat_w-1 DOWNTO 0);
-
-  SIGNAL r_snk_out  : t_dp_siso := c_dp_siso_rdy;
-  SIGNAL r          : t_reg;
-  SIGNAL nxt_r      : t_reg;
-
-  -- Debug signals
-  SIGNAL snk_in_data        : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-  SIGNAL i_src_out          : t_dp_sosi;
-  SIGNAL src_out_data       : STD_LOGIC_VECTOR(c_in_buf_dat_w-1 DOWNTO 0);
-
-  SIGNAL dbg_g_in_dat_w   : NATURAL := g_in_dat_w;
-  SIGNAL dbg_in_nof_words : NATURAL := g_in_nof_words;
-  SIGNAL dbg_in_symbol_w  : NATURAL := g_in_symbol_w;
-  SIGNAL dbc_in_buf_dat_w : NATURAL := c_in_buf_dat_w;
-
-BEGIN
-
-  snk_in_data <= snk_in.data(g_in_dat_w-1 DOWNTO 0);
-  
-  src_out      <= i_src_out;
-  src_out_data <= i_src_out.data(c_in_buf_dat_w-1 DOWNTO 0);
-  
-  gen_bypass : IF g_bypass=TRUE GENERATE
-    snk_out   <= src_in;
-    i_src_out <= snk_in;
-  END GENERATE;
-  
-  no_bypass : IF g_bypass=FALSE GENERATE
-
-    p_comb : PROCESS(rst, r, snk_in, data_vec, src_in)
-      VARIABLE v : t_reg;
-    BEGIN
-      ------------------------------------------------------------------------
-      -- Default
-      v := r;
-      v.src_out.sync  := '0';
-      v.src_out.valid := '0';
-      v.src_out.sop   := '0';
-      v.src_out.eop   := '0';
-  
-      --------------------------------------------------------------------------
-      -- Function
-      IF r.hold_out.valid='0' THEN
-      
-        -- Clear hold_out for new output valid (= new subsection)
-        IF r.src_out.valid='1' THEN
-          v.hold_out := c_dp_sosi_rst;
-        END IF;
-  
-        -- Capture the snk_in block info that is valid at sop and eop
-        IF snk_in.sop='1' THEN
-          v.hold_out.sop    := '1';
-          v.hold_out.sync   := snk_in.sync;
-          v.src_out.bsn     := snk_in.bsn;
-          v.src_out.channel := snk_in.channel;
-        END IF;
-        IF snk_in.eop='1' THEN
-          v.hold_out.eop    := '1';
-          v.hold_out.empty  := SHIFT_UVEC(snk_in.empty, -c_in_empty_lo);  -- use snk_in.empty as offset for src_out.empty in nof bits
-          v.src_out.err     := snk_in.err;
-        END IF;
-  
-        -- Capture the data per subsection in a block
-        IF snk_in.valid='1' OR r.flush='1' THEN
-          -- shift in during block
-          v.dat_arr(g_in_nof_words-1 DOWNTO 1) := r.dat_arr(g_in_nof_words-2 DOWNTO 0);  -- shift up from low to high and shift in at index 0
-          IF r.flush='1' THEN
-            v.dat_arr(0) := (OTHERS=>'0');                                               -- shift in data=0 for flush
-          ELSE
-            v.dat_arr(0) := snk_in.data(g_in_dat_w-1 DOWNTO 0);                          -- shift in valid data
-          END IF;
-  
-          -- pack subsection
-          IF r.pack_bit_cnt<c_in_buf_dat_w-g_in_dat_w THEN
-            v.pack_bit_cnt := r.pack_bit_cnt + g_in_dat_w;
-  
-            -- early end of pack subsection
-            IF snk_in.eop='1' THEN
-              v.flush := '1';                   -- enable flush in case eop occurs before end of pack subsection
-              v.dat_bit_cnt := v.pack_bit_cnt;  -- capture the current subsection pack_bit_cnt
-            END IF;
-          ELSE                                  -- r.pack_bit_cnt=c_in_buf_dat_w-g_in_dat_w
-            -- default end of pack subsection
-            v.pack_bit_cnt := 0;
-            v.flush := '0';
-            IF r.flush='0' THEN
-              v.dat_bit_cnt := c_in_buf_dat_w;  -- set default subsection pack_bit_cnt
-            END IF;
-            
-            v.hold_out.valid := '1';            -- the function has new data to output
-          END IF;
-        END IF;
-  
-        -- pass on the v.dat_arr as data vector
-        v.src_out.data := RESIZE_DP_DATA(data_vec);
-  
-        -- pass on dat_bit_cnt via DP empty field
-        v.src_out.empty := INCR_UVEC(v.hold_out.empty, c_in_buf_dat_w - v.dat_bit_cnt);
-  
-        -- output input stage into output stage when ready, else hold_out.valid to signal pending output
-        IF v.hold_out.valid='1' THEN
-          IF src_in.ready='1' THEN
-            v.src_out.valid := '1';
-            v.src_out.sync  := v.hold_out.sync;
-            v.src_out.sop   := v.hold_out.sop;
-            v.src_out.eop   := v.hold_out.eop;
-            v.hold_out.valid := '0';
-          END IF;
-        END IF;
-      ELSE
-        -- pending output
-        IF src_in.ready='1' THEN
-          v.src_out.valid := '1';
-          v.src_out.sync  := r.hold_out.sync;
-          v.src_out.sop   := r.hold_out.sop;
-          v.src_out.eop   := r.hold_out.eop;
-          v.hold_out.valid := '0';
-        END IF;
-      END IF;
-  
-      ------------------------------------------------------------------------
-      -- Reset and nxt_r
-      IF rst = '1' THEN
-        v.src_out       := c_dp_sosi_rst;
-        v.hold_out      := c_dp_sosi_rst;
-        v.flush         := '0';
-        v.dat_bit_cnt   := 0;
-        v.pack_bit_cnt  := 0;
-      END IF;
-  
-      nxt_r <= v;
-    END PROCESS;
-  
-    --------------------------------------------------------------------------
-    -- p_reg
-    r <= nxt_r WHEN rising_edge(clk);
-  
-    --------------------------------------------------------------------------
-    -- Wires
-    p_data_vec : PROCESS(nxt_r)
-    BEGIN
-      FOR I IN 0 TO g_in_nof_words-1 LOOP
-        data_vec((I+1)*g_in_dat_w-1 DOWNTO I*g_in_dat_w) <= nxt_r.dat_arr(I);
-      END LOOP;
-    END PROCESS;
-  
-    --------------------------------------------------------------------------
-    -- Wired output
-    i_src_out <= r.src_out;
-  
-    --------------------------------------------------------------------------
-    -- Flow control
-  
-    -- local function flow control
-    p_flow : PROCESS(nxt_r)
-    BEGIN
-      r_snk_out <= c_dp_siso_rdy;
-      IF nxt_r.flush='1' THEN
-        r_snk_out.ready <= '0';   -- input shift in stage function is always ready except when flushing
-      END IF;
-    END PROCESS;
-  
-    -- combined local and remote src_in flow control
-    snk_out.ready <= r_snk_out.ready WHEN nxt_r.hold_out.valid='0' ELSE src_in.ready;  -- if there is pending output then the src_in ready determines the flow control
-    snk_out.xon   <= src_in.xon;  -- just pass on the xon/off frame flow control
-  
-  END GENERATE;
-  
-END rtl;
-
-
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ENTITY dp_repack_out IS
-  GENERIC (
-    g_bypass           : BOOLEAN := FALSE;
-    g_in_buf_dat_w     : NATURAL;
-    g_out_dat_w        : NATURAL;
-    g_out_nof_words    : NATURAL;
-    g_out_symbol_w     : NATURAL := 1  -- default 1 for snk_in.empty in nof bits, else use power of 2
-  );
-  PORT (
-    rst              : IN  STD_LOGIC;
-    clk              : IN  STD_LOGIC;
-
-    snk_out          : OUT t_dp_siso;
-    snk_in           : IN  t_dp_sosi;
-
-    src_in           : IN  t_dp_siso;
-    src_out          : OUT t_dp_sosi
-  );
-END dp_repack_out;
-
-ARCHITECTURE rtl OF dp_repack_out IS
-
-  CONSTANT c_out_buf_dat_w     : NATURAL := g_out_dat_w * g_out_nof_words;
-  CONSTANT c_out_buf_dat_lo    : NATURAL := sel_a_b(c_out_buf_dat_w > g_in_buf_dat_w, c_out_buf_dat_w -  g_in_buf_dat_w, 0);  -- pack into subsection with 0 or more padding bits
-  CONSTANT c_snk_in_dat_lo     : NATURAL := sel_a_b(c_out_buf_dat_w < g_in_buf_dat_w,  g_in_buf_dat_w - c_out_buf_dat_w, 0);  -- unpack from subsection that has 0 or more padding bits
-  CONSTANT c_bit_cnt_max       : NATURAL := c_out_buf_dat_w;
-  CONSTANT c_out_empty_lo      : NATURAL := true_log2(g_out_symbol_w);
-
-  TYPE t_dat_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0);
-
-  TYPE t_reg IS RECORD
-    dat_arr       : t_dat_arr(g_out_nof_words-1 DOWNTO 0);
-    src_out       : t_dp_sosi;
-    hold_out      : t_dp_sosi;                                -- hold src_out valid and sync/sop/eop until src_in.ready
-    shift         : STD_LOGIC;                                -- shift out the dat_arr
-    dat_bit_cnt   : NATURAL RANGE 0 TO c_bit_cnt_max;         -- actual nof bits in subsection
-    pack_bit_cnt  : NATURAL RANGE 0 TO c_bit_cnt_max;         -- count nof bits in subsection
-    empty_bit_cnt : NATURAL RANGE 0 TO c_bit_cnt_max;         -- empty nof bits in subsection
-    eos           : STD_LOGIC;                                -- end of subsection
-  END RECORD;
-
-  SIGNAL data_vec  : STD_LOGIC_VECTOR(c_out_buf_dat_w-1 DOWNTO 0) := (OTHERS=>'0');
-
-  SIGNAL r_snk_out : t_dp_siso := c_dp_siso_rdy;
-  SIGNAL r         : t_reg;
-  SIGNAL nxt_r     : t_reg;
-
-  -- Debug signals
-  SIGNAL snk_in_data        : STD_LOGIC_VECTOR(g_in_buf_dat_w-1 DOWNTO 0);
-  SIGNAL i_src_out          : t_dp_sosi;
-  SIGNAL src_out_data       : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0);
-
-  SIGNAL dbg_g_in_buf_dat_w : NATURAL := g_in_buf_dat_w;
-  SIGNAL dbg_g_out_dat_w    : NATURAL := g_out_dat_w;
-  SIGNAL dbg_out_nof_words  : NATURAL := g_out_nof_words;
-  SIGNAL dbg_out_symbol_w   : NATURAL := g_out_symbol_w;
-  SIGNAL dbc_out_buf_dat_w  : NATURAL := c_out_buf_dat_w;
-  SIGNAL dbc_out_buf_dat_lo : NATURAL := c_out_buf_dat_lo;
-  SIGNAL dbc_snk_in_dat_lo  : NATURAL := c_snk_in_dat_lo;
-
-BEGIN
-
-  snk_in_data <= snk_in.data(g_in_buf_dat_w-1 DOWNTO 0);
-  
-  src_out      <= i_src_out;
-  src_out_data <= i_src_out.data(g_out_dat_w-1 DOWNTO 0);
-  
-  gen_bypass : IF g_bypass=TRUE GENERATE
-    snk_out <= src_in;
-    
-    p_src_out : PROCESS(snk_in)
-    BEGIN
-      i_src_out <= snk_in;
-      IF c_snk_in_dat_lo>0 THEN
-        i_src_out.data  <= SHIFT_UVEC(snk_in.data,   c_snk_in_dat_lo);
-        i_src_out.empty <= INCR_UVEC( snk_in.empty, -c_snk_in_dat_lo);
-      END IF;
-      IF c_out_buf_dat_lo>0 THEN
-        i_src_out.data  <= SHIFT_UVEC(snk_in.data, -c_out_buf_dat_lo);
-        i_src_out.empty <= INCR_UVEC( snk_in.empty, c_out_buf_dat_lo);
-      END IF;
-    END PROCESS;
-  END GENERATE;
-  
-  no_bypass : IF g_bypass=FALSE GENERATE
-
-    p_comb : PROCESS(rst, snk_in, r, data_vec, src_in)
-      VARIABLE v : t_reg;
-    BEGIN
-      ------------------------------------------------------------------------
-      -- Default
-      v := r;
-      v.src_out.sync  := '0';
-      v.src_out.valid := '0';
-      v.src_out.sop   := '0';
-      v.src_out.eop   := '0';
-  
-      ------------------------------------------------------------------------
-      -- Function
-      IF r.hold_out.valid='0' THEN
-      
-        -- Clear hold_out for new output valid
-        IF r.src_out.sop='1' THEN
-          v.hold_out.sync := '0';
-          v.hold_out.sop  := '0';
-        END IF;
-        IF r.src_out.eop='1' THEN
-          v.hold_out.eop := '0';
-        END IF;
-  
-        -- Capture the snk_in block info that is valid at sop and eop
-        IF snk_in.sop='1' THEN
-          v.hold_out.sop    := '1';
-          v.hold_out.sync   := snk_in.sync;
-          v.src_out.bsn     := snk_in.bsn;
-          v.src_out.channel := snk_in.channel;
-        END IF;
-        IF snk_in.eop='1' THEN
-          v.hold_out.eop    := '1';  -- local function will calculate src_out.empty based on snk_in.empty
-          v.src_out.err     := snk_in.err;
-        END IF;
-  
-        IF r.shift='1' THEN
-          -- shift out rest of subsection
-          v.hold_out.valid := '1';
-  
-          v.dat_arr(g_out_nof_words-1 DOWNTO 1) := r.dat_arr(g_out_nof_words-2 DOWNTO 0);  -- shift up from low to high and shift out at high index
-          v.dat_arr(0) := (OTHERS=>'0');                                                   -- shift in data=0
-  
-          v.pack_bit_cnt := r.pack_bit_cnt - g_out_dat_w;
-  
-          -- end of pack subsection
-          IF v.pack_bit_cnt<=r.empty_bit_cnt THEN
-            v.eos   := '1';                     -- end of subsection, so ready for new snk_in
-            v.shift := '0';                     -- stop shifting
-          END IF;
-  
-        ELSIF snk_in.valid='1' THEN
-          -- start of pack subsection
-          v.hold_out.valid := '1';
-  
-          FOR I IN 0 TO g_out_nof_words-1 LOOP
-            v.dat_arr(I) := data_vec((I+1)*g_out_dat_w-1 DOWNTO I*g_out_dat_w);
-          END LOOP;
-  
-          v.dat_bit_cnt := g_in_buf_dat_w - c_snk_in_dat_lo;          -- default dat_bit_cnt per subsection
-          IF snk_in.eop='1' THEN
-            v.dat_bit_cnt := g_in_buf_dat_w - TO_UINT(snk_in.empty);  -- pass on last subsection dat_bit_cnt info via DP empty field
-          END IF;
-          
-          v.pack_bit_cnt  := c_out_buf_dat_w - g_out_dat_w;
-          v.empty_bit_cnt := c_out_buf_dat_w - v.dat_bit_cnt;
-          v.eos           := '0';
-          v.shift         := '1';
-  
-          -- end of pack subsection
-          IF v.pack_bit_cnt<=v.empty_bit_cnt THEN
-            v.eos   := '1';         -- end of subsection, so ready for new snk_in
-            v.shift := '0';
-          END IF;
-        END IF;
-  
-        -- fill in local empty if this is the last subsection of a block
-        IF v.eos='1' THEN
-          IF v.hold_out.eop='1' THEN
-            v.src_out.empty := TO_DP_EMPTY(v.empty_bit_cnt - v.pack_bit_cnt);  -- in nof bits
-            v.src_out.empty := SHIFT_UVEC(v.src_out.empty, c_out_empty_lo);    -- in nof symbols
-          END IF;
-        END IF;
-  
-        -- pass on the v.dat_arr as data vector
-        v.src_out.data  := RESIZE_DP_DATA(v.dat_arr(g_out_nof_words-1));
-  
-        -- output valid data when ready, else hold_out.valid to signal pending output
-        IF v.hold_out.valid='1' THEN
-          IF src_in.ready='1' THEN
-            v.src_out.valid  := '1';
-            v.src_out.sync   := v.hold_out.sync;
-            v.src_out.sop    := v.hold_out.sop;
-            v.src_out.eop    := v.hold_out.eop AND v.eos;  -- output eop at end of subsection
-            v.hold_out.valid := '0';
-          END IF;
-        END IF;
-  
-      ELSE
-        -- pending output
-        IF src_in.ready='1' THEN
-          v.src_out.valid := '1';
-          v.src_out.sync  := r.hold_out.sync;
-          v.src_out.sop   := r.hold_out.sop;
-          v.src_out.eop   := r.hold_out.eop AND r.eos;  -- output eop at end of subsection
-          v.hold_out.valid := '0';
-        END IF;
-      END IF;
-  
-      ------------------------------------------------------------------------
-      -- Reset and nxt_r
-      IF rst = '1' THEN
-        v.src_out       := c_dp_sosi_rst;
-        v.hold_out      := c_dp_sosi_rst;
-        v.shift         := '0';
-        v.dat_bit_cnt   := 0;
-        v.pack_bit_cnt  := 0;
-        v.empty_bit_cnt := 0;
-        v.eos           := '0';
-      END IF;
-  
-      nxt_r <= v;
-    END PROCESS;
-  
-    --------------------------------------------------------------------------
-    -- p_reg
-    r <= nxt_r WHEN rising_edge(clk);
-  
-    --------------------------------------------------------------------------
-    -- Wires
-    data_vec(c_out_buf_dat_w-1 DOWNTO c_out_buf_dat_lo) <= snk_in.data(g_in_buf_dat_w-1 DOWNTO c_snk_in_dat_lo);
-  
-    --------------------------------------------------------------------------
-    -- Wired output
-    i_src_out <= r.src_out;
-  
-    --------------------------------------------------------------------------
-    -- Flow control
-  
-    -- local function flow control
-    p_flow : PROCESS(nxt_r)
-    BEGIN
-      r_snk_out <= c_dp_siso_rdy;
-      IF nxt_r.shift='1' AND nxt_r.eos='0' THEN
-        r_snk_out.ready <= '0';   -- output shift out stage function is only ready when it is not shifting or at the end of the subsection
-      END IF;
-    END PROCESS;
-  
-    -- combined local and remote src_in flow control
-    snk_out.ready <= r_snk_out.ready WHEN nxt_r.hold_out.valid='0' ELSE src_in.ready;  -- if there is pending output then the src_in ready determines the flow control
-    snk_out.xon   <= src_in.xon;  -- just pass on the xon/off frame flow control
-    
-  END GENERATE;
-  
-END rtl;
-
-
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-
-ENTITY dp_repack_data IS
-  GENERIC (
-    g_enable_repack_in  : BOOLEAN := TRUE;
-    g_enable_repack_out : BOOLEAN := TRUE;
-    g_in_bypass         : BOOLEAN := FALSE;
-    g_in_dat_w          : NATURAL;
-    g_in_nof_words      : NATURAL;
-    g_in_symbol_w       : NATURAL := 1;  -- default 1 for snk_in.empty in nof bits, else use power of 2
-    g_out_bypass        : BOOLEAN := FALSE;
-    g_out_dat_w         : NATURAL;
-    g_out_nof_words     : NATURAL;
-    g_out_symbol_w      : NATURAL := 1   -- default 1 for src_out.empty in nof bits, else use power of 2
-  );
-  PORT (
-    rst              : IN  STD_LOGIC;
-    clk              : IN  STD_LOGIC;
-
-    snk_out          : OUT t_dp_siso;
-    snk_in           : IN  t_dp_sosi;
-
-    src_in           : IN  t_dp_siso;
-    src_out          : OUT t_dp_sosi
-  );
-END dp_repack_data;
-
-
-ARCHITECTURE str OF dp_repack_data IS
-
-  CONSTANT c_in_buf_dat_w      : NATURAL := g_in_dat_w * g_in_nof_words;
-
-  SIGNAL snk_in_data       : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-  SIGNAL i_snk_out         : t_dp_siso;
-
-  SIGNAL pack_siso         : t_dp_siso;
-  SIGNAL pack_sosi         : t_dp_sosi;
-  SIGNAL pack_sosi_data    : STD_LOGIC_VECTOR(c_in_buf_dat_w-1 DOWNTO 0);
-
-  SIGNAL i_src_out         : t_dp_sosi;
-  SIGNAL src_out_data      : STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0);
-
-  SIGNAL snk_out_ready_reg : STD_LOGIC_VECTOR(0 TO c_dp_stream_rl);
-  SIGNAL pack_ready_reg    : STD_LOGIC_VECTOR(0 TO c_dp_stream_rl);
-
-BEGIN
-
-  snk_out <= i_snk_out;
-  src_out <= i_src_out;
-
-  snk_in_data    <= snk_in.data(g_in_dat_w-1 DOWNTO 0);
-  pack_sosi_data <= pack_sosi.data(c_in_buf_dat_w-1 DOWNTO 0);
-  src_out_data   <= i_src_out.data(g_out_dat_w-1 DOWNTO 0);
-
-  no_dp_repack_in : IF g_enable_repack_in=FALSE GENERATE
-    i_snk_out <= pack_siso;
-    pack_sosi <= snk_in;
-  END GENERATE;
-
-  gen_dp_repack_in : IF g_enable_repack_in=TRUE GENERATE
-    u_dp_repack_in : ENTITY work.dp_repack_in
-    GENERIC MAP (
-      g_bypass       => g_in_bypass,
-      g_in_dat_w     => g_in_dat_w,
-      g_in_nof_words => g_in_nof_words,
-      g_in_symbol_w  => g_in_symbol_w
-    )
-    PORT MAP (
-      rst      => rst,
-      clk      => clk,
-
-      snk_out  => i_snk_out,
-      snk_in   => snk_in,
-
-      src_in   => pack_siso,
-      src_out  => pack_sosi
-    );
-  END GENERATE;
-
-  no_dp_repack_out : IF g_enable_repack_out=FALSE GENERATE
-    pack_siso <= src_in;
-    i_src_out <= pack_sosi;
-  END GENERATE;
-
-  gen_dp_repack_out : IF g_enable_repack_out=TRUE GENERATE
-    u_dp_repack_out : ENTITY work.dp_repack_out
-    GENERIC MAP (
-      g_bypass        => g_out_bypass,
-      g_in_buf_dat_w  => c_in_buf_dat_w,
-      g_out_dat_w     => g_out_dat_w,
-      g_out_nof_words => g_out_nof_words,
-      g_out_symbol_w  => g_out_symbol_w
-    )
-    PORT MAP (
-      rst      => rst,
-      clk      => clk,
-
-      snk_out  => pack_siso,
-      snk_in   => pack_sosi,
-
-      src_in   => src_in,
-      src_out  => i_src_out
-    );
-  END GENERATE;
-
-  -- Simulation only: internal stream RL verification
-  proc_dp_siso_alert(clk, snk_in, i_snk_out, snk_out_ready_reg);
-  proc_dp_siso_alert(clk, pack_sosi, pack_siso, pack_ready_reg);
-
-END str;
diff --git a/cores/base/dp/dp_repack_data/hdllib.cfg b/cores/base/dp/dp_repack_data/hdllib.cfg
deleted file mode 100644
index bb4139616f9d019c159f9b9a2441177de1533e0a..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_repack_data/hdllib.cfg
+++ /dev/null
@@ -1,20 +0,0 @@
-hdl_lib_name = dp_repack_data
-hdl_library_clause_name = dp_repack_data_lib
-hdl_lib_uses_synth = dp_pkg
-hdl_lib_uses_sim = 
-hdl_lib_technology = 
-
-synth_files =
-    dp_repack_data.vhd
-   
-test_bench_files = 
-    tb_dp_repack_data.vhd
-    tb_tb_dp_repack_data.vhd
-
-regression_test_vhdl = 
-    tb_tb_dp_repack_data.vhd
-    
-[modelsim_project_file]
-
-
-[quartus_project_file]
diff --git a/cores/base/dp/dp_repack_data/tb_dp_repack_data.vhd b/cores/base/dp/dp_repack_data/tb_dp_repack_data.vhd
deleted file mode 100644
index 2d2d5f95684a228a8782e1b21fbd7ef157fa2f7a..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_repack_data/tb_dp_repack_data.vhd
+++ /dev/null
@@ -1,317 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2015
--- 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:
--- . Test bench for dp_repack_data
--- Description:
---                                                       c_no_unpack
---                                                          .
---             g_in_dat_w             g_pack_dat_w          .   g_in_dat_w
---             g_in_nof_words         g_pack_nof_words      .   g_in_nof_words
---                 .                       .                .       .
---                 .   u_pack              .       u_unpack .       .
---                 .   ______________      .       ______________   .
---                 .  |dp_repack_data|     .      |dp_repack_data|  .
---   stimuli_src ---->|              |----------->|              |----> verify_snk
---                    | in       out |  pack_src  | in       out |
---                    |______________|            |______________|
---
--- Usage:                                  
--- > as 10
--- > run -all
---
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE common_pkg_lib.common_lfsr_sequences_pkg.ALL;
-USE common_pkg_lib.tb_common_pkg.ALL;
-USE dp_pkg_lib.dp_stream_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
-
-ENTITY tb_dp_repack_data IS
-  GENERIC (
-    -- general
-    g_flow_control_stimuli   : t_dp_flow_control_enum := e_active;  -- always e_active, e_random or e_pulse flow control
-    g_flow_control_verify    : t_dp_flow_control_enum := e_active;  -- always e_active, e_random or e_pulse flow control
-    -- specific
-    g_in_dat_w               : NATURAL := 8 * 42;
-    g_in_nof_words           : NATURAL := 1;
-    g_pack_dat_w             : NATURAL := 32;
-    g_pack_nof_words         : NATURAL := 11;
-    g_in_bypass              : BOOLEAN := TRUE;   -- can use TRUE when g_in_nof_words=1  or g_in_nof_words=g_out_nof_words
-    g_pack_bypass            : BOOLEAN := FALSE;  -- can use TRUE when g_out_nof_words=1 or g_in_nof_words=g_out_nof_words
-    g_in_symbol_w            : NATURAL := 8;      -- default 1 for snk_in.empty  in nof bits, else use power of 2
-    g_pack_symbol_w          : NATURAL := 8;      -- default 1 for src_out.empty in nof bits, else use power of 2
-    g_nof_repeat             : NATURAL := 10;
-    g_pkt_len                : NATURAL := 1;     -- if not a multiple of g_in_nof_words then the input stage flush creates gap between blocks
-    g_pkt_gap                : NATURAL := 0
-  );
-END tb_dp_repack_data;
-
-
-ARCHITECTURE tb OF tb_dp_repack_data IS
-
-  CONSTANT c_no_unpack                : BOOLEAN := FALSE;
-  CONSTANT c_enable_repack_in         : BOOLEAN := TRUE;
-  CONSTANT c_enable_repack_out        : BOOLEAN := TRUE;
-
-  -- dp_stream_stimuli
-  CONSTANT c_stimuli_pulse_active     : NATURAL := 3;  --g_in_nof_words;
-  CONSTANT c_stimuli_pulse_period     : NATURAL := 7;
-
-  CONSTANT c_data_init                : NATURAL := 0;
-  CONSTANT c_bsn_init                 : STD_LOGIC_VECTOR(c_dp_stream_bsn_w-1 DOWNTO 0) := X"0000000000000000";  -- X"0877665544332211"
-  CONSTANT c_err_init                 : NATURAL := 247;
-  CONSTANT c_channel_init             : NATURAL := 5;  -- fixed
-
-  -- dp_stream_verify
-  CONSTANT c_verify_pulse_active      : NATURAL := 1;
-  CONSTANT c_verify_pulse_period      : NATURAL := 5;
-
-  CONSTANT c_data_max                 : UNSIGNED(g_in_dat_w-1 DOWNTO 0) := (OTHERS=>'1');
-  CONSTANT c_dsp_max                  : UNSIGNED(g_in_dat_w-1 DOWNTO 0) := (OTHERS=>'1');
-
-  --CONSTANT c_verify_snk_in_cnt_max    : t_dp_sosi_unsigned := c_dp_sosi_unsigned_rst;  -- default 0 is no wrap
-  CONSTANT c_verify_snk_in_cnt_max    : t_dp_sosi_unsigned := TO_DP_SOSI_UNSIGNED('0', '0', '0', '0', c_data_max, c_dsp_max, c_dsp_max, c_unsigned_0, c_unsigned_0, c_unsigned_0, c_unsigned_0);
-  CONSTANT c_verify_snk_in_cnt_gap    : t_dp_sosi_unsigned := c_dp_sosi_unsigned_ones; -- default only accept increment +1
-
-  CONSTANT c_expected_pkt_len         : NATURAL := sel_a_b(c_no_unpack, g_pkt_len * g_pack_nof_words / g_in_nof_words, g_pkt_len);
-  -- both
-  CONSTANT c_sync_period              : NATURAL := 10;
-  CONSTANT c_sync_offset              : NATURAL := 7;
-
-  SIGNAL clk                        : STD_LOGIC := '1';
-  SIGNAL rst                        : STD_LOGIC := '1';
-  SIGNAL tb_end                     : STD_LOGIC := '0';
-
-  SIGNAL stimuli_src_in             : t_dp_siso := c_dp_siso_rdy;
-  SIGNAL stimuli_src_out            : t_dp_sosi;
-  SIGNAL stimuli_src_out_data       : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-
-  SIGNAL verify_snk_in_enable       : t_dp_sosi_sl := c_dp_sosi_sl_rst;
-  SIGNAL last_snk_in                : t_dp_sosi;
-  SIGNAL last_snk_in_evt            : STD_LOGIC;
-  SIGNAL verify_last_snk_in_evt     : t_dp_sosi_sl := c_dp_sosi_sl_rst;
-
-  SIGNAL verify_snk_out             : t_dp_siso := c_dp_siso_rdy;
-  SIGNAL verify_snk_in              : t_dp_sosi;
-  SIGNAL verify_snk_in_data         : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-
-  -- specific
-  SIGNAL pack_src_in                : t_dp_siso;
-  SIGNAL pack_src_out               : t_dp_sosi;
-  SIGNAL pack_src_out_data          : STD_LOGIC_VECTOR(g_pack_dat_w-1 DOWNTO 0);
-
-  SIGNAL unpack_src_in              : t_dp_siso;
-  SIGNAL unpack_src_out             : t_dp_sosi;
-  SIGNAL unpack_src_out_data        : STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0);
-
-BEGIN
-
-  clk <= (NOT clk) OR tb_end AFTER clk_period/2;
-  rst <= '1', '0' AFTER clk_period*7;
-
-  ------------------------------------------------------------------------------
-  -- DATA GENERATION
-  ------------------------------------------------------------------------------
-
-  u_dp_stream_stimuli : ENTITY dp_pkg_lib.dp_stream_stimuli
-  GENERIC MAP (
-    g_instance_nr    => 0,                        -- only one stream so choose index 0
-    -- flow control
-    g_random_w       => 15,                       -- use different random width for stimuli and for verify to have different random sequences
-    g_pulse_active   => c_stimuli_pulse_active,
-    g_pulse_period   => c_stimuli_pulse_period,
-    g_flow_control   => g_flow_control_stimuli,   -- always active, random or pulse flow control
-    -- initializations
-    g_sync_period    => c_sync_period,
-    g_sync_offset    => c_sync_offset,
-    g_data_init      => c_data_init,
-    g_bsn_init       => c_bsn_init,
-    g_err_init       => c_err_init,
-    g_channel_init   => c_channel_init,
-    -- specific
-    g_in_dat_w       => g_in_dat_w,
-    g_nof_repeat     => g_nof_repeat,
-    g_pkt_len        => g_pkt_len,
-    g_pkt_gap        => g_pkt_gap
-  )
-  PORT MAP (
-    rst                 => rst,
-    clk                 => clk,
-
-    -- Generate stimuli
-    src_in              => stimuli_src_in,
-    src_out             => stimuli_src_out,
-
-    -- End of stimuli
-    last_snk_in         => last_snk_in,      -- expected verify_snk_in after end of stimuli
-    last_snk_in_evt     => last_snk_in_evt,  -- trigger verify to verify the last_snk_in
-    tb_end              => tb_end            -- signal end of tb as far as this dp_stream_stimuli is concerned
-  );
-
-
-  ------------------------------------------------------------------------------
-  -- DATA VERIFICATION
-  ------------------------------------------------------------------------------
-
-  -- Select fields that need to be verified
-  -- . during the test
-  verify_snk_in_enable.sync    <= '1';
-  verify_snk_in_enable.bsn     <= '1';
-  verify_snk_in_enable.data    <= '1' WHEN c_no_unpack=FALSE ELSE '0';
-  verify_snk_in_enable.re      <= '0';
-  verify_snk_in_enable.im      <= '0';
-  verify_snk_in_enable.valid   <= '1';
-  verify_snk_in_enable.sop     <= '1';
-  verify_snk_in_enable.eop     <= '1';
-  verify_snk_in_enable.empty   <= '0';
-  verify_snk_in_enable.channel <= '1';
-  verify_snk_in_enable.err     <= '1';
-
-  -- . after the test
-  verify_last_snk_in_evt.sync    <= last_snk_in_evt;
-  verify_last_snk_in_evt.bsn     <= last_snk_in_evt;
-  verify_last_snk_in_evt.data    <= last_snk_in_evt WHEN c_no_unpack=FALSE ELSE '0';
-  verify_last_snk_in_evt.re      <= '0';
-  verify_last_snk_in_evt.im      <= '0';
-  verify_last_snk_in_evt.valid   <= last_snk_in_evt;
-  verify_last_snk_in_evt.sop     <= last_snk_in_evt;
-  verify_last_snk_in_evt.eop     <= last_snk_in_evt;
-  verify_last_snk_in_evt.empty   <= '0';
-  verify_last_snk_in_evt.channel <= last_snk_in_evt;
-  verify_last_snk_in_evt.err     <= last_snk_in_evt;
-
-  u_dp_stream_verify : ENTITY dp_pkg_lib.dp_stream_verify
-  GENERIC MAP (
-    g_instance_nr    => 0,                        -- only one stream so choose index 0
-    -- flow control
-    g_random_w       => 14,                       -- use different random width for stimuli and for verify to have different random sequences
-    g_pulse_active   => c_verify_pulse_active,
-    g_pulse_period   => c_verify_pulse_period,
-    g_flow_control   => g_flow_control_verify,    -- always active, random or pulse flow control
-    -- initializations
-    g_sync_period    => c_sync_period,
-    g_sync_offset    => c_sync_offset,
-    g_snk_in_cnt_max => c_verify_snk_in_cnt_max,
-    g_snk_in_cnt_gap => c_verify_snk_in_cnt_gap,
-    -- specific
-    g_in_dat_w       => g_in_dat_w,
-    g_pkt_len        => c_expected_pkt_len
-  )
-  PORT MAP (
-    rst                        => rst,
-    clk                        => clk,
-
-    -- Verify data
-    snk_out                    => verify_snk_out,
-    snk_in                     => verify_snk_in,
-
-    -- During stimuli
-    verify_snk_in_enable       => verify_snk_in_enable,  -- enable verify to verify that the verify_snk_in fields are incrementing
-
-    -- End of stimuli
-    expected_snk_in            => last_snk_in,            -- expected verify_snk_in after end of stimuli
-    verify_expected_snk_in_evt => verify_last_snk_in_evt  -- trigger verify to verify the last_snk_in
-  );
-
-  ------------------------------------------------------------------------------
-  -- DUT Pack
-  ------------------------------------------------------------------------------
-
-  u_pack : ENTITY work.dp_repack_data
-  GENERIC MAP (
-    g_enable_repack_in  => c_enable_repack_in,
-    g_enable_repack_out => c_enable_repack_out,
-    g_in_bypass         => g_in_bypass,
-    g_in_dat_w          => g_in_dat_w,
-    g_in_nof_words      => g_in_nof_words,
-    g_in_symbol_w       => g_in_symbol_w,
-    g_out_bypass        => g_pack_bypass,
-    g_out_dat_w         => g_pack_dat_w,
-    g_out_nof_words     => g_pack_nof_words,
-    g_out_symbol_w      => g_pack_symbol_w
-  )
-  PORT MAP (
-    rst              => rst,
-    clk              => clk,
-
-    snk_out          => stimuli_src_in,
-    snk_in           => stimuli_src_out,
-
-    src_in           => pack_src_in,
-    src_out          => pack_src_out
-  );
-
-  pack_src_out_data <= pack_src_out.data(g_pack_dat_w-1 DOWNTO 0);
-
-  ------------------------------------------------------------------------------
-  -- DUT Unpack
-  ------------------------------------------------------------------------------
-
-  no_unpack : IF c_no_unpack=TRUE GENERATE
-    pack_src_in    <= unpack_src_in;
-    unpack_src_out <= pack_src_out;
-  END GENERATE;
-
-  gen_unpack : IF c_no_unpack=FALSE GENERATE
-    u_unpack : ENTITY work.dp_repack_data
-    GENERIC MAP (
-      g_enable_repack_in  => c_enable_repack_out,
-      g_enable_repack_out => c_enable_repack_in,
-      g_in_bypass         => g_pack_bypass,
-      g_in_dat_w          => g_pack_dat_w,
-      g_in_nof_words      => g_pack_nof_words,
-      g_in_symbol_w       => g_pack_symbol_w,
-      g_out_bypass        => g_in_bypass,
-      g_out_dat_w         => g_in_dat_w,
-      g_out_nof_words     => g_in_nof_words,
-      g_out_symbol_w      => g_in_symbol_w
-    )
-    PORT MAP (
-      rst              => rst,
-      clk              => clk,
-
-      snk_out          => pack_src_in,
-      snk_in           => pack_src_out,
-
-      src_in           => unpack_src_in,
-      src_out          => unpack_src_out
-    );
-  END GENERATE;
-
-  unpack_src_out_data <= unpack_src_out.data(g_in_dat_w-1 DOWNTO 0);
-
-  unpack_src_in <= verify_snk_out;
-  verify_snk_in <= unpack_src_out;
-  
-  ------------------------------------------------------------------------------
-  -- Auxiliary
-  ------------------------------------------------------------------------------
-
-  -- Map to slv to ease monitoring in wave window
-  stimuli_src_out_data <= stimuli_src_out.data(g_in_dat_w-1 DOWNTO 0);
-  verify_snk_in_data   <= verify_snk_in.data(g_in_dat_w-1 DOWNTO 0);
-
-END tb;
diff --git a/cores/base/dp/dp_repack_data/tb_tb_dp_repack_data.vhd b/cores/base/dp/dp_repack_data/tb_tb_dp_repack_data.vhd
deleted file mode 100644
index 62f5bdb7c4f788ef5e90c96955a5919678652ffc..0000000000000000000000000000000000000000
--- a/cores/base/dp/dp_repack_data/tb_tb_dp_repack_data.vhd
+++ /dev/null
@@ -1,166 +0,0 @@
--------------------------------------------------------------------------------
---
--- Copyright (C) 2015
--- 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/>.
---
--------------------------------------------------------------------------------
-
-LIBRARY IEEE, common_pkg_lib, dp_pkg_lib;
-USE IEEE.std_logic_1164.ALL;
-USE common_pkg_lib.common_pkg.ALL;
-USE dp_pkg_lib.tb_dp_pkg.ALL;
-
--- Purpose: Verify multiple variations of tb_dp_repack_data
--- Description:
--- Usage:
--- > as 6
--- > run -all
-
-ENTITY tb_tb_dp_repack_data IS
-END tb_tb_dp_repack_data;
-
-
-ARCHITECTURE tb OF tb_tb_dp_repack_data IS
-
-  CONSTANT c_nof_repeat  : NATURAL := 5;
-  
-  CONSTANT c_flow        : t_dp_flow_control_enum_arr := c_dp_flow_control_enum_arr;
-  CONSTANT c_bool        : t_nat_boolean_arr := c_nat_boolean_arr;
-  
-  SIGNAL tb_end : STD_LOGIC := '0';  -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
-  
-BEGIN
-
-  -- -- general
-  -- g_flow_control_stimuli   : t_dp_flow_control_enum := e_active;  -- always e_active, e_random or e_pulse flow control
-  -- g_flow_control_verify    : t_dp_flow_control_enum := e_active;  -- always e_active, e_random or e_pulse flow control
-  -- -- specific
-  -- g_in_dat_w               : NATURAL := 5;
-  -- g_in_nof_words           : NATURAL := 2;
-  -- g_pack_dat_w             : NATURAL := 16;
-  -- g_pack_nof_words         : NATURAL := 1;
-  -- g_in_bypass              : BOOLEAN := FALSE;  -- can use TRUE when g_in_nof_words=1  or g_in_nof_words=g_out_nof_words
-  -- g_pack_bypass            : BOOLEAN := FALSE;  -- can use TRUE when g_out_nof_words=1 or g_in_nof_words=g_out_nof_words
-  -- g_in_symbol_w            : NATURAL := 1;      -- default 1 for snk_in.empty  in nof bits, else use power of 2
-  -- g_pack_symbol_w          : NATURAL := 1;      -- default 1 for src_out.empty in nof bits, else use power of 2
-  -- g_nof_repeat             : NATURAL := 10;
-  -- g_pkt_len                : NATURAL := 11;     -- if not a multiple of g_in_nof_words then the input stage flush creates gap between blocks
-  -- g_pkt_gap                : NATURAL := 0
-  
-  g_flow_control_stimuli : FOR I IN 0 TO 2 GENERATE    -- 0 = e_active, 1 = e_random, 2 = e_pulse
-    g_flow_control_verify : FOR J IN 0 TO 2 GENERATE    -- 0 = e_active, 1 = e_random, 2 = e_pulse
-
-      -------------------------------------------------------------------------
-      -- Tests that can use bypass
-      -- . g_in_nof_words = 1
-      -- . g_out_nof_words = 1
-      -- . g_in_nof_words = g_in_nof_words >= 1
-      -------------------------------------------------------------------------
-      
-      gen_bool_bypass : FOR K IN 0 TO 1 GENERATE
-        gen_bool_bypass : FOR L IN 0 TO 1 GENERATE
-          -- no repack, g_in_nof_words = g_out_nof_words = 1
-          u_16_1_16_1_len_10_gap_0   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 16, 1, 16, 1, c_bool(K), c_bool(L), 1, 1, c_nof_repeat, 10, 0);  -- g_pkt_len > g_in_nof_words
-          u_16_1_16_1_len_3_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 16, 1, 16, 1, c_bool(K), c_bool(L), 1, 1, c_nof_repeat,  3, 0);  -- g_pkt_len > g_in_nof_words, odd
-          u_16_1_16_1_len_2_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 16, 1, 16, 1, c_bool(K), c_bool(L), 1, 1, c_nof_repeat,  2, 0);  -- g_pkt_len > g_in_nof_words, even
-          u_16_1_16_1_len_1_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 16, 1, 16, 1, c_bool(K), c_bool(L), 1, 1, c_nof_repeat,  1, 0);  -- g_pkt_len = g_in_nof_words
-          
-          u_16_1_16_1_len_1_gap_1    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 16, 1, 16, 1, c_bool(K), c_bool(L), 1, 1, c_nof_repeat,  1, 1);  -- g_pkt_gap > 0
-        END GENERATE;
-      
-        -- no repack, g_in_nof_words = g_out_nof_words > 1
-        u_16_3_16_3_len_10_gap_0   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  16, 3, 16, 3, c_bool(K), c_bool(K), 1, 1, c_nof_repeat, 10,  0);
-        
-        -- g_in_nof_words > g_pack_nof_words can use always active stimuli except when g_pkt_len MOD g_in_nof_words /= 0, because then the input stage needs to flush
-        u_8_4_32_1_len_1_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 4, 32, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat,  1,  0);  -- g_pkt_len < g_in_nof_words
-        u_8_4_32_1_len_2_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 4, 32, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat,  2,  0);  -- g_pkt_len = g_in_nof_words
-        u_8_4_32_1_len_3_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 4, 32, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat,  3,  0);  -- g_pkt_len > g_in_nof_words, MOD /= 0
-        u_8_4_32_1_len_10_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 4, 32, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat, 10,  0);  -- g_pkt_len > g_in_nof_words, MOD /= 0
-        u_8_4_32_1_len_11_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 4, 32, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat, 11,  0);  -- g_pkt_len > g_in_nof_words, MOD /= 0
-        u_8_4_32_1_len_12_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 4, 32, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat, 12,  0);  -- g_pkt_len > g_in_nof_words, MOD = 0
-      
-        u_8_4_32_1_len_12_gap_2    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 4, 32, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat, 12,  2);  -- g_pkt_gap > 0
-      
-        -- g_in_nof_words < g_pack_nof_words will apply backpressure, because the output stage needs to output more
-        u_32_1_8_4_len_1_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 32, 1, 8, 4, c_bool(K), FALSE, 1, 1, c_nof_repeat,  1,  0);  -- g_pkt_len = g_in_nof_words
-        u_32_1_8_4_len_2_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 32, 1, 8, 4, c_bool(K), FALSE, 1, 1, c_nof_repeat,  2,  0);  -- g_pkt_len > g_in_nof_words
-        u_32_1_8_4_len_3_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 32, 1, 8, 4, c_bool(K), FALSE, 1, 1, c_nof_repeat,  3,  0);  -- g_pkt_len > g_in_nof_words
-        u_32_1_8_4_len_10_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 32, 1, 8, 4, c_bool(K), FALSE, 1, 1, c_nof_repeat, 10,  0);  -- g_pkt_len > g_in_nof_words
-        
-        u_32_1_8_4_len_11_gap_1    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 32, 1, 8, 4, c_bool(K), FALSE, 1, 1, c_nof_repeat, 11,  1);  -- g_pkt_gap > 0
-      
-        -- g_in_dat_w MOD 8 /= 0, g_in_nof_words=1
-        u_14_1_8_2_len_10_gap_0   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 14, 1, 8, 2, c_bool(K), FALSE, 1, 1, c_nof_repeat, 10,  0);  -- repack with subsection padding, even multiple of g_in_nof_words
-        u_14_1_8_2_len_11_gap_0   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 14, 1, 8, 2, c_bool(K), FALSE, 1, 1, c_nof_repeat, 11,  0);  -- repack with subsection padding, odd multiple of g_in_nof_words
-        
-        -- g_in_dat_w MOD 8 /= 0, g_out_nof_words=1
-        u_5_2_16_1_len_10_gap_0  : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 5, 2, 16, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat, 10,  0);  -- repack with subsection padding, integer multiple of g_in_nof_words
-        u_5_2_16_1_len_11_gap_0  : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 5, 2, 16, 1, FALSE, c_bool(K), 1, 1, c_nof_repeat, 11,  0);  -- repack with subsection padding, fractional multiple of g_in_nof_words
-        
-        -- g_in_nof_words=1, g_pack_nof_words>1
-        u_8_1_4_2_len_10_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   8, 1,  4,  2, c_bool(K), FALSE, 1, 1, c_nof_repeat, 10,  0);
-        u_512_1_32_16_len_1_gap_20 : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 512, 1, 32, 16, c_bool(K), FALSE, 1, 1, c_nof_repeat,  1, 20);  -- pack a larger header slv into g_pack_dat_w words
-        
-        -- serialize to and deserialize from g_pack_dat_w=1 bit
-        u_8_1_1_8_len_10_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  8, 1, 1,  8, c_bool(K), FALSE, 1, 1, c_nof_repeat, 10,  0);  -- g_pack_dat_w=1
-        u_32_1_1_32_len_10_gap_7   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 32, 1, 1, 32, c_bool(K), FALSE, 1, 1, c_nof_repeat, 10,  7);  -- g_pack_dat_w=1
-      
-        -- g_in_symbol_w /= 1, g_out_symbol_w /= 1
-        u_20_1_8_3_symbol_1_4_len_10_gap_0  : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 20, 1, 8, 3, c_bool(K), FALSE, 1, 4, c_nof_repeat, 10, 0);  -- no repack
-        u_20_1_8_3_symbol_4_1_len_10_gap_0  : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 20, 1, 8, 3, c_bool(K), FALSE, 4, 1, c_nof_repeat, 10, 0);  -- no repack
-        u_20_1_8_3_symbol_4_4_len_10_gap_0  : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 20, 1, 8, 3, c_bool(K), FALSE, 4, 4, c_nof_repeat, 10, 0);  -- no repack
-        
-        -- pack ETH/IP/UDP header, g_in_symbol_w = 8, g_out_symbol_w = 8
-        u_336_1_32_11_symbol_8_8_len_1_gap_0  : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 336, 1, 32, 11, c_bool(K), FALSE, 8, 8, c_nof_repeat, 1, 0);  --pack to 32 bit --> empty = 2
-        u_336_1_64_6_symbol_8_8_len_1_gap_0   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J), 336, 1, 64,  6, c_bool(K), FALSE, 8, 8, c_nof_repeat, 1, 0);  --pack to 64 bit --> empty = 6
-      END GENERATE;
-      
-      -------------------------------------------------------------------------
-      -- Tests that cannot use bypass
-      -------------------------------------------------------------------------
-      
-      -- g_in_nof_words > 1 and g_pack_nof_words > 1
-      u_24_2_16_3_len_1_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  24, 2, 16, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  1, 0);  -- g_pkt_len < g_in_nof_words
-      u_24_2_16_3_len_2_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  24, 2, 16, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  2, 0);  -- g_pkt_len = g_in_nof_words
-      u_24_2_16_3_len_3_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  24, 2, 16, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  3, 0);  -- g_pkt_len = fractional multiple of g_in_nof_words
-      u_24_2_16_3_len_10_gap_0   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  24, 2, 16, 3, FALSE, FALSE, 1, 1, c_nof_repeat, 10, 0);  -- g_pkt_len = integer multiple of g_in_nof_words
-      u_24_2_16_3_len_11_gap_0   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  24, 2, 16, 3, FALSE, FALSE, 1, 1, c_nof_repeat, 11, 0);  -- g_pkt_len = fractional multiple of g_in_nof_words
-      
-      u_24_2_16_3_len_11_gap_3   : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  24, 2, 16, 3, FALSE, FALSE, 1, 1, c_nof_repeat, 11, 3);  -- g_pkt_gap > 0
-
-      -- g_in_dat_w MOD 8 /= 0
-      u_6_5_10_3_len_1_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  1, 0);  -- g_pkt_len < g_in_nof_words
-      u_6_5_10_3_len_2_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  2, 0);  -- g_pkt_len < g_in_nof_words
-      u_6_5_10_3_len_3_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  3, 0);  -- g_pkt_len < g_in_nof_words
-      u_6_5_10_3_len_4_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  4, 0);  -- g_pkt_len < g_in_nof_words
-      u_6_5_10_3_len_5_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat,  5, 0);  -- g_pkt_len = g_in_nof_words
-      u_6_5_10_3_len_10_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat, 10, 0);  -- g_pkt_len = integer multiple of g_in_nof_words
-      u_6_5_10_3_len_11_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat, 11, 0);  -- g_pkt_len = fractional multiple of g_in_nof_words
-      
-      u_6_5_10_3_len_21_gap_3    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),   6, 5, 10, 3, FALSE, FALSE, 1, 1, c_nof_repeat, 21, 3);  -- g_pkt_gap > 0
-      
-      -- subsection padding, g_in_dat_w * g_in_nof_words < g_pack_dat_w * g_pack_nof_words
-      u_18_2_8_5_len_1_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  18, 2,  8, 5, FALSE, FALSE, 1, 1, c_nof_repeat,  1, 0);  -- g_pkt_len < g_in_nof_words
-      u_18_2_8_5_len_2_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  18, 2,  8, 5, FALSE, FALSE, 1, 1, c_nof_repeat,  2, 0);  -- g_pkt_len = g_in_nof_words
-      u_18_2_8_5_len_3_gap_0     : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  18, 2,  8, 5, FALSE, FALSE, 1, 1, c_nof_repeat,  3, 0);  -- g_pkt_len = fractional multiple of g_in_nof_words
-      u_18_2_8_5_len_10_gap_0    : ENTITY work.tb_dp_repack_data GENERIC MAP (c_flow(I), c_flow(J),  18, 2,  8, 5, FALSE, FALSE, 1, 1, c_nof_repeat, 10, 0);  -- g_pkt_len = integer multiple of g_in_nof_words
-      
-    END GENERATE;
-  END GENERATE;
-                                                                                               
-END tb;