diff --git a/libraries/base/dp/hdllib.cfg b/libraries/base/dp/hdllib.cfg
index c33690558424837b122beee5e306d9266d1a86ad..3b1bff1f02a4186cb170dc23e7f7e42b99c69aea 100644
--- a/libraries/base/dp/hdllib.cfg
+++ b/libraries/base/dp/hdllib.cfg
@@ -104,6 +104,8 @@ synth_files =
     src/vhdl/dp_bsn_align.vhd
     src/vhdl/dp_bsn_align_reg.vhd
     src/vhdl/mms_dp_bsn_align.vhd
+    src/vhdl/dp_bsn_align_v2.vhd
+    src/vhdl/mmp_dp_bsn_align_v2.vhd
     src/vhdl/dp_frame_rd.vhd
     src/vhdl/dp_frame_fsn.vhd
     src/vhdl/dp_frame_tx.vhd
@@ -211,6 +213,8 @@ test_bench_files =
     tb/vhdl/tb_dp_block_validate_channel.vhd
     tb/vhdl/tb_dp_bsn_align.vhd
     tb/vhdl/tb_mms_dp_bsn_align.vhd
+    tb/vhdl/tb_dp_bsn_align_v2.vhd
+    tb/vhdl/tb_mmp_dp_bsn_align_v2.vhd
     tb/vhdl/tb_dp_bsn_monitor.vhd
     tb/vhdl/tb_dp_bsn_monitor_v2.vhd
     tb/vhdl/tb_dp_bsn_source.vhd
@@ -295,6 +299,7 @@ test_bench_files =
     tb/vhdl/tb_tb_dp_block_from_mm.vhd
     tb/vhdl/tb_tb_dp_block_validate_channel.vhd
     tb/vhdl/tb_tb_dp_bsn_align.vhd
+    tb/vhdl/tb_tb_dp_bsn_align_v2.vhd
     tb/vhdl/tb_tb_dp_bsn_source_v2.vhd
     tb/vhdl/tb_tb_dp_bsn_sync_scheduler.vhd
     tb/vhdl/tb_tb_dp_concat.vhd
@@ -351,6 +356,7 @@ regression_test_vhdl =
     tb/vhdl/tb_dp_latency_adapter.vhd
     tb/vhdl/tb_dp_shiftreg.vhd
     tb/vhdl/tb_dp_bsn_source.vhd
+    tb/vhdl/tb_mmp_dp_bsn_align_v2.vhd
     tb/vhdl/tb_mms_dp_bsn_source.vhd
     tb/vhdl/tb_mms_dp_bsn_source_v2.vhd
     tb/vhdl/tb_mmp_dp_bsn_sync_scheduler.vhd
@@ -364,6 +370,7 @@ regression_test_vhdl =
     tb/vhdl/tb_tb_dp_block_gen_valid_arr.vhd
     tb/vhdl/tb_tb_dp_block_from_mm.vhd
     tb/vhdl/tb_tb_dp_block_validate_channel.vhd
+    tb/vhdl/tb_tb_dp_bsn_align_v2.vhd
     tb/vhdl/tb_tb_dp_bsn_source_v2.vhd
     tb/vhdl/tb_tb_dp_bsn_sync_scheduler.vhd
     tb/vhdl/tb_tb_dp_concat.vhd
diff --git a/libraries/base/dp/src/vhdl/dp_block_from_mm.vhd b/libraries/base/dp/src/vhdl/dp_block_from_mm.vhd
index 4b88f228595ecc68035b9fa574b36064ebe8b91e..37b58b49b76f0b9a8cdf48339be448a2de30a941 100644
--- a/libraries/base/dp/src/vhdl/dp_block_from_mm.vhd
+++ b/libraries/base/dp/src/vhdl/dp_block_from_mm.vhd
@@ -86,8 +86,6 @@ BEGIN
   last_mm_address <= g_step_size * (g_nof_data - 1) + g_data_size + start_address - 1;
   mm_address      <= start_address + r.word_index + r.step_index;
   
-  mm_mosi.address <= TO_MEM_ADDRESS(mm_address);
-
   -- Take care of g_mm_rd_latency for out_sosi.sop and out_sosi.eop
   r_sop_p <= r.sop WHEN rising_edge(clk);
   r_eop_p <= r.eop WHEN rising_edge(clk);
@@ -120,7 +118,9 @@ BEGIN
     v := r;
     v.sop := '0';
     v.eop := '0';
-    mm_mosi.rd <= '0';
+    mm_mosi <= c_mem_mosi_rst;  -- use default 0 to avoid Warning: (vsim-8684) No drivers exist on out port .wr, .wrdata
+    mm_mosi.address <= TO_MEM_ADDRESS(mm_address);  -- only use mosi.rd and mosi.address
+
     IF r.busy = '0' AND start_pulse = '1' THEN
       -- initiate next block
       v.busy := '1';
diff --git a/libraries/base/dp/src/vhdl/dp_block_to_mm.vhd b/libraries/base/dp/src/vhdl/dp_block_to_mm.vhd
index 2520c398666f8fa545c8e61c4cb38b375f29aee6..711ca1a86d7e7a56bc4f28d6a303859ecb9999ee 100644
--- a/libraries/base/dp/src/vhdl/dp_block_to_mm.vhd
+++ b/libraries/base/dp/src/vhdl/dp_block_to_mm.vhd
@@ -65,10 +65,15 @@ ARCHITECTURE rtl OF dp_block_to_mm IS
   SIGNAL address : NATURAL := 0;
 
 BEGIN
-  address         <= start_address + r.word_index + r.step_index;
-  mm_mosi.address <= TO_MEM_ADDRESS(address);
-  mm_mosi.wrdata  <= RESIZE_MEM_DATA(in_sosi.data);
-  mm_mosi.wr      <= d.wr;
+  address <= start_address + r.word_index + r.step_index;
+
+  p_mm_mosi : PROCESS(address, in_sosi, d)
+  BEGIN
+    mm_mosi <= c_mem_mosi_rst;  -- default to avoid ** Warning: (vsim-8684) No drivers exist on out port mm_mosi.rd
+    mm_mosi.address <= TO_MEM_ADDRESS(address);
+    mm_mosi.wrdata  <= RESIZE_MEM_DATA(in_sosi.data);
+    mm_mosi.wr      <= d.wr;
+  END PROCESS;
   
   p_reg : PROCESS(rst, clk)
   BEGIN
diff --git a/libraries/base/dp/src/vhdl/dp_bsn_align_v2.vhd b/libraries/base/dp/src/vhdl/dp_bsn_align_v2.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..87dcb99739f0d7daec770140c9dc65d42511126d
--- /dev/null
+++ b/libraries/base/dp/src/vhdl/dp_bsn_align_v2.vhd
@@ -0,0 +1,442 @@
+-- --------------------------------------------------------------------------
+-- Copyright 2021
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+-- http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+-- --------------------------------------------------------------------------
+--
+-- Author: Eric Kooistra, 3 Sept 2021
+-- Purpose :
+--   Align frames from multiple input streams
+-- Description:
+--   The aligner uses a circular buffer to capture the blocks that arrive at
+--   the input streams. The blocks have a block sequence number (BSN) that
+--   is used to align the inputs. The input stream 0 is treated as local
+--   input stream that is ahead of the other remote input streams. After a
+--   certain number of blocks on input 0, the same block on all remote
+--   inputs should also have arrived. If not then they are replaced by
+--   replacement data. The output streams are paced by the block rate of input 0.
+--   The user has to read the block within the block period.
+--
+--   Features:
+--   . uses lost_data flag and replacement data to replace lost input blocks
+--   . uses replacement data to replace disabled input streams
+--   . output block can be read in arbitrary order
+--
+--   For more detailed description see:
+--   https://support.astron.nl/confluence/display/L2M/L6+FWLIB+Design+Document%3A+BSN+aligner+v2
+--
+-- Remarks:
+-- . This dp_bsn_align_v2.vhd replaces the dp_bsn_align.vhd that was used in
+--   APERTIF. Main differences are that the old component uses FIFO buffers,
+--   timeouts and states, and v2 does not, which makes v2 simpler and more
+--   robust.
+
+LIBRARY IEEE,common_lib;
+USE IEEE.std_logic_1164.ALL;
+USE IEEE.numeric_std.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE work.dp_stream_pkg.ALL;
+
+
+ENTITY dp_bsn_align_v2 IS
+  GENERIC (
+    g_nof_streams                : NATURAL;           -- number of input and output streams
+    g_bsn_latency_max            : NATURAL;           -- Maximum travel latency of a remote block in number of block periods T_blk
+    g_nof_aligners_max           : POSITIVE := 1;     -- 1 when only align at last node, > 1 when align at every intermediate node
+    g_block_size                 : NATURAL := 32;     -- > 1, g_block_size=1 is not supported
+    g_bsn_w                      : NATURAL := c_dp_stream_bsn_w;  -- number of bits in sosi BSN
+    g_data_w                     : NATURAL;           -- number of bits in sosi data
+    g_replacement_value          : INTEGER := 0;      -- output sosi data value for missing input blocks
+    g_use_mm_output              : BOOLEAN := FALSE;  -- output via MM or via streaming DP
+    g_pipeline_input             : NATURAL := 0;      -- >= 0, choose 0 for wires, choose 1 to ease timing closure
+    g_rd_latency                 : NATURAL := 1       -- 1 or 2, choose 2 to ease timing closure
+  );
+  PORT (
+    dp_rst         : IN  STD_LOGIC;
+    dp_clk         : IN  STD_LOGIC;
+
+    node_index     : IN  NATURAL RANGE 0 TO g_nof_aligners_max := 0;  -- only used when g_nof_aligners_max > 1
+
+    -- MM control
+    stream_en_arr  : IN  STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0) := (OTHERS=>'1');
+
+    -- Streaming input
+    in_sosi_arr    : IN  t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+
+    -- Output via local MM interface in dp_clk domain, when g_use_mm_output = TRUE.
+    mm_sosi        : OUT t_dp_sosi;   -- streaming information that signals that an output block can be read
+    mm_copi        : IN  t_mem_copi := c_mem_copi_rst;  -- read access to output block, all output streams share same mm_copi
+    mm_cipo_arr    : OUT t_mem_cipo_arr(g_nof_streams-1 DOWNTO 0);
+
+    -- Output via streaming DP interface, when g_use_mm_output = TRUE.
+    out_sosi_arr   : OUT t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0)
+  );
+END dp_bsn_align_v2;
+
+
+ARCHITECTURE rtl OF dp_bsn_align_v2 IS
+
+  -- Circular buffer per stream
+  CONSTANT c_buffer_nof_blocks : NATURAL :=  ceil_pow2(1 + g_nof_aligners_max * g_bsn_latency_max);
+
+  CONSTANT c_ram_size       : NATURAL := c_buffer_nof_blocks * g_block_size;
+  CONSTANT c_ram_buf        : t_c_mem := (latency  => 1,
+                                          adr_w    => ceil_log2(c_ram_size),
+                                          dat_w    => g_data_w,
+                                          nof_dat  => c_ram_size,
+                                          init_sl  => '0');
+
+  CONSTANT c_block_size_w   : NATURAL := ceil_log2(g_block_size);
+  CONSTANT c_block_size_slv : STD_LOGIC_VECTOR(c_block_size_w-1 DOWNTO 0) := TO_UVEC(g_block_size, c_block_size_w);
+  CONSTANT c_blk_pointer_w  : NATURAL := ceil_log2(c_buffer_nof_blocks);
+
+  -- Use fixed slv width instead of using naturals for address calculation, to
+  -- avoid that synthesis may infer a too larger multiplier
+  CONSTANT c_product_w      : NATURAL := c_blk_pointer_w + c_block_size_w;
+
+  TYPE t_bsn_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_bsn_w-1 DOWNTO 0);
+  TYPE t_adr_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_mem_ram.adr_w-1 DOWNTO 0);
+  TYPE t_filled_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_buffer_nof_blocks-1 DOWNTO 0);
+
+  TYPE t_reg IS RECORD
+    -- p_write_arr
+    wr_pointer           : NATURAL;
+    wr_copi_arr          : t_mem_copi_arr(g_nof_streams-1 DOWNTO 0);
+    -- all streams
+    filled_arr           : t_filled_arr(g_nof_streams-1 DOWNTO 0);
+    use_replacement_data : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+    -- local reference
+    sync_arr             : STD_LOGIC_VECTOR(c_buffer_nof_blocks-1 DOWNTO 0);
+    bsn_arr              : t_bsn_arr(c_buffer_nof_blocks-1 DOWNTO 0);
+    mm_sosi              : t_dp_sosi;
+    dp_sosi              : t_dp_sosi;
+    -- p_read
+    rd_pointer           : INTEGER;  -- use integer to detect need to wrap to natural
+    rd_offset            : STD_LOGIC_VECTOR(c_mem_ram.adr_w-1 DOWNTO 0);
+    rd_copi              : t_mem_copi;
+    fill_cipo_arr        : t_mem_cipo_arr(g_nof_streams-1 DOWNTO 0);  -- used combinatorial to contain rd_cipo_arr from buffer or replacement data
+    out_bsn              : STD_LOGIC_VECTOR(g_bsn_w-1 DOWNTO 0);  -- hold BSN for streaming output
+  END RECORD;
+
+  TYPE t_comb IS RECORD
+    ref_sosi          : t_dp_sosi;
+    pointer_slv       : STD_LOGIC_VECTOR(c_blk_pointer_w-1 DOWNTO 0);
+    product_slv       : STD_LOGIC_VECTOR(c_product_w-1 DOWNTO 0);
+    lost_data_flag    : STD_LOGIC;
+    out_sosi_arr      : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  END RECORD;
+
+  CONSTANT c_reg_rst  : t_reg := (0,
+                                  (OTHERS=>c_mem_copi_rst),
+                                  (OTHERS=>(OTHERS=>'0')),
+                                  (OTHERS=>'0'),
+                                  (OTHERS=>'0'),
+                                  (OTHERS=>(OTHERS=>'0')),
+                                  c_dp_sosi_rst,
+                                  c_dp_sosi_rst,
+                                  0,
+                                  (OTHERS=>'0'),
+                                  c_mem_copi_rst,
+                                  (OTHERS=>c_mem_cipo_rst),
+                                  (OTHERS=>'0'));
+
+  -- State registers for p_comb
+  SIGNAL r             : t_reg;
+  SIGNAL nxt_r         : t_reg;
+
+  -- Memoryless signals in p_comb (wires used as local auxiliary variables)
+  SIGNAL s             : t_comb;
+
+  -- Structural signals (wires used to connect components and IO)
+  SIGNAL dp_done       : STD_LOGIC;
+  SIGNAL dp_done_arr   : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL dp_copi       : t_mem_copi;
+  SIGNAL dp_copi_arr   : t_mem_copi_arr(g_nof_streams-1 DOWNTO 0);
+
+  SIGNAL rd_sosi_arr   : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL rd_cipo_arr   : t_mem_cipo_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>c_mem_cipo_rst);
+
+  -- Pipeline registers
+  SIGNAL in_sosi_arr_p : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL rd_copi       : t_mem_copi;
+
+  -- Debug signals
+  SIGNAL dbg_nof_streams         : NATURAL := g_nof_streams;
+  SIGNAL dbg_bsn_latency_max     : NATURAL := g_bsn_latency_max;
+  SIGNAL dbg_nof_aligners_max    : NATURAL := g_nof_aligners_max;
+  SIGNAL dbg_block_size          : NATURAL := g_block_size;
+  SIGNAL dbg_bsn_w               : NATURAL := g_bsn_w;
+  SIGNAL dbg_data_w              : NATURAL := g_data_w;
+  SIGNAL dbg_replacement_value   : INTEGER := g_replacement_value;
+  SIGNAL dbg_use_mm_output       : BOOLEAN := g_use_mm_output;
+  SIGNAL dbg_pipeline_input      : NATURAL := g_pipeline_input;
+  SIGNAL dbg_rd_latency          : NATURAL := g_rd_latency;
+  SIGNAL dbg_c_buffer_nof_blocks : NATURAL := c_buffer_nof_blocks;
+  SIGNAL dbg_c_product_w         : NATURAL := c_product_w;
+
+BEGIN
+
+  mm_sosi <= r.mm_sosi WHEN g_use_mm_output = TRUE ELSE c_dp_sosi_rst;
+
+  p_reg : PROCESS(dp_clk, dp_rst)
+  BEGIN
+    IF dp_rst='1' THEN
+      r <= c_reg_rst;
+    ELSIF rising_edge(dp_clk) THEN
+      r <= nxt_r;
+    END IF;
+  END PROCESS;
+  
+  p_comb : PROCESS(r, in_sosi_arr_p, mm_copi, dp_copi, rd_cipo_arr, rd_sosi_arr)
+    VARIABLE v : t_reg;   -- State variable
+    VARIABLE d : t_comb;  -- Memoryless auxiliary variables, local wires
+  BEGIN
+    v := r;  -- state signals
+    v.mm_sosi := func_dp_stream_reset_control(r.mm_sosi);
+    v.wr_copi_arr := RESET_MEM_COPI_CTRL(r.wr_copi_arr);
+
+    ----------------------------------------------------------------------------
+    -- p_write_arr
+    ----------------------------------------------------------------------------
+    FOR I IN 0 TO g_nof_streams-1 LOOP
+      -- p_write
+      IF in_sosi_arr_p(I).valid = '1' THEN
+        -- . increment address during block
+        v.wr_copi_arr(I).address := RESIZE_MEM_ADDRESS(INCR_UVEC(r.wr_copi_arr(I).address(c_mem_ram.adr_w-1 DOWNTO 0), 1));
+        v.wr_copi_arr(I).wr := '1';
+        v.wr_copi_arr(I).wrdata := RESIZE_MEM_SDATA(in_sosi_arr_p(I).data);
+      END IF;
+
+      IF in_sosi_arr_p(I).sop = '1' THEN
+        -- . set address at start of block
+        d.pointer_slv := in_sosi_arr_p(I).bsn(c_blk_pointer_w-1 DOWNTO 0);
+        d.product_slv := MULT_UVEC(d.pointer_slv, c_block_size_slv);
+        v.wr_copi_arr(I).address := RESIZE_MEM_ADDRESS(d.product_slv);
+
+        -- . set filled flag at sop, so assume rest of block will follow in time
+        v.filled_arr(I)(TO_UINT(d.pointer_slv)) := '1';
+      END IF;
+    END LOOP;
+
+    ----------------------------------------------------------------------------
+    -- p_control, all at sop of local reference input 0
+    ----------------------------------------------------------------------------
+    d.ref_sosi := in_sosi_arr_p(0);
+    IF d.ref_sosi.sop = '1' THEN
+      -- . write sync & bsn buffer
+      v.wr_pointer := TO_UINT(d.ref_sosi.bsn(c_blk_pointer_w-1 DOWNTO 0));
+      v.sync_arr(v.wr_pointer) := d.ref_sosi.sync;
+      v.bsn_arr(v.wr_pointer) := d.ref_sosi.bsn(g_bsn_w-1 DOWNTO 0);
+
+      -- . update read block pointer at g_bsn_latency_max blocks behind the reference write pointer
+      IF g_nof_aligners_max = 1 THEN
+        v.rd_pointer := v.wr_pointer - g_bsn_latency_max;
+      ELSE
+        v.rd_pointer := v.wr_pointer - g_bsn_latency_max * node_index;
+      END IF;
+      IF v.rd_pointer < 0 THEN
+        v.rd_pointer := v.rd_pointer + c_buffer_nof_blocks;
+      END IF;
+
+      -- . update read address of read block pointer
+      d.pointer_slv := TO_UVEC(v.rd_pointer, c_blk_pointer_w);
+      d.product_slv := MULT_UVEC(d.pointer_slv, c_block_size_slv);
+      v.rd_offset := RESIZE_UVEC(d.product_slv, c_mem_ram.adr_w);
+
+      -- . issue mm_sosi, if there is output ready to be read, indicated by filled reference block
+      IF r.filled_arr(0)(v.rd_pointer) = '1' THEN
+        v.mm_sosi.sop := '1';
+        v.mm_sosi.eop := '1';
+        v.mm_sosi.valid := '1';
+        -- . pass on timestamp information
+        v.mm_sosi.sync := v.sync_arr(v.rd_pointer);
+        v.mm_sosi.bsn := RESIZE_DP_BSN(v.bsn_arr(v.rd_pointer));
+        -- . pass on lost data flags for enabled streams via channel field, and
+        --   determine whether the ouput has to insert replacement data
+        v.mm_sosi.channel := (OTHERS=>'0');
+        FOR I IN 0 TO g_nof_streams-1 LOOP
+          d.lost_data_flag := NOT v.filled_arr(I)(v.rd_pointer);
+          IF stream_en_arr(I) = '1' THEN  -- use MM bit at sop
+            v.use_replacement_data(I) := d.lost_data_flag;  -- enabled stream, so replace the data if the data was lost
+            v.mm_sosi.channel(I) := d.lost_data_flag;  -- enabled stream, so flag the data if the data was lost
+          ELSE
+            v.use_replacement_data(I) := '1';  -- disabled stream, so replace the data, but do not flag the data as lost
+          END IF;
+        END LOOP;
+      END IF;
+
+      -- . clear filled flags, after mm_sosi was issued, or could have been issued
+      FOR I IN 0 TO g_nof_streams-1 LOOP
+        v.filled_arr(I)(v.rd_pointer) := '0';
+      END LOOP;
+    END IF;
+
+    ----------------------------------------------------------------------------
+    -- p_read
+    ----------------------------------------------------------------------------
+
+    -- Read the data from the buffer, or replace a block by replacement data
+    -- . default use input data from the circular buffer
+    v.fill_cipo_arr := rd_cipo_arr;
+    -- . if necessary, replace a stream by replacement data
+    FOR I IN 0 TO g_nof_streams-1 LOOP
+      IF r.use_replacement_data(I) = '1' THEN
+        v.fill_cipo_arr(I).rddata := TO_MEM_SDATA(g_replacement_value);
+      END IF;
+    END LOOP;
+
+    IF g_use_mm_output THEN
+      --------------------------------------------------------------------------
+      -- Do the output via the MM interface
+      --------------------------------------------------------------------------
+      -- . adjust the rd address to the current buffer output block
+      --   sum yields c_mem_ram.adr_w bits, because left operand in ADD_UVECdetermines width
+      v.rd_copi := mm_copi;
+      v.rd_copi.address := RESIZE_MEM_ADDRESS(ADD_UVEC(r.rd_offset, mm_copi.address));
+
+      -- . output via MM interface
+      mm_cipo_arr <= v.fill_cipo_arr;
+
+      -- . no output via DP streaming interface
+      out_sosi_arr <= (OTHERS => c_dp_sosi_rst);
+    ELSE
+      --------------------------------------------------------------------------
+      -- Do the output via the DP streaming interface
+      --------------------------------------------------------------------------
+      -- . adjust the rd address
+      --   sum yields c_mem_ram.adr_w bits, because left operand in ADD_UVECdetermines width
+      v.rd_copi := dp_copi;
+      v.rd_copi.address := RESIZE_MEM_ADDRESS(ADD_UVEC(r.rd_offset, dp_copi.address));
+
+      -- . hold mm_sosi.sync, bsn, channel
+      IF r.mm_sosi.sop = '1' THEN
+        v.dp_sosi := r.mm_sosi;
+      END IF;
+
+      -- . pass on input data from the buffer
+      d.out_sosi_arr := rd_sosi_arr;  -- = v.fill_cipo_arr in streaming format, contains the
+                                      -- input data from the buffer or replacement data
+      IF rd_sosi_arr(0).sop = '1' THEN
+        -- . at sop pass on input info from r.dp_sosi to all streams in out_sosi_arr
+        d.out_sosi_arr := func_dp_stream_arr_set(d.out_sosi_arr, r.dp_sosi.sync, "SYNC");
+        d.out_sosi_arr := func_dp_stream_arr_set(d.out_sosi_arr, r.dp_sosi.bsn, "BSN");
+        FOR I IN 0 TO g_nof_streams-1 LOOP
+          -- . pass on the lost flag per stream
+          d.out_sosi_arr(I).channel := RESIZE_DP_CHANNEL(slv(r.dp_sosi.channel(I)));
+        END LOOP;
+
+        -- . hold BSN until next sop, to ease view in wave window
+        v.out_bsn := r.dp_sosi.bsn(g_bsn_w-1 DOWNTO 0);
+      ELSE
+        -- . until next sop pass on BSN, to ease view in wave window
+        d.out_sosi_arr := func_dp_stream_arr_set(d.out_sosi_arr, r.out_bsn, "BSN");
+      END IF;
+
+      -- . output via DP streaming interface
+      out_sosi_arr <= d.out_sosi_arr;
+
+      -- . no output via MM interface
+      mm_cipo_arr <= (OTHERS => c_mem_cipo_rst);
+    END IF;
+
+    ----------------------------------------------------------------------------
+    -- next state
+    ----------------------------------------------------------------------------
+    nxt_r <= v;
+
+    -- memory less signals, only for view in wave window
+    s <= d;
+  END PROCESS;
+
+  ------------------------------------------------------------------------------
+  -- Circular buffers
+  ------------------------------------------------------------------------------
+
+  gen_data_buffer : FOR I IN 0 TO g_nof_streams-1 GENERATE
+    u_data_buffer : ENTITY common_lib.common_ram_r_w
+    GENERIC MAP (
+      g_ram     => c_ram_buf
+    )
+    PORT MAP (
+      rst       => dp_rst,
+      clk       => dp_clk,
+      wr_en     => r.wr_copi_arr(I).wr,
+      wr_adr    => r.wr_copi_arr(I).address(c_ram_buf.adr_w-1 DOWNTO 0),
+      wr_dat    => r.wr_copi_arr(I).wrdata(c_ram_buf.dat_w-1 DOWNTO 0),
+      rd_en     => rd_copi.rd,
+      rd_adr    => rd_copi.address(c_ram_buf.adr_w-1 DOWNTO 0),
+      rd_dat    => rd_cipo_arr(I).rddata(c_ram_buf.dat_w-1 DOWNTO 0),
+      rd_val    => rd_cipo_arr(I).rdval
+    );
+  END GENERATE;
+
+  ------------------------------------------------------------------------------
+  -- MM to streaming DP
+  ------------------------------------------------------------------------------
+
+  gen_streaming_output : IF NOT g_use_mm_output GENERATE
+    gen_mm_to_dp : FOR I IN 0 TO g_nof_streams-1 GENERATE
+      u_mm_to_dp: ENTITY work.dp_block_from_mm
+      GENERIC MAP (
+        g_data_size          => 1,
+        g_step_size          => 1,
+        g_nof_data           => g_block_size,
+        g_data_w             => g_data_w,
+        g_mm_rd_latency      => g_rd_latency,
+        g_reverse_word_order => FALSE
+      )
+      PORT MAP (
+        rst           => dp_rst,
+        clk           => dp_clk,
+        start_pulse   => r.mm_sosi.sop,
+        start_address => 0,
+        mm_done       => dp_done_arr(I),
+        mm_mosi       => dp_copi_arr(I),
+        mm_miso       => nxt_r.fill_cipo_arr(I),
+        out_sosi      => rd_sosi_arr(I),
+        out_siso      => c_dp_siso_rdy
+      );
+    END GENERATE;
+
+    -- Use dp_copi_arr(0) to read same addresses in parallel for all streams
+    dp_copi <= dp_copi_arr(0);
+    dp_done <= dp_done_arr(0);   -- for viewing only
+  END GENERATE;
+
+
+  ------------------------------------------------------------------------------
+  -- Pipelining
+  ------------------------------------------------------------------------------
+
+  -- . input
+  u_in_sosi_arr_p : ENTITY work.dp_pipeline_arr
+  GENERIC MAP (
+    g_nof_streams => g_nof_streams,
+    g_pipeline    => g_pipeline_input  -- 0 for wires, > 0 for registers,
+  )
+  PORT MAP (
+    rst          => dp_rst,
+    clk          => dp_clk,
+    -- ST sink
+    snk_in_arr   => in_sosi_arr,
+    -- ST source
+    src_out_arr  => in_sosi_arr_p
+  );
+
+  -- . read RAM
+  rd_copi <= nxt_r.rd_copi WHEN g_rd_latency = 1 ELSE r.rd_copi;
+
+END rtl;
diff --git a/libraries/base/dp/src/vhdl/dp_stream_pkg.vhd b/libraries/base/dp/src/vhdl/dp_stream_pkg.vhd
index dece1acc5d05756e51fa4ce82e21175e5b9903c6..e1fc62ec2221605273d8b325d3f8f50bea656594 100644
--- a/libraries/base/dp/src/vhdl/dp_stream_pkg.vhd
+++ b/libraries/base/dp/src/vhdl/dp_stream_pkg.vhd
@@ -298,7 +298,7 @@ PACKAGE dp_stream_pkg Is
   
   -- 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_sosi_arr; slv : STD_LOGIC_VECTOR; str : STRING) RETURN t_dp_sosi_arr;  -- also support slv fields
   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;
@@ -889,13 +889,19 @@ PACKAGE BODY dp_stream_pkg IS
   
   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
+    VARIABLE v_slv : STD_LOGIC_VECTOR(dp'RANGE) := slv(dp'RANGE);  -- map to ensure same range as for dp
   BEGIN
     FOR I IN dp'RANGE LOOP
+      -- use v_slv(I) to set individual sl field
       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);
+      -- use slv to set individual slv field
+      ELSIF str="BSN"     THEN v_dp(I).bsn     := RESIZE_DP_BSN(slv);
+      ELSIF str="CHANNEL" THEN v_dp(I).channel := RESIZE_DP_CHANNEL(slv);
+      ELSIF str="EMPTY"   THEN v_dp(I).empty   := RESIZE_DP_EMPTY(slv);
+      ELSIF str="ERR"     THEN v_dp(I).err     := RESIZE_DP_ERROR(slv);
       ELSE  REPORT "Error in func_dp_stream_arr_set for t_dp_sosi_arr";
       END IF;
     END LOOP;
diff --git a/libraries/base/dp/src/vhdl/mmp_dp_bsn_align_v2.vhd b/libraries/base/dp/src/vhdl/mmp_dp_bsn_align_v2.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..5f55dc5a6675482176658ff3d29b308769cde600
--- /dev/null
+++ b/libraries/base/dp/src/vhdl/mmp_dp_bsn_align_v2.vhd
@@ -0,0 +1,222 @@
+-- --------------------------------------------------------------------------
+-- Copyright 2021
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+-- http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+-- --------------------------------------------------------------------------
+--
+-- Author: Eric Kooistra, 6 Sept 2021
+-- Purpose: MMP for dp_bsn_align_v2
+-- Description:
+--   Add MM interfaces to dp_bsn_align_v2:
+--
+--   * Instantiates input BSN monitors when g_nof_input_bsn_monitors > 0
+--   * Instantiates output BSN monitor g_use_bsn_output_monitor = TRUE
+--   * Define MM reg for input enable/disable control for input i:
+--
+--      wi    Bits  Access     Type   Name
+--       i     [0]      RW  boolean   input_enable
+--
+--      where i = 0:g_nof_streams-1 and input_enable '1' is on, '0' is off
+--
+--   For more description see dp_bsn_align_v2 and
+--   https://support.astron.nl/confluence/display/L2M/L6+FWLIB+Design+Document%3A+BSN+aligner+v2
+
+LIBRARY IEEE, common_lib;
+USE IEEE.STD_LOGIC_1164.ALL;
+USE IEEE.NUMERIC_STD.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE work.dp_stream_pkg.ALL;
+
+
+ENTITY mmp_dp_bsn_align_v2 IS
+  GENERIC (
+    g_nof_streams                : NATURAL;           -- number of input and output streams
+    g_bsn_latency_max            : NATURAL;           -- Maximum travel latency of a remote block in number of block periods T_blk
+    g_nof_aligners_max           : NATURAL := 1;      -- 1 when only align at last node, > 1 when align at every intermediate node
+    g_block_size                 : NATURAL := 32;     -- > 1, g_block_size=1 is not supported
+    g_bsn_w                      : NATURAL := c_dp_stream_bsn_w;  -- number of bits in sosi BSN
+    g_data_w                     : NATURAL;           -- number of bits in sosi data
+    g_replacement_value          : INTEGER := 0;      -- output sosi data value for missing input blocks
+    g_nof_clk_per_sync           : NATURAL := 200*10**6;
+    g_nof_input_bsn_monitors     : NATURAL := 0;
+    g_use_bsn_output_monitor     : BOOLEAN := FALSE
+  );
+  PORT (
+    -- Memory-mapped clock domain
+    mm_rst                  : IN  STD_LOGIC;
+    mm_clk                  : IN  STD_LOGIC;
+
+    reg_copi                : IN  t_mem_copi;
+    reg_cipo                : OUT t_mem_cipo;
+
+    reg_input_monitor_copi  : IN  t_mem_copi;
+    reg_input_monitor_cipo  : OUT t_mem_cipo;
+
+    reg_output_monitor_copi : IN  t_mem_copi;
+    reg_output_monitor_cipo : OUT t_mem_cipo;
+
+    -- Streaming clock domain
+    dp_rst         : IN  STD_LOGIC;
+    dp_clk         : IN  STD_LOGIC;
+
+    node_index     : IN  NATURAL := 0;  -- only used when g_nof_aligners_max > 1
+
+    -- Streaming input
+    in_sosi_arr    : IN  t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+
+    -- Output via local MM in dp_clk domain
+    mm_copi        : IN  t_mem_copi;  -- read access to output block, all output streams share same mm_copi
+    mm_cipo_arr    : OUT t_mem_cipo_arr(g_nof_streams-1 DOWNTO 0);
+    mm_sosi        : OUT t_dp_sosi   -- streaming information that signals that an output block can be read
+  );
+END mmp_dp_bsn_align_v2;
+
+
+ARCHITECTURE str OF mmp_dp_bsn_align_v2 IS
+
+  -- Use one MM word (bit 0) per input_enable bit, similar as in dp_bsn_align_reg.vhd.
+
+  -- TYPE t_c_mem IS RECORD
+  --   latency   : NATURAL;    -- read latency
+  --   adr_w     : NATURAL;
+  --   dat_w     : NATURAL;
+  --   nof_dat   : NATURAL;    -- optional, nof dat words <= 2**adr_w
+  --   init_sl   : STD_LOGIC;  -- optional, init all dat words to std_logic '0', '1' or 'X'
+  CONSTANT c_mm_reg     : t_c_mem := (1, ceil_log2(g_nof_streams), 1, g_nof_streams, '0');
+
+  SIGNAL reg_wr         : STD_LOGIC_VECTOR(c_mm_reg.nof_dat*c_mm_reg.dat_w-1 DOWNTO 0);
+  SIGNAL stream_en_arr  : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+
+  SIGNAL mm_sosi_arr    : t_dp_sosi_arr(0 DOWNTO 0);
+
+BEGIN
+
+  u_reg : ENTITY common_lib.common_reg_r_w_dc
+  GENERIC MAP (
+    g_cross_clock_domain   => TRUE,
+    g_readback             => FALSE,
+    g_reg                  => c_mm_reg
+  )
+  PORT MAP (
+    -- Clocks and reset
+    mm_rst         => mm_rst,
+    mm_clk         => mm_clk,
+    st_rst         => dp_rst,
+    st_clk         => dp_clk,
+
+    -- Memory Mapped Slave in mm_clk domain
+    sla_in         => reg_copi,
+    sla_out        => reg_cipo,
+
+    -- MM registers in st_clk domain
+    reg_wr_arr     => OPEN,
+    reg_rd_arr     => OPEN,
+    out_reg        => reg_wr,   -- readback via ST clock domain
+    in_reg         => reg_wr
+  );
+
+  stream_en_arr <= reg_wr;
+
+  -- Use input BSN monitors for the first g_nof_input_bsn_monitors input
+  -- streams, e.g. to support:
+  -- . only one input stream (g_nof_input_bsn_monitors = 1), or
+  -- . all input streams (g_nof_input_bsn_monitors = g_nof_streams).
+  gen_bsn_mon_input : IF g_nof_input_bsn_monitors > 0 GENERATE
+    u_bsn_mon_input : ENTITY work.mms_dp_bsn_monitor_v2
+    GENERIC MAP (
+      g_nof_streams        => g_nof_input_bsn_monitors,
+      g_cross_clock_domain => TRUE,
+      g_sync_timeout       => g_nof_clk_per_sync,
+      g_bsn_w              => g_bsn_w,
+      g_error_bi           => 0,
+      g_cnt_sop_w          => c_word_w,
+      g_cnt_valid_w        => c_word_w,
+      g_cnt_latency_w      => c_word_w
+    )
+    PORT MAP (
+      -- Memory-mapped clock domain
+      mm_rst         => mm_rst,
+      mm_clk         => mm_clk,
+      reg_mosi       => reg_input_monitor_copi,
+      reg_miso       => reg_input_monitor_cipo,
+
+      -- Streaming clock domain
+      dp_rst         => dp_rst,
+      dp_clk         => dp_clk,
+      ref_sync       => in_sosi_arr(0).sync,  -- local reference sync input
+
+      in_siso_arr    => (OTHERS=>c_dp_siso_rdy),
+      in_sosi_arr    => in_sosi_arr(g_nof_input_bsn_monitors-1 DOWNTO 0)
+    );
+  END GENERATE;
+
+  gen_bsn_mon_output : IF g_use_bsn_output_monitor GENERATE
+    u_bsn_mon_output : ENTITY work.mms_dp_bsn_monitor_v2
+    GENERIC MAP (
+      g_nof_streams        => 1,  -- all outputs have same BSN monitor information
+      g_cross_clock_domain => TRUE,
+      g_sync_timeout       => g_nof_clk_per_sync,
+      g_bsn_w              => g_bsn_w,
+      g_error_bi           => 0,
+      g_cnt_sop_w          => c_word_w,
+      g_cnt_valid_w        => c_word_w,
+      g_cnt_latency_w      => c_word_w
+    )
+    PORT MAP (
+      -- Memory-mapped clock domain
+      mm_rst         => mm_rst,
+      mm_clk         => mm_clk,
+      reg_mosi       => reg_output_monitor_copi,
+      reg_miso       => reg_output_monitor_cipo,
+
+      -- Streaming clock domain
+      dp_rst         => dp_rst,
+      dp_clk         => dp_clk,
+      ref_sync       => in_sosi_arr(0).sync,  -- local reference sync input
+
+      in_siso_arr    => (OTHERS=>c_dp_siso_rdy),
+      in_sosi_arr    => mm_sosi_arr
+    );
+  END GENERATE;
+
+  u_bsn_align : ENTITY work.dp_bsn_align_v2
+  GENERIC MAP (
+    g_nof_streams                => g_nof_streams,
+    g_bsn_latency_max            => g_bsn_latency_max,
+    g_nof_aligners_max           => g_nof_aligners_max,
+    g_block_size                 => g_block_size,
+    g_bsn_w                      => g_bsn_w,
+    g_data_w                     => g_data_w,
+    g_replacement_value          => g_replacement_value
+  )
+  PORT MAP (
+    dp_rst         => dp_rst,
+    dp_clk         => dp_clk,
+    node_index     => node_index,
+    -- MM control
+    stream_en_arr  => stream_en_arr,
+    -- Streaming input
+    in_sosi_arr    => in_sosi_arr,
+    -- Output via local MM in dp_clk domain
+    mm_copi        => mm_copi,
+    mm_cipo_arr    => mm_cipo_arr,
+    mm_sosi        => mm_sosi
+  );
+
+  mm_sosi <= mm_sosi_arr(0);
+
+END str;
+
diff --git a/libraries/base/dp/tb/vhdl/tb_dp_block_from_mm.vhd b/libraries/base/dp/tb/vhdl/tb_dp_block_from_mm.vhd
index 7898f94d3415f65df10ac943340699cb361cff52..d139f3759ed1daaac47c051f7902127421137580 100644
--- a/libraries/base/dp/tb/vhdl/tb_dp_block_from_mm.vhd
+++ b/libraries/base/dp/tb/vhdl/tb_dp_block_from_mm.vhd
@@ -76,13 +76,12 @@ ARCHITECTURE tb OF tb_dp_block_from_mm IS
   SIGNAL block_done        : STD_LOGIC;
 
   SIGNAL rd_mosi           : t_mem_mosi;
-  SIGNAL rd_miso           : t_mem_miso;
+  SIGNAL rd_miso           : t_mem_miso := c_mem_miso_rst;
   
   SIGNAL blk_sosi          : t_dp_sosi;
   SIGNAL blk_siso          : t_dp_siso := c_dp_siso_rdy;
 
-  SIGNAL wr_mosi           : t_mem_mosi;
-  SIGNAL wr_miso           : t_mem_miso;
+  SIGNAL wr_mosi           : t_mem_mosi := c_mem_mosi_rst;
 
   -- needed for init and verify
   SIGNAL ram_wr_en         : STD_LOGIC := '0';
diff --git a/libraries/base/dp/tb/vhdl/tb_dp_bsn_align_v2.vhd b/libraries/base/dp/tb/vhdl/tb_dp_bsn_align_v2.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..4e62f1ceba00e9d1ddd859c1ef6ed081bfb85ec4
--- /dev/null
+++ b/libraries/base/dp/tb/vhdl/tb_dp_bsn_align_v2.vhd
@@ -0,0 +1,428 @@
+-- --------------------------------------------------------------------------
+-- Copyright 2021
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+-- http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+-- --------------------------------------------------------------------------
+--
+-- Author: Eric Kooistra, 3 Sept 2021
+-- Purpose: Verify dp_bsn_align_v2
+-- Description:
+-- Usage:
+-- > as 10
+-- > run -all
+  
+LIBRARY IEEE, common_lib, dp_lib;
+USE IEEE.std_logic_1164.ALL;
+USE IEEE.numeric_std.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE common_lib.common_str_pkg.ALL;
+USE common_lib.tb_common_pkg.ALL;
+USE dp_lib.dp_stream_pkg.ALL;
+USE dp_lib.tb_dp_pkg.ALL;
+
+
+ENTITY tb_dp_bsn_align_v2 IS
+  GENERIC (
+    -- DUT
+    g_nof_streams          : NATURAL := 2;      -- number of input and output streams
+    g_bsn_latency_max      : NATURAL := 2;      -- Maximum travel latency of a remote block in number of block periods T_blk
+    g_nof_aligners_max     : POSITIVE := 1;     -- 1 when only align at last node, > 1 when align at every intermediate node
+    g_block_size           : NATURAL := 11;     -- > 1, g_block_size=1 is not supported
+    g_block_period         : NATURAL := 20;     -- >= g_block_size, = g_block_size + c_gap_size
+    g_bsn_w                : NATURAL := c_dp_stream_bsn_w;  -- number of bits in sosi BSN
+    g_data_w               : NATURAL := 16;     -- number of bits in sosi data
+    g_replacement_value    : INTEGER := 17;      -- output sosi data replacement value for missing input blocks
+    g_use_mm_output        : BOOLEAN := FALSE;   -- output via MM or via streaming DP
+    g_pipeline_input       : NATURAL := 1;      -- >= 0, choose 0 for wires, choose 1 to ease timing closure
+    g_rd_latency           : NATURAL := 2;      -- 1 or 2, choose 2 to ease timing closure
+
+    -- TB
+    g_tb_diff_delay_max    : NATURAL := 10;      -- maximum nof clk delay between any inputs, <= c_align_latency_nof_clk
+    g_tb_nof_restart       : NATURAL := 2;       -- number of times to restart the input stimuli
+    g_tb_nof_blocks        : NATURAL := 20       -- number of input blocks per restart
+  );
+END tb_dp_bsn_align_v2;
+
+
+ARCHITECTURE tb OF tb_dp_bsn_align_v2 IS
+
+  CONSTANT c_rl                       : NATURAL := 1;
+  
+  CONSTANT c_data_w                   : NATURAL := 16;
+  CONSTANT c_data_init                : INTEGER := 0;
+  CONSTANT c_bsn_w                    : NATURAL := 16;  -- use <= 31 bit to fit NATURAL
+  CONSTANT c_bsn_init                 : NATURAL := 3;
+  CONSTANT c_channel_init             : INTEGER := 0;
+  CONSTANT c_err_init                 : NATURAL := 247;
+  CONSTANT c_sync_period              : NATURAL := 7;
+  CONSTANT c_sync_offset              : NATURAL := 2;
+  
+  CONSTANT c_gap_size                 : NATURAL := g_block_period - g_block_size;
+  CONSTANT c_dut_latency              : NATURAL := g_pipeline_input + g_rd_latency + 2;
+  CONSTANT c_align_latency_nof_blocks : NATURAL := g_bsn_latency_max;  -- DUT buffer latency in number blocks
+  CONSTANT c_align_latency_nof_valid  : NATURAL := g_bsn_latency_max * g_block_size;  -- DUT buffer latency in number of data samples
+  CONSTANT c_align_latency_nof_clk    : NATURAL := g_bsn_latency_max * g_block_period;  -- DUT buffer latency in number clk cycles
+  CONSTANT c_total_latency            : NATURAL := c_dut_latency + c_align_latency_nof_clk;
+  CONSTANT c_verify_nof_blocks        : NATURAL := g_tb_nof_blocks - c_align_latency_nof_blocks;  -- skip last blocks that are still in the DUT buffer
+
+  TYPE t_tb_state IS (s_idle, s_start, s_restart);
+
+  TYPE t_data_arr    IS ARRAY (g_nof_streams-1 DOWNTO 0) OF STD_LOGIC_VECTOR(c_data_w-1 DOWNTO 0);
+  TYPE t_bsn_arr     IS ARRAY (g_nof_streams-1 DOWNTO 0) OF STD_LOGIC_VECTOR(c_bsn_w-1 DOWNTO 0);
+  TYPE t_err_arr     IS ARRAY (g_nof_streams-1 DOWNTO 0) OF STD_LOGIC_VECTOR(c_dp_stream_error_w-1 DOWNTO 0);
+  TYPE t_channel_arr IS ARRAY (g_nof_streams-1 DOWNTO 0) OF STD_LOGIC_VECTOR(c_dp_stream_channel_w-1 DOWNTO 0);
+
+  TYPE t_reg IS RECORD
+    -- p_write_arr
+    sync         : STD_LOGIC;
+    bsn          : STD_LOGIC_VECTOR(g_bsn_w-1 DOWNTO 0);
+    out_sosi_arr : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  END RECORD;
+
+  SIGNAL tb_end_arr            : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0) := (OTHERS => '0');
+  SIGNAL tb_end                : STD_LOGIC;
+  SIGNAL clk                   : STD_LOGIC := '1';
+  SIGNAL rst                   : STD_LOGIC := '1';
+
+  SIGNAL node_index            : NATURAL := 0;
+
+  SIGNAL stream_en_arr         : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0) := (OTHERS => '1');  -- default all streams are enabled
+
+  SIGNAL ref_siso_arr          : t_dp_siso_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy);
+  SIGNAL ref_sosi_arr          : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL in_sosi_arr           : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
+
+  SIGNAL in_sync_arr           : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL in_sop_arr            : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL in_eop_arr            : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL in_val_arr            : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL in_data_arr           : t_data_arr;
+  SIGNAL in_bsn_arr            : t_bsn_arr;
+  SIGNAL in_channel_arr        : t_channel_arr;
+  SIGNAL in_err_arr            : t_err_arr;
+
+  SIGNAL mm_copi_arr           : t_mem_copi_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL mm_copi               : t_mem_copi;   -- read access to output block, all output streams share same mm_copi
+  SIGNAL mm_cipo_arr           : t_mem_cipo_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL mm_sosi               : t_dp_sosi;   -- streaming information that signals that an output block can be read
+  SIGNAL mm_done_arr           : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL mm_done               : STD_LOGIC;
+  SIGNAL dut_sosi_arr          : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL tb_sosi_arr           : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL r                     : t_reg;
+  SIGNAL nxt_r                 : t_reg;
+
+  SIGNAL out_siso_arr          : t_dp_siso_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy);
+  SIGNAL out_sosi_arr          : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
+  SIGNAL out_sosi              : t_dp_sosi;
+
+  SIGNAL out_sync_arr          : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL out_sop_arr           : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL out_eop_arr           : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL out_val_arr           : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0);
+  SIGNAL out_data_arr          : t_data_arr;
+  SIGNAL hold_data_arr         : t_data_arr;
+  SIGNAL out_bsn_arr           : t_bsn_arr;
+  SIGNAL out_channel_arr       : t_channel_arr;
+  SIGNAL out_err_arr           : t_err_arr;
+
+  SIGNAL tb_state              : t_tb_state;
+  SIGNAL tb_bsn                : INTEGER;
+  SIGNAL restart_cnt_arr       : t_nat_integer_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS => -1);
+  SIGNAL restart_cnt           : INTEGER := 0;
+  SIGNAL ref_sosi_arr_dly      : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
+  SIGNAL out_sosi_arr_exp      : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
+  SIGNAL out_sosi_exp          : t_dp_sosi;
+  SIGNAL verify_done_arr       : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0) := (OTHERS => '0');
+  SIGNAL verify_sosi_en_arr    : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0) := (OTHERS => '0');
+
+  SIGNAL hold_out_sop_arr      : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0) := (OTHERS => '0');
+  SIGNAL expected_out_bsn_arr  : t_bsn_arr;
+  SIGNAL expected_out_data_arr : t_data_arr;
+
+  -- Return input delay as function of inputs stream index I
+  FUNCTION func_input_delay(I : NATURAL) RETURN NATURAL IS
+  BEGIN
+    RETURN g_tb_diff_delay_max * I / (g_nof_streams - 1);
+  END;
+
+  SIGNAL dbg_tb_diff_delay_max : NATURAL := g_tb_diff_delay_max;
+  SIGNAL dbg_func_delay_max : NATURAL := func_input_delay(g_nof_streams - 1);
+
+BEGIN
+
+  clk <= (NOT clk) OR tb_end AFTER clk_period/2;
+  rst <= '1', '0' AFTER clk_period*7;
+  
+  ------------------------------------------------------------------------------
+  -- DATA GENERATION
+  ------------------------------------------------------------------------------
+  
+  -- Generate data path input data
+  gen_input : FOR I IN g_nof_streams-1 DOWNTO 0 GENERATE
+    p_stimuli : PROCESS
+      VARIABLE v_sync      : STD_LOGIC := '0';
+      VARIABLE v_bsn       : NATURAL;
+      VARIABLE v_data      : NATURAL := c_data_init;
+      VARIABLE v_channel   : NATURAL := c_channel_init;
+      VARIABLE v_err       : NATURAL := c_err_init;
+    BEGIN
+      v_data := v_data + I;
+      ref_sosi_arr(I) <= c_dp_sosi_rst;
+      proc_common_wait_until_low(clk, rst);
+      proc_common_wait_some_cycles(clk, 10);
+      restart_cnt_arr(I) <= restart_cnt_arr(I) + 1;
+
+      -- Begin of stimuli
+      FOR S IN 0 TO g_tb_nof_restart-1 LOOP
+        v_bsn := c_bsn_init;
+        IF S = 2 THEN
+          stream_en_arr(1) <= '0';
+        END IF;
+        FOR R IN 0 TO g_tb_nof_blocks-1 LOOP
+          v_sync := sel_a_b(v_bsn 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, 0, 0, g_block_size, v_channel, v_err, v_sync, TO_UVEC(v_bsn, c_bsn_w), clk, stream_en_arr(I), ref_siso_arr(I), ref_sosi_arr(I));
+          v_bsn  := v_bsn + 1;
+          v_data := v_data + g_block_size;
+          proc_common_wait_some_cycles(clk, c_gap_size);  -- create gap between frames
+        END LOOP;
+        -- no gap between restarts, to ease verification by maintaining fixed latency of out_sosi_arr_exp
+        restart_cnt_arr(I) <= restart_cnt_arr(I) + 1;
+      END LOOP;
+
+      -- End of stimuli, g_bsn_latency_max blocks remain in DUT buffer
+      expected_out_bsn_arr(I) <= TO_UVEC(v_bsn-1 - c_align_latency_nof_blocks, c_bsn_w);
+      expected_out_data_arr(I) <= TO_UVEC(v_data-1 - c_align_latency_nof_valid, c_data_w);
+      
+      proc_common_wait_some_cycles(clk, 100);
+      verify_done_arr(I) <= '1';
+      proc_common_wait_some_cycles(clk, 1);
+      verify_done_arr(I) <= '0';
+      
+      tb_end_arr(I) <= '1';
+      WAIT;
+    END PROCESS;
+  END GENERATE;
+
+  -- Use tb_state to view tb progress in Wave window
+  restart_cnt <= restart_cnt_arr(0);
+
+  p_tb_state : PROCESS(restart_cnt)
+  BEGIN
+    tb_state <= s_idle;
+    IF restart_cnt = 0 THEN tb_state <= s_start; END IF;
+    IF restart_cnt = 1 THEN tb_state <= s_restart; END IF;
+    IF restart_cnt > 1 THEN tb_state <= s_restart; END IF;
+  END PROCESS;
+
+  -- Create latency misalignment between the input streams
+  gen_in_sosi_arr : FOR I IN g_nof_streams-1 DOWNTO 0 GENERATE
+    in_sosi_arr(I) <= TRANSPORT ref_sosi_arr(I) AFTER func_input_delay(I) * clk_period;
+  END GENERATE;
+
+
+  tb_end <= vector_and(tb_end_arr);
+  
+  mon_sosi : FOR I IN g_nof_streams-1 DOWNTO 0 GENERATE
+    -- Ease in_sosi_arr monitoring
+    in_sync_arr(I)    <= in_sosi_arr(I).sync;
+    in_sop_arr(I)     <= in_sosi_arr(I).sop;
+    in_eop_arr(I)     <= in_sosi_arr(I).eop;
+    in_val_arr(I)     <= in_sosi_arr(I).valid;
+    in_data_arr(I)    <= in_sosi_arr(I).data(c_data_w-1 DOWNTO 0);
+    in_bsn_arr(I)     <= in_sosi_arr(I).bsn(c_bsn_w-1 DOWNTO 0);
+    in_channel_arr(I) <= in_sosi_arr(I).channel;
+    in_err_arr(I)     <= in_sosi_arr(I).err;
+
+    -- Ease out_sosi_arr monitoring and verification
+    out_sync_arr(I)    <= out_sosi_arr(I).sync;
+    out_sop_arr(I)     <= out_sosi_arr(I).sop;
+    out_eop_arr(I)     <= out_sosi_arr(I).eop;
+    out_val_arr(I)     <= out_sosi_arr(I).valid;
+    out_data_arr(I)    <= out_sosi_arr(I).data(c_data_w-1 DOWNTO 0);
+    out_bsn_arr(I)     <= out_sosi_arr(I).bsn(c_bsn_w-1 DOWNTO 0);
+    out_channel_arr(I) <= out_sosi_arr(I).channel;
+    out_err_arr(I)     <= out_sosi_arr(I).err;
+  END GENERATE;
+
+  out_sosi <= out_sosi_arr(0);  -- take out_sosi control and info from out_sosi_arr(0)
+
+  ------------------------------------------------------------------------------
+  -- DATA VERIFICATION, use multiple ways to increase coverage
+  -- a) Use proc_dp_verify_*() to verify output compared to prev output
+  -- b) Use delayed in_sosi_arr as expected out_sosi_arr
+  ------------------------------------------------------------------------------
+
+  tb_bsn <= TO_UINT(out_sosi.bsn);
+
+  ref_sosi_arr_dly <= TRANSPORT ref_sosi_arr AFTER c_total_latency * clk_period;
+  out_sosi_arr_exp <= ref_sosi_arr_dly WHEN rising_edge(clk);
+  out_sosi_exp <= out_sosi_arr_exp(0);  -- take out_sosi_exp control and info from out_sosi_arr_exp(0)
+
+  gen_verify_ctrl : FOR I IN g_nof_streams-1 DOWNTO 0 GENERATE
+    -- . Verify that sop and eop come in pairs
+    proc_dp_verify_sop_and_eop(clk, out_val_arr(I), out_sop_arr(I), out_eop_arr(I), hold_out_sop_arr(I));
+
+    -- . No data verification here, using p_verify_sosi is easier than using proc_dp_verify_data().
+
+    -- . Verify that the stimuli have been applied at all
+    hold_data_arr(I) <= out_data_arr(I) WHEN out_val_arr(I) = '1';  -- hold last valid data
+
+    proc_dp_verify_value("out_data_arr", e_equal, clk, verify_done_arr(I), expected_out_data_arr(I), hold_data_arr(I));
+    proc_dp_verify_value("out_bsn_arr", e_equal, clk, verify_done_arr(I), expected_out_bsn_arr(I), out_bsn_arr(I));
+  END GENERATE;
+  
+  -- . Use delayed in_sosi_arr as expected out_sosi_arr, this is possible
+  --   because the DUT has no flow control and has a fixed latency.
+  p_verify_sosi_en_arr : PROCESS(out_sosi_exp)
+  BEGIN
+    IF g_tb_diff_delay_max <= c_align_latency_nof_clk THEN
+      verify_sosi_en_arr <= (OTHERS => '1');
+      IF TO_UINT(out_sosi_exp.bsn) - c_bsn_init >= c_verify_nof_blocks THEN
+        verify_sosi_en_arr <= (OTHERS => '0');
+      END IF;
+    END IF;
+  END PROCESS;
+
+  gen_verify_streams : FOR I IN g_nof_streams-1 DOWNTO 0 GENERATE
+    p_verify_sosi : PROCESS(clk)
+    BEGIN
+      IF rising_edge(clk) THEN
+        IF verify_sosi_en_arr(I) = '1' AND out_sosi_arr_exp(I).valid = '1' THEN
+           ASSERT out_sosi_arr(I).sync = out_sosi_arr_exp(I).sync REPORT "Wrong sync for output " & int_to_str(I) SEVERITY ERROR;
+           ASSERT out_sosi_arr(I).sop = out_sosi_arr_exp(I).sop REPORT "Wrong sop for output " & int_to_str(I) SEVERITY ERROR;
+           ASSERT out_sosi_arr(I).eop = out_sosi_arr_exp(I).eop REPORT "Wrong eop for output " & int_to_str(I) SEVERITY ERROR;
+           ASSERT out_sosi_arr(I).valid = out_sosi_arr_exp(I).valid REPORT "Wrong valid for output " & int_to_str(I) SEVERITY ERROR;
+           IF stream_en_arr(I) = '1' THEN
+             ASSERT out_sosi_arr(I).data  = out_sosi_arr_exp(I).data REPORT "Wrong data for output " & int_to_str(I) & " : "
+                                                                            & int_to_str(TO_UINT(out_sosi_arr(I).data)) & " /= "
+                                                                            & int_to_str(TO_UINT(out_sosi_arr_exp(I).data)) SEVERITY ERROR;
+           ELSE
+             ASSERT TO_UINT(out_sosi_arr(I).data) = g_replacement_value REPORT "Wrong data for output " & int_to_str(I) & " : "
+                                                                               & int_to_str(TO_UINT(out_sosi_arr(I).data)) & " /= "
+                                                                               & int_to_str(g_replacement_value) SEVERITY ERROR;
+           END IF;
+        END IF;
+      END IF;
+    END PROCESS;
+  END GENERATE;
+
+  ------------------------------------------------------------------------------
+  -- DUT 
+  ------------------------------------------------------------------------------
+  
+  u_bsn_align : ENTITY work.dp_bsn_align_v2
+  GENERIC MAP (
+    g_nof_streams                => g_nof_streams,
+    g_bsn_latency_max            => g_bsn_latency_max,
+    g_nof_aligners_max           => g_nof_aligners_max,
+    g_block_size                 => g_block_size,
+    g_bsn_w                      => g_bsn_w,
+    g_data_w                     => g_data_w,
+    g_replacement_value          => g_replacement_value,
+    g_use_mm_output              => g_use_mm_output,    -- output via MM or via streaming DP
+    g_pipeline_input             => g_pipeline_input,   -- >= 0, choose 0 for wires, choose 1 to ease timing closure
+    g_rd_latency                 => g_rd_latency        -- 1 or 2, choose 2 to ease timing closure
+  )
+  PORT MAP (
+    dp_rst         => rst,
+    dp_clk         => clk,
+    -- Control
+    node_index     => node_index,
+    stream_en_arr  => stream_en_arr,
+    -- Streaming input
+    in_sosi_arr    => in_sosi_arr,
+    -- Output via local MM interface in dp_clk domain
+    mm_copi        => mm_copi,
+    mm_cipo_arr    => mm_cipo_arr,
+    mm_sosi        => mm_sosi,
+
+    -- Output via streaming DP interface
+    out_sosi_arr   => dut_sosi_arr
+  );
+
+  ------------------------------------------------------------------------------
+  -- MM to streaming DP
+  ------------------------------------------------------------------------------
+  no_use_mm_output : IF NOT g_use_mm_output GENERATE
+    out_sosi_arr <= dut_sosi_arr;
+  END GENERATE;
+
+  gen_use_mm_output : IF g_use_mm_output GENERATE
+    mm_copi <= mm_copi_arr(0);
+    mm_done <= mm_done_arr(0);   -- for viewing only
+
+    gen_mm_to_dp : FOR I IN 0 TO g_nof_streams-1 GENERATE
+      u_mm_to_dp: ENTITY work.dp_block_from_mm
+      GENERIC MAP (
+        g_data_size          => 1,
+        g_step_size          => 1,
+        g_nof_data           => g_block_size,
+        g_data_w             => g_data_w,
+        g_mm_rd_latency      => g_rd_latency,
+        g_reverse_word_order => FALSE
+      )
+      PORT MAP (
+        rst           => rst,
+        clk           => clk,
+        start_pulse   => mm_sosi.sop,
+        start_address => 0,
+        mm_done       => mm_done_arr(I),
+        mm_mosi       => mm_copi_arr(I),
+        mm_miso       => mm_cipo_arr(I),
+        out_sosi      => tb_sosi_arr(I),
+        out_siso      => c_dp_siso_rdy
+      );
+    END GENERATE;
+
+    p_comb : PROCESS(r, mm_sosi, tb_sosi_arr)
+      VARIABLE v : t_reg;
+    BEGIN
+      v := r;
+
+      -- hold mm_sosi.sync, bsn
+      IF mm_sosi.sop = '1' THEN
+        v.sync := mm_sosi.sync;
+        v.bsn  := mm_sosi.bsn(g_bsn_w-1 DOWNTO 0);
+      END IF;
+
+      -- apply mm_sosi.sync, bsn at sop to all streams in out_sosi_arr
+      v.out_sosi_arr := tb_sosi_arr;
+      IF tb_sosi_arr(0).sop = '1' THEN
+        v.out_sosi_arr := func_dp_stream_arr_set(v.out_sosi_arr, r.sync, "SYNC");
+        v.out_sosi_arr := func_dp_stream_arr_set(v.out_sosi_arr, r.bsn, "BSN");
+      ELSE
+        -- hold sosi.bsn until next sop, to easy view in wave window
+        FOR I IN 0 TO g_nof_streams-1 LOOP
+          v.out_sosi_arr(I).bsn := r.out_sosi_arr(I).bsn;
+        END LOOP;
+      END IF;
+
+      -- next state
+      nxt_r <= v;
+    END PROCESS;
+
+    p_reg : PROCESS(clk)
+    BEGIN
+      IF rising_edge(clk) THEN
+        r <= nxt_r;
+      END IF;
+    END PROCESS;
+
+    out_sosi_arr <= nxt_r.out_sosi_arr;
+  END GENERATE;
+
+END tb;
diff --git a/libraries/base/dp/tb/vhdl/tb_mmp_dp_bsn_align_v2.vhd b/libraries/base/dp/tb/vhdl/tb_mmp_dp_bsn_align_v2.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..2b624d5d125f2c1f117c8b18c2fd3e7a2b867f55
--- /dev/null
+++ b/libraries/base/dp/tb/vhdl/tb_mmp_dp_bsn_align_v2.vhd
@@ -0,0 +1,189 @@
+-- --------------------------------------------------------------------------
+-- Copyright 2021
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+-- http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+-- --------------------------------------------------------------------------
+--
+-- Author: E. Kooistra, 6 sept 2021
+-- Purpose: Verify MM part of mmp_dp_bsn_align_v2
+-- Description:
+--    The functional part is already verified by tb_tb_dp_bsn_align_v2.vhd.
+-- Usage:
+-- > as 5
+-- > run -all
+  
+LIBRARY IEEE, common_lib, technology_lib;
+USE IEEE.std_logic_1164.ALL;
+USE IEEE.numeric_std.ALL;
+USE common_lib.common_pkg.ALL;
+USE common_lib.tb_common_pkg.ALL;
+USE common_lib.common_mem_pkg.ALL;
+USE common_lib.tb_common_mem_pkg.ALL; 
+USE common_lib.common_str_pkg.ALL;
+USE work.dp_stream_pkg.ALL;
+USE work.tb_dp_pkg.ALL;
+
+ENTITY tb_mmp_dp_bsn_align_v2 IS
+END tb_mmp_dp_bsn_align_v2;
+
+
+ARCHITECTURE tb OF tb_mmp_dp_bsn_align_v2 IS
+
+  CONSTANT c_mm_clk_period              : TIME := 40 ns;
+  CONSTANT c_dp_clk_period              : TIME := 10 ns;
+  CONSTANT c_cross_clock_domain_latency : NATURAL := 20;
+
+  CONSTANT c_report_note                : BOOLEAN := FALSE;  -- Use TRUE for tb debugging, else FALSE to keep Transcript window more empty
+
+  CONSTANT c_nof_input_sync             : NATURAL := 10;
+  CONSTANT c_nof_block_per_sync         : NATURAL := 32;
+  CONSTANT c_block_size                 : NATURAL := 10;
+  CONSTANT c_input_gap_size             : NATURAL := 3;
+  CONSTANT c_sim_nof_blocks             : NATURAL := c_nof_block_per_sync * c_nof_input_sync;
+
+  CONSTANT c_nof_streams                : NATURAL := 2;
+  CONSTANT c_bsn_latency_max            : POSITIVE := 2;
+  CONSTANT c_nof_aligners_max           : NATURAL := 1;
+  CONSTANT c_bsn_w                      : NATURAL := c_dp_stream_bsn_w;
+  CONSTANT c_data_w                     : NATURAL := 16;
+  CONSTANT c_replacement_value          : INTEGER := 0;
+  CONSTANT c_nof_clk_per_sync           : NATURAL := 200*10**6;
+  CONSTANT c_nof_input_bsn_monitors     : NATURAL := 0;
+  CONSTANT c_use_bsn_output_monitor     : BOOLEAN := FALSE;
+
+  SIGNAL tb_end                   : STD_LOGIC := '0';
+  SIGNAL stimuli_end              : STD_LOGIC := '0';
+
+  -- MM clock domain
+  SIGNAL mm_clk                   : STD_LOGIC := '1';
+  SIGNAL mm_rst                   : STD_LOGIC := '1';
+
+  SIGNAL reg_copi                 : t_mem_copi := c_mem_copi_rst;
+  SIGNAL reg_cipo                 : t_mem_cipo;
+  SIGNAL reg_input_monitor_copi   : t_mem_copi := c_mem_copi_rst;
+  SIGNAL reg_input_monitor_cipo   : t_mem_cipo;
+  SIGNAL reg_output_monitor_copi  : t_mem_copi := c_mem_copi_rst;
+  SIGNAL reg_output_monitor_cipo  : t_mem_cipo;
+
+  -- DP clock domain
+  SIGNAL dp_clk                   : STD_LOGIC := '1';
+  SIGNAL dp_rst                   : STD_LOGIC := '1';
+
+  SIGNAL node_index               : NATURAL := 0;  -- only used when g_bsn_latency_use_node_index is TRUE
+  SIGNAL stimuli_sosi             : t_dp_sosi;
+  SIGNAL in_sosi_arr              : t_dp_sosi_arr(c_nof_streams-1 DOWNTO 0);
+  SIGNAL mm_copi                  : t_mem_copi;   -- read access to output block, all output streams share same mm_copi
+  SIGNAL mm_cipo_arr              : t_mem_cipo_arr(c_nof_streams-1 DOWNTO 0);
+  SIGNAL mm_sosi                  : t_dp_sosi;   -- streaming information that signals that an output block can be read
+
+BEGIN
+
+  dp_clk <= (NOT dp_clk) OR tb_end AFTER c_dp_clk_period/2;
+  mm_clk <= (NOT mm_clk) OR tb_end AFTER c_mm_clk_period/2;
+  dp_rst <= '1', '0' AFTER c_dp_clk_period*7;    
+  mm_rst <= '1', '0' AFTER c_mm_clk_period*7;
+  
+  ------------------------------------------------------------------------------
+  -- MM stimuli and verification
+  ------------------------------------------------------------------------------
+
+  p_stimuli_and_verify_mm : PROCESS
+    VARIABLE v_bsn : NATURAL;
+  BEGIN              
+    proc_common_wait_until_low(dp_clk, mm_rst);
+    proc_common_wait_until_low(dp_clk, dp_rst);
+    proc_common_wait_some_cycles(mm_clk, 5);
+
+
+    ---------------------------------------------------------------------------
+    -- End of test
+    ---------------------------------------------------------------------------
+    proc_common_wait_until_high(dp_clk, stimuli_end);
+    tb_end <= '1';
+    WAIT;
+  END PROCESS;
+
+  ------------------------------------------------------------------------------
+  -- Streaming stimuli
+  ------------------------------------------------------------------------------
+
+  -- Generate data blocks with input sync
+  u_stimuli : ENTITY work.dp_stream_stimuli
+  GENERIC MAP (
+    g_sync_period  => c_nof_block_per_sync,
+    g_err_init     => 0,
+    g_err_incr     => 0,  -- do not increment, to not distract from viewing of BSN in Wave window
+    g_channel_init => 0,
+    g_channel_incr => 0,  -- do not increment, to not distract from viewing of BSN in Wave window
+    g_nof_repeat   => c_sim_nof_blocks,
+    g_pkt_len      => c_block_size,
+    g_pkt_gap      => c_input_gap_size
+  )
+  PORT MAP (
+    rst               => dp_rst,
+    clk               => dp_clk,
+
+    -- Generate stimuli
+    src_out           => stimuli_sosi,
+
+    -- End of stimuli
+    tb_end            => stimuli_end
+  );
+
+  in_sosi_arr <= (OTHERS => stimuli_sosi);
+
+  ------------------------------------------------------------------------------
+  -- DUT
+  ------------------------------------------------------------------------------
+
+  u_bsn_align : ENTITY work.mmp_dp_bsn_align_v2
+  GENERIC MAP (
+    g_nof_streams                => c_nof_streams,
+    g_bsn_latency_max            => c_bsn_latency_max,
+    g_nof_aligners_max           => c_nof_aligners_max,
+    g_block_size                 => c_block_size,
+    g_bsn_w                      => c_bsn_w,
+    g_data_w                     => c_data_w,
+    g_replacement_value          => c_replacement_value,
+    g_nof_clk_per_sync           => c_nof_clk_per_sync,
+    g_nof_input_bsn_monitors     => c_nof_input_bsn_monitors,
+    g_use_bsn_output_monitor     => c_use_bsn_output_monitor
+  )
+  PORT MAP (
+    mm_rst                  => mm_rst,
+    mm_clk                  => mm_clk,
+
+    reg_copi                => reg_copi,
+    reg_cipo                => reg_cipo,
+
+    reg_input_monitor_copi  => reg_input_monitor_copi,
+    reg_input_monitor_cipo  => reg_input_monitor_cipo,
+
+    reg_output_monitor_copi => reg_output_monitor_copi,
+    reg_output_monitor_cipo => reg_output_monitor_cipo,
+
+    dp_rst                  => dp_rst,
+    dp_clk                  => dp_clk,
+
+    node_index              => node_index,
+    -- Streaming input
+    in_sosi_arr             => in_sosi_arr,
+    -- Output via local MM in dp_clk domain
+    mm_copi                 => mm_copi,
+    mm_cipo_arr             => mm_cipo_arr,
+    mm_sosi                 => mm_sosi
+  );
+
+END tb;
diff --git a/libraries/base/dp/tb/vhdl/tb_tb_dp_bsn_align_v2.vhd b/libraries/base/dp/tb/vhdl/tb_tb_dp_bsn_align_v2.vhd
new file mode 100644
index 0000000000000000000000000000000000000000..f47d2acf82d36d526f01bd4df781fd3e733b094f
--- /dev/null
+++ b/libraries/base/dp/tb/vhdl/tb_tb_dp_bsn_align_v2.vhd
@@ -0,0 +1,70 @@
+-- --------------------------------------------------------------------------
+-- Copyright 2021
+-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
+-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
+--
+-- Licensed under the Apache License, Version 2.0 (the "License");
+-- you may not use this file except in compliance with the License.
+-- You may obtain a copy of the License at
+--
+-- http://www.apache.org/licenses/LICENSE-2.0
+--
+-- Unless required by applicable law or agreed to in writing, software
+-- distributed under the License is distributed on an "AS IS" BASIS,
+-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+-- See the License for the specific language governing permissions and
+-- limitations under the License.
+-- --------------------------------------------------------------------------
+--
+-- Author: E. Kooistra, 15 sept 2021
+-- Purpose: Regression multi tb for dp_bsn_align_v2
+-- Description:
+-- Usage:
+-- > as 3
+-- > run -all
+
+LIBRARY IEEE;
+USE IEEE.std_logic_1164.ALL;
+USE work.tb_dp_pkg.ALL;
+
+
+ENTITY tb_tb_dp_bsn_align_v2 IS
+END tb_tb_dp_bsn_align_v2;
+
+
+ARCHITECTURE tb OF tb_tb_dp_bsn_align_v2 IS
+
+  CONSTANT c_bsn_latency_max      : POSITIVE := 1;
+  CONSTANT c_block                : NATURAL := 11;
+  CONSTANT c_period               : NATURAL := 20;
+  CONSTANT c_delay_max            : NATURAL := c_bsn_latency_max * c_period;
+ 
+  SIGNAL tb_end : STD_LOGIC := '0';  -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
+
+BEGIN
+
+  -- -- DUT
+  -- g_nof_streams                : NATURAL := 2;      -- number of input and output streams
+  -- g_bsn_latency_max            : NATURAL := 1;      -- Maximum travel latency of a remote block in number of block periods T_blk
+  -- g_nof_aligners_max           : NATURAL := 1;      -- 1 when only align at last node, > 1 when align at every intermediate node
+  -- g_block_size                 : NATURAL := 11;     -- > 1, g_block_size=1 is not supported
+  -- g_block_period               : NATURAL := 20;     -- >= g_block_size, = g_block_size + c_gap_size
+  -- g_bsn_w                      : NATURAL := c_dp_stream_bsn_w;  -- number of bits in sosi BSN
+  -- g_data_w                     : NATURAL := 16;     -- number of bits in sosi data
+  -- c_replacement_value          : INTEGER := 0;      -- output sosi data replacement value for missing input blocks
+  -- g_use_mm_output              : BOOLEAN := FALSE;  -- output via MM or via streaming DP
+  -- g_pipeline_input             : NATURAL := 1;      -- >= 0, choose 0 for wires, choose 1 to ease timing closure
+  -- g_rd_latency                 : NATURAL := 2;      -- 1 or 2, choose 2 to ease timing closure
+  --
+  -- -- TB
+  -- g_tb_diff_delay_max    : NATURAL := 45;      -- maximum nof clk delay between any inputs, <= c_align_latency
+  -- g_tb_nof_restart       : NATURAL := 1;       -- number of times to restart the input stimuli
+  -- g_tb_nof_blocks        : NATURAL := 10       -- number of input blocks per restart
+
+  u_mm_output          : ENTITY work.tb_dp_bsn_align_v2 GENERIC MAP (2, c_bsn_latency_max, 1, c_block, c_period, 32, 16, 17,  TRUE, 0, 1,                0, 1, 50);
+  u_dp_output          : ENTITY work.tb_dp_bsn_align_v2 GENERIC MAP (2, c_bsn_latency_max, 1, c_block, c_period, 32, 16, 17, FALSE, 0, 1,                0, 1, 50);
+
+  u_diff_delay_no_loss : ENTITY work.tb_dp_bsn_align_v2 GENERIC MAP (2, c_bsn_latency_max, 1, c_block, c_period, 32, 16, 17, FALSE, 0, 1,      c_delay_max, 1, 50);
+  --u_loss_replacement   : ENTITY work.tb_dp_bsn_align_v2 GENERIC MAP (2, c_bsn_latency_max, 1, c_block, c_period, 32, 16, 17, FALSE, 0, 1, 40 + c_delay_max, 1, 50);
+
+END tb;