From 634d058ba1fd48a0bd85e4c483d7b53fa361f6f7 Mon Sep 17 00:00:00 2001
From: Pepping <pepping>
Date: Thu, 12 Feb 2015 11:05:18 +0000
Subject: [PATCH] Copied source files from $UNB

---
 .../src/vhdl/node_unb1_fn_terminal_db.vhd     | 436 ++++++++++++++++
 .../src/vhdl/unb1_fn_terminal_db.vhd          | 487 ++++++++++++++++++
 .../tb/vhdl/tb_node_unb1_fn_terminal_db.vhd   | 458 ++++++++++++++++
 3 files changed, 1381 insertions(+)
 create mode 100644 boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/node_unb1_fn_terminal_db.vhd
 create mode 100644 boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/unb1_fn_terminal_db.vhd
 create mode 100644 boards/uniboard1/designs/unb1_fn_terminal_db/tb/vhdl/tb_node_unb1_fn_terminal_db.vhd

diff --git a/boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/node_unb1_fn_terminal_db.vhd b/boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/node_unb1_fn_terminal_db.vhd
new file mode 100644
index 0000000000..077c748b99
--- /dev/null
+++ b/boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/node_unb1_fn_terminal_db.vhd
@@ -0,0 +1,436 @@
+-------------------------------------------------------------------------------
+--
+-- Copyright (C) 2012
+-- 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: User Rx interface for the UniBoard mesh
+--
+-- Description:
+-- . The node_fn_terminal_db can receive up to 4*4 user steams via 4*3 phy
+--   lanes on the UniBoard mesh. The phy streams are DP/UTH encoded and 
+--   get decoded and output via dp_out_sosi_arr.
+-- . If g_mesh_use_tx=TRUE then the node_fn_terminal_db can also transmit test
+--   data for bidirectional transceiver diagnostic purposes. The IO phy is 
+--   tr_nonbonded.
+-- . If g_use_bsn_align=TRUE then the dp_out_sosi_arr user streams are also
+--   BSN aligned.
+-- . If g_use_data_buf=TRUE then at every sync the dp_out_sosi_arr blocks get
+--   captured into a diag_databuffer for monitoring via MM.
+-- . If g_mesh_mon_select/=0 then also internal signals in the
+--   unb_terminals_mesh can be monitored via a diag_databuffer.
+--
+-- Remarks:
+--
+--   Explanation of impact of dp_distribute on c_rx_output_fifo_size:
+--     The terminals transport c_usr_nof_streams_per_bus=4 blocks onto
+--     g_mesh_nof_serial=3 lanes. This has an impact on c_rx_output_fifo_size.
+--     The dp_distribute from 4 --> 3 causes a transpose such that the 4 usr
+--     streams for t=0 are being transmitted via lane 0. While this happens
+--     one g_usr_block_per later the 4 usr blocks for t=1 will be transmitted
+--     via lane 1, and again one g_usr_block_per later the 4 usr blocks for
+--     t=2 will be transmitted via lane 2:
+--    
+--              3*g_usr_block_per  3*g_usr_block_per  3*g_usr_block_per
+--             <-----------------><-----------------><----------------->
+--     lane 0: Block_0_1_2_3(t0)  Block_0_1_2_3(t3)  Block_0_1_2_3(t6)
+--     lane 1:       Block_0_1_2_3(t1)  Block_0_1_2_3(t4)  ...
+--     lane 2:             Block_0_1_2_3(t2)  Block_0_1_2_3(t5)  ...
+--    
+--     In fact the transport of the 4 usr streams via one lane takes 3 time
+--     blocks (= 3*g_usr_block_per). The BSN aligner needs to align the 4
+--     usr streams until they are all present at the inputs of the BSN aligner
+--     the FIFO must be able to buffer c_burst_usr_nof_block = 3 blocks,
+--     because there are g_mesh_nof_serial-1 = +2 other lanes that already
+--     send blocks for t1 and t2 during t0 on lane 0 and +1 because it is a
+--     fill FIFO that stores at least 1 complete frame.
+--   
+--   Explanation of impact of dp_distribute on BSN align latency:
+--     In a subrack simulation with g_unb_sys=4,1,4 it follows that the BSN
+--     difference can be as much as 4 for UNB1/FN0. The time difference
+--     between BSN 0 for these two streams is then 5195 ns = 4.06 
+--     g_usr_block_per. For a single UniBoard simulation with g_unb_sys=1,1,4
+--     it follows that the BSN difference becomes 2 and almost 3. The time
+--     difference between these two streams is than 2495 ns = 1.95 
+--     g_usr_block_per. To support c_bsn_latency for the dp_bsn_align the
+--     c_burst_bsn_latency therefore needs to be increased. For both subrack
+--     and single Uniboard (as set by g_multi_unb) choose the same BSN latency
+--     adjustment of +c_burst_usr_nof_block. For the subrack sop timeout needs
+--     to be even > 5 g_usr_block_per, because otherwise the BSN difference
+--     of 4 still gets missed. Therefore use c_bsn_latency = 2, so then
+--     c_burst_bsn_latency = 2 + 3 = 5. Note that for the BSN comparison logic
+--     the preferred values for g_bsn_latency are 3, 7, 15 because these 
+--     require the least logic. Similar for the c_rx_output_fifo_size 
+--     g_bsn_latency = 3 and 7 would result in using 1 RAMB or 2 RAMB in
+--     case that g_usr_block_len=96. Therefore choose c_bsn_latency = 3 to
+--     have some extra margin without logic or RAMB cost. The rules from
+--     dp_bsn_align.vhd for how to choose the timeouts and the FIFO size
+--     should therefore now be applied with c_burst_bsn_latency.
+--   
+--   Explanation of impact of dp_distribute on c_phy_rx_fifo_size:
+--     The dp_distribute uses one of the dual clock FIFO in tr_nonbonded to
+--     fill with less than 1 block, the dual clock FIFOs on the oFirmware/designs/fn_terminal_db/src/vhdl/node_fn_terminal_db.vhdther
+--     g_mesh_nof_serial-1 lanes only fill with 1 word. This less than one
+--     block was observed in simulation. Assume that indeed c_phy_rx_fifo_len
+--     = 1 block is sufficient to avoid using more RAM than needed.
+--   
+--   Explanation of impact of c_rx_timeout_w on c_phy_rx_fifo_size:
+--     The uth_rx timeout ensures that the rx FIFO in tr_nonbonded does not
+--     overflow if the reception should suddenly stop during a frame.
+--     If the c_rx_timeout_w is set +1 larger then the rx FIFO will overflow
+--     as was seen in simulation. Temporarily setting the severity in
+--     proc_common_fifo_asserts() to ERROR instead of FAILURE shows that the
+--     terminals will recover from this overflow. The reason is that the
+--     overflow will not corrupt the FIFO control, the uth_rx will ensure
+--     that only complete packets get passed on and the BSN aligner will
+--     after some flushing then recover the Rx alignment.
+--     The uth_rx timeout restarts on every valid. In simulation one of the
+--     4 uth_rx reaches a timeout_cnt of 71 so close to 1 g_usr_block_per.
+--     The other three reach at most 2 words. Typically the gap should be
+--     < g_usr_block_len, because that is the maximum time that the BSN
+--     aligner holds the sop. Hence using ceil_log2(g_usr_block_per)
+--     yields a sufficient upper value. It is not necessary to add +1. It
+--     is also not good to use less, because there could occur quite some
+--     data not valid gap time between the sop and the next valid, due to
+--     the BSN aligner.
+--   
+-- Some more remarks:
+--  . Use ceil_value to get the maximum FIFO size for the requested size.
+--  . In fact c_burst_usr_nof_block depends on whether the terminals use
+--    dp_distribute, because dp_distribute causes a transpose that results
+--    in a burst.
+--  . The c_bsn_latency also depends on whether there is a backplane or
+--    not so on g_multi_unb. Therefore alternatively c_bsn_latency =
+--    sel_a_b(g_multi_unb, 3, 0) could be used.
+--  . Alternatively c_bsn_latency could be made available as generic and
+--    set directly by the user. The c_burst_usr_nof_block can then be
+--    removed to let all settings directly depend on g_bsn_latency. The
+--    advantage is that it
+
+
+LIBRARY IEEE, common_lib, dp_lib, unb_common_lib, diag_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 dp_lib.dp_stream_pkg.ALL;
+USE unb_common_lib.unb_common_pkg.ALL;
+
+ENTITY node_fn_terminal_db IS
+  GENERIC(
+    g_sim                     : BOOLEAN := FALSE;
+    g_sim_level               : NATURAL := 0;     -- 0 = simulate GX IP, 1 = use fast serial behavioural model
+    g_use_bsn_align           : BOOLEAN := TRUE;  -- default TRUE, support FALSE for packet flow debugging purposes (faster synthesis)
+    g_use_data_buf            : BOOLEAN := TRUE; 
+    -- Application Interface
+    g_usr_nof_streams         : NATURAL := 16;
+    g_usr_data_w              : NATURAL := 32;
+    g_usr_block_len           : NATURAL := 96;
+    g_usr_block_per           : NATURAL := 256;   -- block period = block length + gap length
+    -- Terminals Interface
+    g_multi_unb               : BOOLEAN := FALSE;
+    g_use_mesh                : BOOLEAN := TRUE;
+    g_mesh_nof_serial         : NATURAL := 3;     -- default only use the 3 full featured transceivers in the mesh (out of maximal 4), using only 2 is not enough
+    g_mesh_gx_mbps            : NATURAL := 5000;
+    g_mesh_ena_reorder        : BOOLEAN := TRUE;
+    g_mesh_use_tx             : BOOLEAN := TRUE;  -- can be FALSE for BF, use TRUE to support for bidirectional TR diagnostics
+    g_mesh_mon_select         : NATURAL := 0;     -- 0 = no data monitor buffers via MM, else see unb_terminals_mesh.vhd
+    g_mesh_mon_nof_words      : NATURAL := 1024;
+    g_mesh_mon_use_sync       : BOOLEAN := TRUE;
+    -- Auxiliary Interface
+    g_aux                     : t_c_unb_aux := c_unb_aux
+  );
+  PORT(
+    -- System
+    chip_id                     : IN  STD_LOGIC_VECTOR(g_aux.chip_id_w-1 DOWNTO 0);  -- [2:0]
+    
+    mm_rst                      : IN  STD_LOGIC;
+    mm_clk                      : IN  STD_LOGIC;   -- 50 MHz from xo_clk PLL in SOPC system
+    dp_rst                      : IN  STD_LOGIC;
+    dp_clk                      : IN  STD_LOGIC;   -- 200 MHz from CLK system clock
+    dp_pps                      : IN  STD_LOGIC := '0';
+    tr_mesh_clk                 : IN  STD_LOGIC;   -- 156.25 MHz from SB_CLK transceiver clock
+    cal_clk                     : IN  STD_LOGIC;   -- 40 MHz from xo_clk PLL in SOPC system
+
+    -- MM interface
+    -- . diag_data_buffer
+    ram_diag_data_buf_mosi      : IN  t_mem_mosi := c_mem_mosi_rst;
+    ram_diag_data_buf_miso      : OUT t_mem_miso;
+    reg_diag_data_buf_mosi      : IN  t_mem_mosi := c_mem_mosi_rst;
+    reg_diag_data_buf_miso      : OUT t_mem_miso;
+    -- . tr_nonbonded
+    reg_tr_nonbonded_mosi       : IN  t_mem_mosi := c_mem_mosi_rst;
+    reg_tr_nonbonded_miso       : OUT t_mem_miso;
+    reg_diagnostics_mosi        : IN  t_mem_mosi := c_mem_mosi_rst;
+    reg_diagnostics_miso        : OUT t_mem_miso;
+    -- . diag_data_buffer_mesh
+    ram_mesh_diag_data_buf_mosi : IN  t_mem_mosi := c_mem_mosi_rst;
+    ram_mesh_diag_data_buf_miso : OUT t_mem_miso;
+    -- . bsn_monitor
+    reg_bsn_monitor_mosi        : IN  t_mem_mosi := c_mem_mosi_rst;
+    reg_bsn_monitor_miso        : OUT t_mem_miso;
+
+    -- Node stream out
+    dp_out_sosi_arr             : OUT t_dp_sosi_arr(g_usr_nof_streams-1 DOWNTO 0);
+    dp_out_siso_arr             : IN  t_dp_siso_arr(g_usr_nof_streams-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy);
+
+    -- Mesh serial interface (tr_nonbonded)
+    tx_serial_2arr              : OUT t_unb_mesh_sl_2arr;                            -- Tx
+    rx_serial_2arr              : IN  t_unb_mesh_sl_2arr:= (OTHERS=>(OTHERS=>'0'))   -- Rx support for diagnostics
+  );
+END node_fn_terminal_db;
+
+ARCHITECTURE str OF node_fn_terminal_db IS
+  
+  -----------------------------------------------------------------------------
+  -- BSN align 
+  -----------------------------------------------------------------------------
+  CONSTANT c_bsn_request_pipeline : NATURAL := 2;  -- need to use 2 to ease timing closure at 200 MHz
+  CONSTANT c_bsn_latency          : NATURAL := 3;
+  CONSTANT c_burst_usr_nof_block  : NATURAL := g_mesh_nof_serial;   -- 3 phy lane blocks t012 per user stream
+  CONSTANT c_burst_bsn_latency    : NATURAL := c_bsn_latency + c_burst_usr_nof_block;
+  
+  -----------------------------------------------------------------------------
+  -- Terminals
+  -----------------------------------------------------------------------------
+  
+  CONSTANT c_usr_nof_streams_per_bus : NATURAL := g_usr_nof_streams/c_unb_nof_bn;  -- 16 / 4 = 4
+  
+  -- . tr_nonbonded rx fifo
+  CONSTANT c_burst_phy_nof_block  : NATURAL := c_usr_nof_streams_per_bus;  -- burst of 4 usr blocks per t0 per phy lane
+  CONSTANT c_phy_block_len        : NATURAL := g_usr_block_len;            -- no data packing so phy frame is about as long as the user frame (expect for few overhead words)
+  CONSTANT c_phy_rx_fifo_len      : NATURAL := c_phy_block_len * 1;        -- assume only need to store less than one block in practise
+  CONSTANT c_phy_rx_fifo_size     : NATURAL := ceil_value(c_phy_rx_fifo_len, c_bram_m9k_fifo_depth);  -- use tr_nonbonded Rx dual clock FIFO to buffer for dp_distribute
+ 
+  -- . uth_rx timeout_cnt
+  CONSTANT c_rx_timeout_w         : NATURAL := 0;--ceil_log2(g_usr_block_per);
+  
+  -- . uth_terminal_rx output fifo
+  CONSTANT c_rx_output_fifo_len   : NATURAL := (c_burst_bsn_latency + 2) * g_usr_block_len;
+  CONSTANT c_rx_output_fifo_size  : NATURAL := ceil_value(c_rx_output_fifo_len, c_bram_m9k_fifo_depth);
+  CONSTANT c_rx_output_fifo_fill  : NATURAL := g_usr_block_len;  -- keep a full block in the FIFO to ensure that dp_bsn_align gets input without data not valid gaps when the lane rate is slower (as with tr_nonbonded)
+   
+  -- . BSN aligner timeouts
+  CONSTANT c_sop_timeout          : NATURAL := (c_burst_bsn_latency + 1) * g_usr_block_per;  -- wait for sop for some block periods
+  CONSTANT c_xoff_timeout         : NATURAL := c_burst_bsn_latency * 2 * g_usr_block_per;
+  
+  SIGNAL rx_usr_siso_2arr         : t_unb_mesh_siso_2arr;
+  SIGNAL rx_usr_sosi_2arr         : t_unb_mesh_sosi_2arr;
+
+  SIGNAL rx_rew_siso_2arr         : t_unb_mesh_siso_2arr;
+  SIGNAL rx_rew_sosi_2arr         : t_unb_mesh_sosi_2arr;
+
+  SIGNAL rx_usr_siso_arr          : t_dp_siso_arr(g_usr_nof_streams-1 DOWNTO 0);
+  SIGNAL rx_usr_sosi_arr          : t_dp_sosi_arr(g_usr_nof_streams-1 DOWNTO 0);
+ 
+   -----------------------------------------------------------------------------
+  -- Data buffer
+  -----------------------------------------------------------------------------
+  SIGNAL db_in_sosi_arr           : t_dp_sosi_arr(g_usr_nof_streams-1 DOWNTO 0);
+ 
+BEGIN
+
+  gen_mesh: IF g_use_mesh = TRUE GENERATE
+    -----------------------------------------------------------------------------
+    -- Terminals
+    -----------------------------------------------------------------------------
+  
+    u_terminals_mesh : ENTITY unb_common_lib.unb_terminals_mesh
+    GENERIC MAP (
+      g_sim                  => g_sim,
+      g_sim_level            => g_sim_level,
+      -- System
+      g_node_type            => e_fn,
+      g_nof_bus              => c_unb_nof_bn,     -- 4 to 4 nodes in mesh
+      -- User
+      g_usr_use_complex      => TRUE,
+      g_usr_data_w           => g_usr_data_w,
+      g_usr_frame_len        => g_usr_block_len,
+      g_usr_nof_streams      => c_usr_nof_streams_per_bus,
+      -- Phy
+      g_phy_nof_serial       => g_mesh_nof_serial,
+      g_phy_gx_mbps          => g_mesh_gx_mbps,
+      g_phy_rx_fifo_size     => c_phy_rx_fifo_size,
+      g_phy_ena_reorder      => g_mesh_ena_reorder,
+      -- Tx
+      g_use_tx               => g_mesh_use_tx,  -- optionally do support diag Tx
+      g_tx_input_use_fifo    => FALSE,          -- no user Tx
+      -- Rx
+      g_use_rx               => TRUE,   -- user Rx must be TRUE for DB in FN,
+      g_rx_output_use_fifo   => TRUE,   -- Rx output provides FIFOs to ensure that dp_distribute does not get blocked due to substantial backpressure on another output
+      g_rx_output_fifo_size  => c_rx_output_fifo_size,
+      g_rx_output_fifo_fill  => c_rx_output_fifo_fill,
+      g_rx_timeout_w         => c_rx_timeout_w,
+      -- Monitoring
+      g_mon_select           => g_mesh_mon_select,
+      g_mon_nof_words        => g_mesh_mon_nof_words,
+      g_mon_use_sync         => g_mesh_mon_use_sync
+    )
+    PORT MAP (
+      chip_id                => chip_id,
+      
+      mm_rst                 => mm_rst,
+      mm_clk                 => mm_clk,
+      dp_rst                 => dp_rst,
+      dp_clk                 => dp_clk,
+      dp_sync                => dp_pps,
+      tr_clk                 => tr_mesh_clk,
+      cal_clk                => cal_clk,  
+      
+      -- User interface (4 nodes)(4 input streams)
+      rx_usr_siso_2arr       => rx_usr_siso_2arr,
+      rx_usr_sosi_2arr       => rx_usr_sosi_2arr,  -- Rx (user Tx from FN to BN is unused)
+      
+      -- Mesh interface level (4 nodes)(4 lanes)
+      -- . Serial (tr_nonbonded)
+      tx_serial_2arr         => tx_serial_2arr,    -- Tx
+      rx_serial_2arr         => rx_serial_2arr,    -- Rx
+      
+      -- MM Control
+      -- . tr_nonbonded
+      reg_tr_nonbonded_mosi  => reg_tr_nonbonded_mosi,
+      reg_tr_nonbonded_miso  => reg_tr_nonbonded_miso,
+      reg_diagnostics_mosi   => reg_diagnostics_mosi,
+      reg_diagnostics_miso   => reg_diagnostics_miso,
+      
+      -- . diag_data_buffer
+      ram_diag_data_buf_mosi => ram_mesh_diag_data_buf_mosi,
+      ram_diag_data_buf_miso => ram_mesh_diag_data_buf_miso
+    );
+  
+    ---------------------------------------------------------------------------------------
+    -- Forward the received streams, rewire for single or multi UniBoard use
+    ---------------------------------------------------------------------------------------
+    gen_single_unb: IF g_multi_unb = FALSE GENERATE
+      rx_usr_siso_2arr <= rx_rew_siso_2arr;
+      rx_rew_sosi_2arr <= rx_usr_sosi_2arr;
+    END GENERATE;
+  
+    gen_multi_unb: IF g_multi_unb = TRUE GENERATE        
+      rx_rew_sosi_2arr <= func_unb_transpose_2arr(rx_usr_sosi_2arr);
+      rx_usr_siso_2arr <= func_unb_transpose_2arr(rx_rew_siso_2arr);
+    END GENERATE;
+   
+    ---------------------------------------------------------------------------------------
+    -- From 2d to 1d array
+    ---------------------------------------------------------------------------------------
+    gen_i : FOR I IN 0 TO c_unb_nof_bn-1 GENERATE
+      gen_j : FOR J IN 0 TO c_usr_nof_streams_per_bus-1 GENERATE
+        rx_rew_siso_2arr(I)(J)                           <= rx_usr_siso_arr(I*c_usr_nof_streams_per_bus + J);
+        rx_usr_sosi_arr(I*c_usr_nof_streams_per_bus + J) <= rx_rew_sosi_2arr(I)(J);
+      END GENERATE;
+    END GENERATE;
+  
+    -----------------------------------------------------------------------------
+    -- BSN align
+    -----------------------------------------------------------------------------
+    no_align : IF g_use_bsn_align=FALSE GENERATE
+      rx_usr_siso_arr <= (OTHERS=>c_dp_siso_rdy);
+      
+      reg_bsn_monitor_miso <= c_mem_miso_rst;
+    END GENERATE;
+    
+    gen_align : IF g_use_bsn_align=TRUE GENERATE
+      u_bsn_align : ENTITY dp_lib.dp_bsn_align
+      GENERIC MAP (
+        g_block_size           => g_usr_block_len,
+        g_nof_input            => g_usr_nof_streams,
+        g_xoff_timeout         => c_xoff_timeout,
+        g_sop_timeout          => c_sop_timeout,
+        g_bsn_latency          => c_burst_bsn_latency,
+        g_bsn_request_pipeline => c_bsn_request_pipeline
+      )
+      PORT MAP (
+        rst         => dp_rst,
+        clk         => dp_clk,
+        -- ST sinks
+        snk_out_arr => rx_usr_siso_arr,
+        snk_in_arr  => rx_usr_sosi_arr,
+        -- ST source
+        src_in_arr  => dp_out_siso_arr,
+        src_out_arr => db_in_sosi_arr,
+        -- MM
+        in_en_evt   => '0',           -- pulse '1' indicates that the in_en_arr user input enables have been updated
+        in_en_arr   => (OTHERS=>'1')  -- default all user inputs are enabled
+      );
+      
+      u_bsn_monitor_align : ENTITY dp_lib.mms_dp_bsn_monitor
+      GENERIC MAP (
+        g_nof_streams        => 1, -- All streams are synchronous. Only monitor stream(0).
+        g_cross_clock_domain => TRUE,
+        g_bsn_w              => c_dp_stream_bsn_w,
+        g_cnt_sop_w          => c_word_w,
+        g_cnt_valid_w        => c_word_w,
+        g_log_first_bsn      => TRUE
+      )
+      PORT MAP (
+        -- Memory-mapped clock domain
+        mm_rst      => mm_rst,
+        mm_clk      => mm_clk,
+        reg_mosi    => reg_bsn_monitor_mosi,
+        reg_miso    => reg_bsn_monitor_miso,
+        
+        -- Streaming clock domain
+        dp_rst      => dp_rst,
+        dp_clk      => dp_clk,
+        in_siso_arr => (OTHERS=>c_dp_siso_rdy),
+        in_sosi_arr => db_in_sosi_arr(0 DOWNTO 0)
+      );
+    END GENERATE;
+  
+    -----------------------------------------------------------------------------
+    -- Data buffer
+    -----------------------------------------------------------------------------  
+    no_data_buf : IF g_use_data_buf=FALSE GENERATE
+      ram_diag_data_buf_miso <= c_mem_miso_rst;
+      reg_diag_data_buf_miso <= c_mem_miso_rst;
+    END GENERATE;
+    
+    gen_data_buf : IF g_use_data_buf=TRUE GENERATE    
+      u_data_buf : ENTITY diag_lib.mms_diag_data_buffer
+      GENERIC MAP (    
+        g_nof_streams  => g_usr_nof_streams,
+        g_data_w       => g_usr_data_w, 
+        g_buf_nof_data => 1024,
+        g_buf_use_sync => TRUE
+      )
+      PORT MAP (
+        -- System
+        mm_rst            => mm_rst,
+        mm_clk            => mm_clk,
+        dp_rst            => dp_rst,
+        dp_clk            => dp_clk,
+        -- MM interface
+        ram_data_buf_mosi => ram_diag_data_buf_mosi,
+        ram_data_buf_miso => ram_diag_data_buf_miso,
+        reg_data_buf_mosi => reg_diag_data_buf_mosi,
+        reg_data_buf_miso => reg_diag_data_buf_miso,
+        -- ST interface
+        in_sync           => db_in_sosi_arr(0).sync,
+        in_sosi_arr       => db_in_sosi_arr
+      );
+    END GENERATE;
+  
+    -----------------------------------------------------------------------------
+    -- Entity DP out
+    -----------------------------------------------------------------------------  
+    dp_out_sosi_arr <= db_in_sosi_arr;
+  
+  END GENERATE;
+
+END str;
diff --git a/boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/unb1_fn_terminal_db.vhd b/boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/unb1_fn_terminal_db.vhd
new file mode 100644
index 0000000000..d106cbacef
--- /dev/null
+++ b/boards/uniboard1/designs/unb1_fn_terminal_db/src/vhdl/unb1_fn_terminal_db.vhd
@@ -0,0 +1,487 @@
+------------------------------------------------------------------------------
+--
+-- Copyright (C) 2011
+-- 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_lib, unb_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 unb_common_lib.unb_common_pkg.ALL;
+USE unb_common_lib.unb_peripherals_pkg.ALL;
+USE dp_lib.dp_stream_pkg.ALL;
+
+ENTITY fn_terminal_db IS
+  GENERIC (
+    -- General
+    g_sim           : BOOLEAN := FALSE;
+    g_rev_multi_unb : BOOLEAN := FALSE; -- Set to TRUE by Quartus revision fn_terminal_db_rev_multi.
+    g_design_name   : STRING := "fn_terminal_db";  -- Set to "fn_terminal_db_rev_multi_unb" by revision fn_terminal_db_rev_multi
+    g_fw_version    : t_unb_fw_version := (1, 0);  -- firmware version x.y
+    -- Use PHY Interface
+    -- TYPE t_c_unb_use_phy IS RECORD
+    --   eth1g   : NATURAL;
+    --   tr_front: NATURAL;
+    --   tr_mesh : NATURAL;
+    --   tr_back : NATURAL;
+    --   ddr3_I  : NATURAL;
+    --   ddr3_II : NATURAL;
+    --   adc     : NATURAL;
+    --   wdi     : NATURAL;
+    -- END RECORD;
+    g_use_phy       : t_c_unb_use_phy := (1, 0, 1, 0, 0, 0, 0, 1);
+    g_tr_mesh       : t_c_unb_tr      := c_unb_tr_mesh;
+    g_aux           : t_c_unb_aux     := c_unb_aux
+  );
+  PORT (
+   -- GENERAL
+    CLK                    : IN    STD_LOGIC; -- System Clock
+    PPS                    : IN    STD_LOGIC; -- System Sync
+    WDI                    : OUT   STD_LOGIC; -- Watchdog Clear
+    INTA                   : INOUT STD_LOGIC; -- FPGA interconnect line
+    INTB                   : INOUT STD_LOGIC; -- FPGA interconnect line
+
+    -- Others
+    VERSION                : IN    STD_LOGIC_VECTOR(g_aux.version_w-1 DOWNTO 0);
+    ID                     : IN    STD_LOGIC_VECTOR(g_aux.id_w-1 DOWNTO 0);
+    TESTIO                 : INOUT STD_LOGIC_VECTOR(g_aux.testio_w-1 DOWNTO 0);
+
+    -- I2C Interface to Sensors
+    sens_sc                : INOUT STD_LOGIC;
+    sens_sd                : INOUT STD_LOGIC;
+
+    -- 1GbE Control Interface
+    ETH_clk                : IN    STD_LOGIC;
+    ETH_SGIN               : IN    STD_LOGIC;
+    ETH_SGOUT              : OUT   STD_LOGIC;
+    
+    -- Transceiver clocks
+    --SA_CLK                 : IN  STD_LOGIC := '0';  -- TR clock    BN-BI (backplane)
+    SB_CLK                 : IN  STD_LOGIC := '0';  -- TR clock FN-BN    (mesh)
+
+    -- Serial I/O
+    FN_BN_0_TX             : OUT STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0);
+    FN_BN_0_RX             : IN  STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0) := (OTHERS=>'0');
+    FN_BN_1_TX             : OUT STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0);
+    FN_BN_1_RX             : IN  STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0) := (OTHERS=>'0');
+    FN_BN_2_TX             : OUT STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0);
+    FN_BN_2_RX             : IN  STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0) := (OTHERS=>'0');
+    FN_BN_3_TX             : OUT STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0);
+    FN_BN_3_RX             : IN  STD_LOGIC_VECTOR(g_tr_mesh.bus_w-1 DOWNTO 0) := (OTHERS=>'0')
+  );
+END fn_terminal_db;
+
+
+ARCHITECTURE str OF fn_terminal_db IS
+
+  CONSTANT c_use_mesh               : BOOLEAN := g_use_phy.tr_mesh=1; 
+  CONSTANT c_mesh_mon_select        : NATURAL := 1;     -- > 0 = enable SOSI data buffers monitor via MM
+  CONSTANT c_mesh_mon_nof_words     : NATURAL := c_unb_mm_reg_default.ram_diag_db_buf_size;  -- = 1024
+  CONSTANT c_mesh_mon_use_sync      : BOOLEAN := TRUE;  -- when TRUE use dp_pps to trigger the data buffer capture, else new data capture after read access of last data word
+
+  CONSTANT c_reg_diag_db_adr_w      : NATURAL := 5;
+
+  -- System
+  SIGNAL cs_sim                     : STD_LOGIC;
+  SIGNAL xo_clk                     : STD_LOGIC;
+  SIGNAL xo_rst_n                   : STD_LOGIC;
+  SIGNAL cal_clk                    : STD_LOGIC;
+  SIGNAL mm_clk                     : STD_LOGIC;
+  SIGNAL mm_locked                  : STD_LOGIC;
+  SIGNAL mm_rst                     : STD_LOGIC;
+  SIGNAL dp_rst                     : STD_LOGIC;
+  SIGNAL dp_clk                     : STD_LOGIC;
+  SIGNAL dp_pps                     : STD_LOGIC;
+
+  SIGNAL this_chip_id               : STD_LOGIC_VECTOR(c_unb_nof_chip_w-1 DOWNTO 0);  -- [2:0], so range 0-3 for FN and range 4-7 BN
+
+  -- PIOs
+  SIGNAL pout_debug_wave            : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);
+  SIGNAL pout_wdi                   : STD_LOGIC;
+  SIGNAL pin_pps                    : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);
+  SIGNAL pin_intab                  : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := (OTHERS=>'0');
+  SIGNAL pout_intab                 : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);
+
+  -- WDI override
+  SIGNAL reg_wdi_mosi               : t_mem_mosi;
+  SIGNAL reg_wdi_miso               : t_mem_miso;
+
+  -- UniBoard system info
+  SIGNAL reg_unb_system_info_mosi   : t_mem_mosi;
+  SIGNAL reg_unb_system_info_miso   : t_mem_miso;
+  SIGNAL rom_unb_system_info_mosi   : t_mem_mosi;
+  SIGNAL rom_unb_system_info_miso   : t_mem_miso;  
+  
+  -- UniBoard I2C sens
+  SIGNAL reg_unb_sens_mosi          : t_mem_mosi;  -- mms_unb_sens registers
+  SIGNAL reg_unb_sens_miso          : t_mem_miso;
+
+  -- eth1g
+  SIGNAL eth1g_tse_clk              : STD_LOGIC;
+  SIGNAL eth1g_mm_rst               : STD_LOGIC;
+  SIGNAL eth1g_tse_mosi             : t_mem_mosi := c_mem_mosi_rst;  -- ETH TSE MAC registers
+  SIGNAL eth1g_tse_miso             : t_mem_miso;
+  SIGNAL eth1g_reg_mosi             : t_mem_mosi := c_mem_mosi_rst;  -- ETH control and status registers
+  SIGNAL eth1g_reg_miso             : t_mem_miso;
+  SIGNAL eth1g_reg_interrupt        : STD_LOGIC;   -- Interrupt
+  SIGNAL eth1g_ram_mosi             : t_mem_mosi := c_mem_mosi_rst;  -- ETH rx frame and tx frame memory
+  SIGNAL eth1g_ram_miso             : t_mem_miso;
+
+  -- tr_mesh
+  SIGNAL tx_serial_2arr             : t_unb_mesh_sl_2arr;    -- Tx
+  SIGNAL rx_serial_2arr             : t_unb_mesh_sl_2arr;    -- Rx support for diagnostics
+    
+  -- MM tr_nonbonded with diagnostics
+  SIGNAL reg_tr_nonbonded_mosi      : t_mem_mosi := c_mem_mosi_rst;
+  SIGNAL reg_tr_nonbonded_miso      : t_mem_miso;
+
+  SIGNAL reg_diagnostics_mosi       : t_mem_mosi := c_mem_mosi_rst;
+  SIGNAL reg_diagnostics_miso       : t_mem_miso;
+
+  -- MM diag_data_buffer_mesh
+  SIGNAL ram_mesh_diag_data_buf_mosi : t_mem_mosi := c_mem_mosi_rst;
+  SIGNAL ram_mesh_diag_data_buf_miso : t_mem_miso;
+
+  -- MM diag_data_buffer (main)
+  SIGNAL ram_diag_data_buf_mosi     : t_mem_mosi := c_mem_mosi_rst;
+  SIGNAL ram_diag_data_buf_miso     : t_mem_miso;
+  SIGNAL reg_diag_data_buf_mosi     : t_mem_mosi := c_mem_mosi_rst;
+  SIGNAL reg_diag_data_buf_miso     : t_mem_miso;  
+  
+  -- MM bsn_monitor
+  SIGNAL reg_bsn_monitor_mosi       : t_mem_mosi := c_mem_mosi_rst;
+  SIGNAL reg_bsn_monitor_miso       : t_mem_miso;
+
+BEGIN
+
+  -----------------------------------------------------------------------------
+  -- SOPC system
+  -----------------------------------------------------------------------------
+  u_sopc : ENTITY work.sopc_fn_terminal_db
+  PORT MAP (
+    -- 1) global signals:
+    clk_0                                                   => xo_clk,            -- PLL reference = 25 MHz from ETH_clk pin
+    reset_n                                                 => xo_rst_n,
+    mm_clk                                                  => mm_clk,            -- PLL clk[0] = 125 MHz system clock that the NIOS2 and the MM bus run on
+    cal_clk                                                 => cal_clk,           -- PLL clk[1] =  40 MHz calibration clock for the IO reconfiguration
+    tse_clk                                                 => eth1g_tse_clk,     -- PLL clk[2] = 125 MHz dedicated clock for the 1 Gbit Ethernet unit
+
+    -- the_altpll_0
+    areset_to_the_altpll_0                                  => '0',
+    locked_from_the_altpll_0                                => mm_locked,
+    phasedone_from_the_altpll_0                             => OPEN,
+
+    -- the_avs_eth_0
+    coe_clk_export_from_the_avs_eth_0                       => OPEN,
+    coe_reset_export_from_the_avs_eth_0                     => eth1g_mm_rst,
+    coe_tse_address_export_from_the_avs_eth_0               => eth1g_tse_mosi.address(c_unb_mm_reg_default.reg_tse_adr_w-1 DOWNTO 0),
+    coe_tse_write_export_from_the_avs_eth_0                 => eth1g_tse_mosi.wr,
+    coe_tse_writedata_export_from_the_avs_eth_0             => eth1g_tse_mosi.wrdata(c_word_w-1 DOWNTO 0),
+    coe_tse_read_export_from_the_avs_eth_0                  => eth1g_tse_mosi.rd,
+    coe_tse_readdata_export_to_the_avs_eth_0                => eth1g_tse_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_tse_waitrequest_export_to_the_avs_eth_0             => eth1g_tse_miso.waitrequest,
+    coe_reg_address_export_from_the_avs_eth_0               => eth1g_reg_mosi.address(c_unb_mm_reg_default.reg_eth_adr_w-1 DOWNTO 0),
+    coe_reg_write_export_from_the_avs_eth_0                 => eth1g_reg_mosi.wr,
+    coe_reg_writedata_export_from_the_avs_eth_0             => eth1g_reg_mosi.wrdata(c_word_w-1 DOWNTO 0),
+    coe_reg_read_export_from_the_avs_eth_0                  => eth1g_reg_mosi.rd,
+    coe_reg_readdata_export_to_the_avs_eth_0                => eth1g_reg_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_irq_export_to_the_avs_eth_0                         => eth1g_reg_interrupt,
+    coe_ram_address_export_from_the_avs_eth_0               => eth1g_ram_mosi.address(c_unb_mm_reg_default.ram_eth_adr_w-1 DOWNTO 0),
+    coe_ram_write_export_from_the_avs_eth_0                 => eth1g_ram_mosi.wr,
+    coe_ram_writedata_export_from_the_avs_eth_0             => eth1g_ram_mosi.wrdata(c_word_w-1 DOWNTO 0),
+    coe_ram_read_export_from_the_avs_eth_0                  => eth1g_ram_mosi.rd,
+    coe_ram_readdata_export_to_the_avs_eth_0                => eth1g_ram_miso.rddata(c_word_w-1 DOWNTO 0),
+
+    -- the_reg_unb_sens
+    coe_address_export_from_the_reg_unb_sens                => reg_unb_sens_mosi.address(c_unb_mm_reg_default.reg_unb_sens_adr_w-1 DOWNTO 0),
+    coe_clk_export_from_the_reg_unb_sens                    => OPEN,
+    coe_read_export_from_the_reg_unb_sens                   => reg_unb_sens_mosi.rd,
+    coe_readdata_export_to_the_reg_unb_sens                 => reg_unb_sens_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_reset_export_from_the_reg_unb_sens                  => OPEN,
+    coe_write_export_from_the_reg_unb_sens                  => reg_unb_sens_mosi.wr,
+    coe_writedata_export_from_the_reg_unb_sens              => reg_unb_sens_mosi.wrdata(c_word_w-1 DOWNTO 0),
+
+    -- the_reg_tr_nonbonded_mesh
+    coe_address_export_from_the_reg_tr_nonbonded_mesh       => reg_tr_nonbonded_mosi.address(c_unb_mm_reg_default.reg_tr_nonbonded_adr_w-1 DOWNTO 0),
+    coe_clk_export_from_the_reg_tr_nonbonded_mesh           => OPEN,
+    coe_read_export_from_the_reg_tr_nonbonded_mesh          => reg_tr_nonbonded_mosi.rd,
+    coe_readdata_export_to_the_reg_tr_nonbonded_mesh        => reg_tr_nonbonded_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_reset_export_from_the_reg_tr_nonbonded_mesh         => OPEN,
+    coe_write_export_from_the_reg_tr_nonbonded_mesh         => reg_tr_nonbonded_mosi.wr,
+    coe_writedata_export_from_the_reg_tr_nonbonded_mesh     => reg_tr_nonbonded_mosi.wrdata(c_word_w-1 DOWNTO 0),
+
+    -- the_reg_diagnostics_mesh
+    coe_address_export_from_the_reg_diagnostics_mesh        => reg_diagnostics_mosi.address(c_unb_mm_reg_default.reg_diagnostics_adr_w-1 DOWNTO 0),
+    coe_clk_export_from_the_reg_diagnostics_mesh            => OPEN,
+    coe_read_export_from_the_reg_diagnostics_mesh           => reg_diagnostics_mosi.rd,
+    coe_readdata_export_to_the_reg_diagnostics_mesh         => reg_diagnostics_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_reset_export_from_the_reg_diagnostics_mesh          => OPEN,
+    coe_write_export_from_the_reg_diagnostics_mesh          => reg_diagnostics_mosi.wr,
+    coe_writedata_export_from_the_reg_diagnostics_mesh      => reg_diagnostics_mosi.wrdata(c_word_w-1 DOWNTO 0),
+
+    -- the_ram_diag_data_buffer
+    coe_address_export_from_the_ram_diag_data_buffer        => ram_diag_data_buf_mosi.address(c_unb_mm_reg_default.ram_diag_db_adr_w-1 DOWNTO 0),
+    coe_clk_export_from_the_ram_diag_data_buffer            => OPEN,
+    coe_read_export_from_the_ram_diag_data_buffer           => ram_diag_data_buf_mosi.rd,
+    coe_readdata_export_to_the_ram_diag_data_buffer         => ram_diag_data_buf_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_reset_export_from_the_ram_diag_data_buffer          => OPEN,
+    coe_write_export_from_the_ram_diag_data_buffer          => ram_diag_data_buf_mosi.wr,
+    coe_writedata_export_from_the_ram_diag_data_buffer      => ram_diag_data_buf_mosi.wrdata(c_word_w-1 DOWNTO 0),
+
+    -- the_reg_diag_data_buffer
+    coe_address_export_from_the_reg_diag_data_buffer        => reg_diag_data_buf_mosi.address(c_reg_diag_db_adr_w-1 DOWNTO 0),
+    coe_clk_export_from_the_reg_diag_data_buffer            => OPEN,
+    coe_read_export_from_the_reg_diag_data_buffer           => reg_diag_data_buf_mosi.rd,
+    coe_readdata_export_to_the_reg_diag_data_buffer         => reg_diag_data_buf_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_reset_export_from_the_reg_diag_data_buffer          => OPEN,
+    coe_write_export_from_the_reg_diag_data_buffer          => reg_diag_data_buf_mosi.wr,
+    coe_writedata_export_from_the_reg_diag_data_buffer      => reg_diag_data_buf_mosi.wrdata(c_word_w-1 DOWNTO 0),
+
+    -- the_ram_diag_data_buffer_mesh
+    coe_address_export_from_the_ram_diag_data_buffer_mesh   => ram_mesh_diag_data_buf_mosi.address(c_unb_mm_reg_default.ram_diag_db_adr_w-1 DOWNTO 0),
+    coe_clk_export_from_the_ram_diag_data_buffer_mesh       => OPEN,
+    coe_read_export_from_the_ram_diag_data_buffer_mesh      => ram_mesh_diag_data_buf_mosi.rd,
+    coe_readdata_export_to_the_ram_diag_data_buffer_mesh    => ram_mesh_diag_data_buf_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_reset_export_from_the_ram_diag_data_buffer_mesh     => OPEN,
+    coe_write_export_from_the_ram_diag_data_buffer_mesh     => ram_mesh_diag_data_buf_mosi.wr,
+    coe_writedata_export_from_the_ram_diag_data_buffer_mesh => ram_mesh_diag_data_buf_mosi.wrdata(c_word_w-1 DOWNTO 0),
+    
+    -- the_reg_bsn_monitor
+    coe_address_export_from_the_reg_bsn_monitor             => reg_bsn_monitor_mosi.address(c_unb_mm_reg_default.reg_bsn_monitor_adr_w-1 DOWNTO 0),
+    coe_clk_export_from_the_reg_bsn_monitor                 => OPEN,
+    coe_read_export_from_the_reg_bsn_monitor                => reg_bsn_monitor_mosi.rd,
+    coe_readdata_export_to_the_reg_bsn_monitor              => reg_bsn_monitor_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_reset_export_from_the_reg_bsn_monitor               => OPEN,
+    coe_write_export_from_the_reg_bsn_monitor               => reg_bsn_monitor_mosi.wr,
+    coe_writedata_export_from_the_reg_bsn_monitor           => reg_bsn_monitor_mosi.wrdata(c_word_w-1 DOWNTO 0),
+    
+    -- the_pio_debug_wave
+    out_port_from_the_pio_debug_wave                        => pout_debug_wave,
+
+    -- the_pio_pps
+    in_port_to_the_pio_pps                                  => pin_pps,
+
+    -- the_pio_system_info: actually a avs_common_mm instance
+    coe_clk_export_from_the_pio_system_info                 => OPEN,
+    coe_reset_export_from_the_pio_system_info               => OPEN,
+    coe_address_export_from_the_pio_system_info             => reg_unb_system_info_mosi.address(c_unb_mm_reg_default.reg_unb_system_info_adr_w-1 DOWNTO 0), 
+    coe_read_export_from_the_pio_system_info                => reg_unb_system_info_mosi.rd,
+    coe_readdata_export_to_the_pio_system_info              => reg_unb_system_info_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_write_export_from_the_pio_system_info               => reg_unb_system_info_mosi.wr,
+    coe_writedata_export_from_the_pio_system_info           => reg_unb_system_info_mosi.wrdata(c_word_w-1 DOWNTO 0),
+
+    -- the_rom_system_info
+    coe_clk_export_from_the_rom_system_info                 => OPEN,
+    coe_reset_export_from_the_rom_system_info               => OPEN,
+    coe_address_export_from_the_rom_system_info             => rom_unb_system_info_mosi.address(c_unb_mm_reg_default.rom_unb_system_info_adr_w-1 DOWNTO 0), 
+    coe_read_export_from_the_rom_system_info                => rom_unb_system_info_mosi.rd,
+    coe_readdata_export_to_the_rom_system_info              => rom_unb_system_info_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_write_export_from_the_rom_system_info               => rom_unb_system_info_mosi.wr,
+    coe_writedata_export_from_the_rom_system_info           => rom_unb_system_info_mosi.wrdata(c_word_w-1 DOWNTO 0),
+
+    -- the_pio_wdi
+    out_port_from_the_pio_wdi                               => pout_wdi,
+
+    -- the_reg_wdi: Manual WDI override; causes FPGA reconfiguration if WDI is enabled (g_use_phy).
+    coe_clk_export_from_the_reg_wdi                         => OPEN,
+    coe_reset_export_from_the_reg_wdi                       => OPEN,
+    coe_address_export_from_the_reg_wdi                     => reg_wdi_mosi.address(0), 
+    coe_read_export_from_the_reg_wdi                        => reg_wdi_mosi.rd,
+    coe_readdata_export_to_the_reg_wdi                      => reg_wdi_miso.rddata(c_word_w-1 DOWNTO 0),
+    coe_write_export_from_the_reg_wdi                       => reg_wdi_mosi.wr,
+    coe_writedata_export_from_the_reg_wdi                   => reg_wdi_mosi.wrdata(c_word_w-1 DOWNTO 0)
+  );
+
+  -----------------------------------------------------------------------------
+  -- General control function
+  -----------------------------------------------------------------------------
+  u_ctrl : ENTITY unb_common_lib.ctrl_unb_common
+  GENERIC MAP (
+    -- General
+    g_design_name => g_design_name,
+    g_fw_version  => g_fw_version,
+    -- Use PHY Interface
+    g_use_phy     => g_use_phy,
+    -- Auxiliary Interface
+    g_aux         => g_aux
+  )
+  PORT MAP (
+    --
+    -- >>> SOPC system with conduit peripheral MM bus
+    --
+    -- System
+    cs_sim                   => cs_sim,
+    xo_clk                   => xo_clk,
+    xo_rst_n                 => xo_rst_n,
+    mm_clk                   => mm_clk,
+    mm_locked                => mm_locked,
+    mm_rst                   => mm_rst,
+
+    dp_rst                   => dp_rst,
+    dp_clk                   => dp_clk,
+    dp_pps                   => dp_pps,
+    dp_rst_in                => dp_rst,
+    dp_clk_in                => dp_clk,
+
+    this_chip_id             => this_chip_id,
+    
+    -- PIOs
+    pout_debug_wave          => pout_debug_wave,
+    pout_wdi                 => pout_wdi,
+    pin_pps                  => pin_pps,
+
+    -- System_info
+    reg_unb_system_info_mosi => reg_unb_system_info_mosi,
+    reg_unb_system_info_miso => reg_unb_system_info_miso, 
+    rom_unb_system_info_mosi => rom_unb_system_info_mosi,
+    rom_unb_system_info_miso => rom_unb_system_info_miso, 
+
+    -- Manual WDI override
+    reg_wdi_mosi             => reg_wdi_mosi,
+    reg_wdi_miso             => reg_wdi_miso,
+   
+     -- UniBoard I2C sensors
+    reg_unb_sens_mosi        => reg_unb_sens_mosi,
+    reg_unb_sens_miso        => reg_unb_sens_miso,
+
+    -- eth1g
+    eth1g_tse_clk            => eth1g_tse_clk,
+    eth1g_mm_rst             => eth1g_mm_rst,
+    eth1g_tse_mosi           => eth1g_tse_mosi,
+    eth1g_tse_miso           => eth1g_tse_miso,
+    eth1g_reg_mosi           => eth1g_reg_mosi,
+    eth1g_reg_miso           => eth1g_reg_miso,
+    eth1g_reg_interrupt      => eth1g_reg_interrupt,
+    eth1g_ram_mosi           => eth1g_ram_mosi,
+    eth1g_ram_miso           => eth1g_ram_miso,
+    --
+    -- >>> Ctrl FPGA pins
+    --
+    -- General
+    CLK                      => CLK,
+    PPS                      => PPS,
+    WDI                      => WDI,
+    INTA                     => INTA,
+    INTB                     => INTB,
+
+    -- Others
+    VERSION                  => VERSION,
+    ID                       => ID,
+    TESTIO                   => TESTIO,
+
+    -- I2C Interface to Sensors
+    sens_sc                  => sens_sc,
+    sens_sd                  => sens_sd,
+
+    ETH_clk                  => ETH_clk,
+    ETH_SGIN                 => ETH_SGIN,
+    ETH_SGOUT                => ETH_SGOUT
+  );
+
+  -----------------------------------------------------------------------------
+  -- Node functioon: Terminals and data buffer
+  -----------------------------------------------------------------------------  
+  u_node_fn_terminal_db : ENTITY work.node_fn_terminal_db
+  GENERIC MAP(
+    g_multi_unb                 => g_rev_multi_unb,
+    -- Terminals interface
+    g_use_mesh                  => c_use_mesh,
+    g_mesh_mon_select           => c_mesh_mon_select,
+    g_mesh_mon_nof_words        => c_mesh_mon_nof_words,
+    g_mesh_mon_use_sync         => c_mesh_mon_use_sync,
+    -- Auxiliary Interface
+    g_aux                       => c_unb_aux
+  )
+  PORT MAP(
+    -- System
+    mm_rst                      => mm_rst,
+    mm_clk                      => mm_clk,
+    dp_rst                      => dp_rst,
+    dp_clk                      => dp_clk,
+    dp_pps                      => dp_pps,
+    tr_mesh_clk                 => SB_CLK,
+    cal_clk                     => cal_clk,
+
+    chip_id                     => this_chip_id,
+
+    -- MM interface
+    -- . tr_nonbonded
+    reg_tr_nonbonded_mosi       => reg_tr_nonbonded_mosi,
+    reg_tr_nonbonded_miso       => reg_tr_nonbonded_miso,
+    reg_diagnostics_mosi        => reg_diagnostics_mosi,
+    reg_diagnostics_miso        => reg_diagnostics_miso,
+    -- . diag_data_buffer
+    ram_diag_data_buf_mosi      => ram_diag_data_buf_mosi,
+    ram_diag_data_buf_miso      => ram_diag_data_buf_miso,
+    reg_diag_data_buf_mosi      => reg_diag_data_buf_mosi,
+    reg_diag_data_buf_miso      => reg_diag_data_buf_miso,
+    -- . diag_data_buffer_mesh
+    ram_mesh_diag_data_buf_mosi => ram_mesh_diag_data_buf_mosi,
+    ram_mesh_diag_data_buf_miso => ram_mesh_diag_data_buf_miso,
+    -- . bsn_monitor
+    reg_bsn_monitor_mosi        => reg_bsn_monitor_mosi,
+    reg_bsn_monitor_miso        => reg_bsn_monitor_miso,
+    
+    -- Mesh interface
+    tx_serial_2arr              => tx_serial_2arr,
+    rx_serial_2arr              => rx_serial_2arr
+  );
+
+  -----------------------------------------------------------------------------
+  -- Mesh I/O
+  -----------------------------------------------------------------------------  
+  no_tr_mesh : IF g_use_phy.tr_mesh=0 GENERATE
+    rx_serial_2arr <= (OTHERS=>(OTHERS=>'0'));
+  END GENERATE;
+  
+  gen_tr_mesh : IF g_use_phy.tr_mesh/=0 GENERATE
+    u_mesh_io : ENTITY unb_common_lib.unb_mesh_io
+    GENERIC MAP (
+      g_bus_w => g_tr_mesh.bus_w
+    )
+    PORT MAP (
+      tx_serial_2arr => tx_serial_2arr,
+      rx_serial_2arr => rx_serial_2arr,
+      
+      -- Serial I/O
+      FN_BN_0_TX     => FN_BN_0_TX,
+      FN_BN_0_RX     => FN_BN_0_RX,
+      FN_BN_1_TX     => FN_BN_1_TX,
+      FN_BN_1_RX     => FN_BN_1_RX,
+      FN_BN_2_TX     => FN_BN_2_TX,
+      FN_BN_2_RX     => FN_BN_2_RX,
+      FN_BN_3_TX     => FN_BN_3_TX,
+      FN_BN_3_RX     => FN_BN_3_RX
+    );
+  END GENERATE;
+  
+END;
+
+
+
+
+
+
+
+
+
+
+
+
diff --git a/boards/uniboard1/designs/unb1_fn_terminal_db/tb/vhdl/tb_node_unb1_fn_terminal_db.vhd b/boards/uniboard1/designs/unb1_fn_terminal_db/tb/vhdl/tb_node_unb1_fn_terminal_db.vhd
new file mode 100644
index 0000000000..6c52327983
--- /dev/null
+++ b/boards/uniboard1/designs/unb1_fn_terminal_db/tb/vhdl/tb_node_unb1_fn_terminal_db.vhd
@@ -0,0 +1,458 @@
+-------------------------------------------------------------------------------
+--
+-- Copyright (C) 2012
+-- 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: Verify the terminals for the UniBoard mesh and the backplane using
+--          a block generator (BG) in the BN and a data buffer (DB) in the FN.
+-- Description:
+--   g_unb_sys:
+--     unb  fn  bn
+--     1    1   1     For fastest simulation to verify link and BSN align
+--     1    1   4     Realistic simulation of one UNB with one FN
+--     1    4   1     No added value compared to 1 FN
+--     1    4   4     Complete UNB, functionally no added value compared to
+--                    using 4 BN --> 1 FN, but it does accurately simulate the
+--                    mesh PCB reorder.
+--     4    1   4     Realistic simulation of a subrack with a back PCB and
+--                    four UNB each with one FN
+--     4    4   4     Complete subrack with four UNB with all BN and FN.
+--
+-- Usage:
+--   Modelsim:
+--   > as 8
+--   . Unfold and observe:
+--     - bg_sosi_arr in BN to see the streams that are generated by the BG
+--     - back_*_usr_sosi_arr2 to see what is send between corresponding BN
+--     - mesh_tx_usr_sosi_arr2 to see what is send to the FN via the mesh
+--     - db_in_sosi_arr in FN after BSN aligner to see the aligned streams
+--     - rx_usr_sosi_arr in FN to see what is received before the BSN aligner.
+--
+--   > as 15
+--   . For observing FIFO usedw and uth_rx timeout_cnt
+--
+--   > run 30 us
+--   . After issueing the run command start the Python test case in the shell.
+--
+--   > do tb_mmf_node_fn_terminal_db.do
+--   . To verify rx_usr_sosi_2arr recovery after fault on unb[0], fn[0],
+--     bus[0], lane [0], this can cause expected "Warning: uth_rx(rtl_hold)
+--     timeout occurred!" dependent on when exactly the
+--     tb_mmf_node_fn_terminal_db.do is issued.
+
+--   > do tb_mmf_node_fn_terminal_db.do
+--     . Try again (edit the do file to affect lane 0 on back or mesh)
+--
+--   Shell:
+--   > cd $UPE
+--
+--   . For example do with g_unb_sys = (1, 1, 1):
+--   > python apps/bn_bg_terminal_fn_db/tc_bn_bg_terminal_fn_db.py --unb 0 --bn 0 --fn 0 --sim
+--
+--   . or do with g_unb_sys = (4, 4, 4):
+--   > python apps/bn_bg_terminal_fn_db/tc_bn_bg_terminal_fn_db.py --unb 0:3 --bn 0:3 --fn 0:3 --sim
+--
+--   . or do with g_unb_sys = (4, 1, 4):
+--   > python apps/bn_bg_terminal_fn_db/tc_bn_bg_terminal_fn_db.py --unb 0:3 --bn 0:3 --fn 0 --sim
+--
+
+LIBRARY IEEE, common_lib, unb_common_lib, bn_terminal_bg_lib, fn_terminal_db_lib, mm_lib, bf_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.tb_common_pkg.ALL;
+USE common_lib.tb_common_mem_pkg.ALL;
+USE unb_common_lib.unb_common_pkg.ALL;
+USE unb_common_lib.tb_unb_common_pkg.ALL;
+USE bf_lib.bf_pkg.ALL;
+USE mm_lib.mm_file_pkg.ALL;
+USE mm_lib.mm_file_unb_pkg.ALL;
+
+ENTITY tb_mmf_node_fn_terminal_db IS
+  GENERIC (
+    g_sim_level   : NATURAL := 1;           -- 0 = use accurate GX IP model, 1 = use fast GX behavioural model in tr_nonbonded
+    g_unb_sys     : t_c_mmf_unb_sys := (4, 1, 4)  -- (nof_unb, nof_fn per UniBoard, nof_bn per UniBoard); 
+  );
+END tb_mmf_node_fn_terminal_db;
+
+ARCHITECTURE tb OF tb_mmf_node_fn_terminal_db IS
+
+  CONSTANT c_sim                       : BOOLEAN := TRUE;
+
+  CONSTANT c_use_back                  : BOOLEAN := sel_a_b(g_unb_sys.nof_unb=4, TRUE, FALSE);  -- To interconnect multiple boards via the backplane when g_unb_sys.nof_unb=4 else when g_unb_sys.nof_unb=1
+                                                                                                -- this loops back each back node's BN_BI_TX to BN_BI_RX.  
+  CONSTANT c_ena_mesh_reorder          : BOOLEAN := TRUE;
+  CONSTANT c_mesh_use_bidir            : BOOLEAN := FALSE;
+  CONSTANT c_mesh_nof_serial           : NATURAL := 3;     -- default only use the 3 full featured transceivers in the mesh (out of maximal 4), using only 2 is not enough
+
+  ----------------------------------------------------------------------------
+  -- Clocks and resets
+  ----------------------------------------------------------------------------   
+  CONSTANT c_mm_clk_period             : TIME := 100 ps;
+  CONSTANT c_dp_clk_period             : TIME := 5 ns;
+  CONSTANT c_tr_clk_period             : TIME := 6.4 ns;
+  CONSTANT c_cal_rec_clk_period        : TIME := 25 ns;
+  CONSTANT c_dp_pps_period             : NATURAL := 8;
+
+  SIGNAL dp_pps                        : STD_LOGIC;
+
+  SIGNAL mm_rst                        : STD_LOGIC;
+  SIGNAL mm_clk                        : STD_LOGIC := '1';
+
+  SIGNAL dp_rst                        : STD_LOGIC;
+  SIGNAL dp_clk                        : STD_LOGIC := '1';
+
+  SIGNAL tr_clk                        : STD_LOGIC := '1';
+  SIGNAL cal_rec_clk                   : STD_LOGIC := '1';
+
+  TYPE t_mem_mosi_fn_2arr IS ARRAY  (g_unb_sys.nof_unb-1 DOWNTO 0) OF t_mem_mosi_arr(g_unb_sys.nof_fn-1 DOWNTO 0);
+  TYPE t_mem_miso_fn_2arr IS ARRAY  (g_unb_sys.nof_unb-1 DOWNTO 0) OF t_mem_miso_arr(g_unb_sys.nof_fn-1 DOWNTO 0);
+
+  TYPE t_mem_mosi_bn_2arr IS ARRAY  (g_unb_sys.nof_unb-1 DOWNTO 0) OF t_mem_mosi_arr(g_unb_sys.nof_bn-1 DOWNTO 0);
+  TYPE t_mem_miso_bn_2arr IS ARRAY  (g_unb_sys.nof_unb-1 DOWNTO 0) OF t_mem_miso_arr(g_unb_sys.nof_bn-1 DOWNTO 0);
+
+  ----------------------------------------------------------------------------
+  -- MM buses for node_bn_terminal_bg
+  ----------------------------------------------------------------------------                                         
+  SIGNAL bn_reg_diag_bg_mosi_2arr            : t_mem_mosi_bn_2arr;
+  SIGNAL bn_reg_diag_bg_miso_2arr            : t_mem_miso_bn_2arr;
+   
+  SIGNAL bn_ram_diag_bg_mosi_2arr            : t_mem_mosi_bn_2arr;
+  SIGNAL bn_ram_diag_bg_miso_2arr            : t_mem_miso_bn_2arr;
+   
+  SIGNAL bn_reg_tr_nonbonded_mesh_mosi_2arr  : t_mem_mosi_bn_2arr;
+  SIGNAL bn_reg_tr_nonbonded_mesh_miso_2arr  : t_mem_miso_bn_2arr;
+   
+  SIGNAL bn_reg_diagnostics_mesh_mosi_2arr   : t_mem_mosi_bn_2arr;
+  SIGNAL bn_reg_diagnostics_mesh_miso_2arr   : t_mem_miso_bn_2arr;
+   
+  SIGNAL bn_reg_tr_nonbonded_back_mosi_2arr  : t_mem_mosi_bn_2arr;
+  SIGNAL bn_reg_tr_nonbonded_back_miso_2arr  : t_mem_miso_bn_2arr;
+   
+  SIGNAL bn_reg_diagnostics_back_mosi_2arr   : t_mem_mosi_bn_2arr;
+  SIGNAL bn_reg_diagnostics_back_miso_2arr   : t_mem_miso_bn_2arr;
+   
+  SIGNAL bn_ram_diag_data_buf_mesh_mosi_2arr : t_mem_mosi_bn_2arr;
+  SIGNAL bn_ram_diag_data_buf_mesh_miso_2arr : t_mem_miso_bn_2arr;
+
+  SIGNAL bn_reg_ppsh_mosi_2arr               : t_mem_mosi_bn_2arr;
+  SIGNAL bn_reg_ppsh_miso_2arr               : t_mem_miso_bn_2arr;
+
+  ----------------------------------------------------------------------------
+  -- MM buses for node_fn_terminal_db
+  ----------------------------------------------------------------------------   
+  SIGNAL fn_reg_tr_nonbonded_mosi_2arr       : t_mem_mosi_fn_2arr;
+  SIGNAL fn_reg_tr_nonbonded_miso_2arr       : t_mem_miso_fn_2arr;
+   
+  SIGNAL fn_reg_diagnostics_mosi_2arr        : t_mem_mosi_fn_2arr;
+  SIGNAL fn_reg_diagnostics_miso_2arr        : t_mem_miso_fn_2arr;
+
+  SIGNAL fn_ram_diag_data_buf_mosi_2arr      : t_mem_mosi_fn_2arr;
+  SIGNAL fn_ram_diag_data_buf_miso_2arr      : t_mem_miso_fn_2arr;
+
+  SIGNAL fn_reg_diag_data_buf_mosi_2arr      : t_mem_mosi_fn_2arr;
+  SIGNAL fn_reg_diag_data_buf_miso_2arr      : t_mem_miso_fn_2arr;
+   
+  SIGNAL fn_ram_mesh_diag_data_buf_mosi_2arr : t_mem_mosi_fn_2arr;
+  SIGNAL fn_ram_mesh_diag_data_buf_miso_2arr : t_mem_miso_fn_2arr;
+   
+  SIGNAL fn_reg_bsn_monitor_mosi_2arr        : t_mem_mosi_fn_2arr;
+  SIGNAL fn_reg_bsn_monitor_miso_2arr        : t_mem_miso_fn_2arr;
+
+  SIGNAL fn_reg_ppsh_mosi_2arr               : t_mem_mosi_fn_2arr;
+  SIGNAL fn_reg_ppsh_miso_2arr               : t_mem_miso_fn_2arr;
+
+  ------------------------------------------------------------------------------
+  -- BN back side serial I/O
+  ------------------------------------------------------------------------------
+  SIGNAL bn_out_back_serial_4arr : t_unb_back_sl_4arr; 
+  SIGNAL bn_in_back_serial_4arr  : t_unb_back_sl_4arr;
+
+  ------------------------------------------------------------------------------
+  -- BN & FN mesh side serial I/O
+  ------------------------------------------------------------------------------
+  SIGNAL bn_out_mesh_serial_4arr : t_unb_mesh_sl_4arr;
+  SIGNAL bn_in_mesh_serial_4arr  : t_unb_mesh_sl_4arr;
+
+  SIGNAL fn_in_mesh_serial_4arr  : t_unb_mesh_sl_4arr;
+  SIGNAL fn_out_mesh_serial_4arr : t_unb_mesh_sl_4arr;
+ 
+  ----------------------------------------------------------------------------
+  -- Component declaration of mm_file (many instances in this TB)
+  ----------------------------------------------------------------------------
+  COMPONENT mm_file
+  GENERIC(
+    g_file_prefix       : STRING;
+    g_mm_clk_period     : TIME := c_mm_clk_period;
+    g_update_on_change  : BOOLEAN := FALSE
+  );
+  PORT (
+    mm_rst        : IN  STD_LOGIC;
+    mm_clk        : IN  STD_LOGIC;
+    mm_master_out : OUT t_mem_mosi;
+    mm_master_in  : IN  t_mem_miso 
+  );
+  END COMPONENT;
+
+BEGIN
+
+  ----------------------------------------------------------------------------
+  -- Clock and reset generation
+  ----------------------------------------------------------------------------
+  mm_clk <= NOT mm_clk AFTER c_mm_clk_period/2;
+  mm_rst <= '1', '0' AFTER c_mm_clk_period*5;
+
+  dp_clk <= NOT dp_clk AFTER c_dp_clk_period/2;
+  dp_rst <= '1', '0' AFTER c_dp_clk_period*5;
+
+  tr_clk <= NOT tr_clk AFTER c_tr_clk_period/2;
+  cal_rec_clk <= NOT cal_rec_clk AFTER c_cal_rec_clk_period/2;
+
+  ----------------------------------------------------------------------------
+  -- Procedure that polls a sim control file that can be used to e.g. get
+  -- the simulation time in ns
+  ----------------------------------------------------------------------------
+  mmf_poll_sim_ctrl_file(c_mmf_unb_file_path & "sim.ctrl", c_mmf_unb_file_path & "sim.stat");
+ 
+  ------------------------------------------------------------------------------
+  -- External PPS
+  ------------------------------------------------------------------------------  
+  proc_common_gen_pulse(1, c_dp_pps_period, '1', dp_rst, dp_clk, dp_pps);
+
+  ----------------------------------------------------------------------------
+  -- DUTs and their MM buses
+  ----------------------------------------------------------------------------
+  gen_unb : FOR UNB IN 0 TO g_unb_sys.nof_unb-1 GENERATE  
+    gen_bn: FOR BN IN 0 TO g_unb_sys.nof_bn-1 GENERATE  
+      ----------------------------------------------------------------------------
+      -- bn_terminal_bg: MM <-> file I/O
+      ----------------------------------------------------------------------------
+      --u_mm_file_reg_diagnostics_back   : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "REG_DIAGNOSTICS_BACK") 
+      --                                              PORT MAP(mm_rst, mm_clk, bn_reg_diagnostics_back_mosi_2arr(UNB)(BN), bn_reg_diagnostics_back_miso_2arr(UNB)(BN) );
+
+      u_mm_file_reg_diag_bg            : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "REG_DIAG_BG")
+                                                    PORT MAP(mm_rst, mm_clk, bn_reg_diag_bg_mosi_2arr(UNB)(BN), bn_reg_diag_bg_miso_2arr(UNB)(BN) );
+
+      u_mm_file_ram_diag_bg            : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "RAM_DIAG_BG")
+                                                    PORT MAP(mm_rst, mm_clk, bn_ram_diag_bg_mosi_2arr(UNB)(BN), bn_ram_diag_bg_miso_2arr(UNB)(BN) );
+  
+      --u_mm_file_reg_tr_nonbonded_mesh  : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "REG_TR_NONBONDED_MESH")                
+      --                                              PORT MAP(mm_rst, mm_clk, bn_reg_tr_nonbonded_mesh_mosi_2arr(UNB)(BN), bn_reg_tr_nonbonded_mesh_miso_2arr(UNB)(BN) );
+ 
+      --u_mm_file_reg_diagnostics_mesh   : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "REG_DIAGNOSTICS_MESH")                    
+      --                                              PORT MAP(mm_rst, mm_clk, bn_reg_diagnostics_mesh_mosi_2arr(UNB)(BN), bn_reg_diagnostics_mesh_miso_2arr(UNB)(BN) );
+
+      --u_mm_file_reg_tr_nonbonded_back  : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "REG_TR_NONBONDED_BACK")                   
+      --                                              PORT MAP(mm_rst, mm_clk, bn_reg_tr_nonbonded_back_mosi_2arr(UNB)(BN), bn_reg_tr_nonbonded_back_miso_2arr(UNB)(BN) );
+
+      --u_mm_file_ram_diag_data_buf_mesh : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "RAM_DIAG_DATA_BUF_MESH")
+      --                                              PORT MAP(mm_rst, mm_clk, bn_ram_diag_data_buf_mesh_mosi_2arr(UNB)(BN), bn_ram_diag_data_buf_mesh_miso_2arr(UNB)(BN) );
+
+      --u_mm_file_reg_ppsh               : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, BN, "BN") & "PIO_PPS") -- Using the old PIO name
+      --                                              PORT MAP(mm_rst, mm_clk, bn_reg_ppsh_mosi_2arr(UNB)(BN), bn_reg_ppsh_miso_2arr(UNB)(BN) );
+      
+      ----------------------------------------------------------------------------
+      -- bn_terminal_bg: Node function: block generator & terminals
+      ---------------------------------------------------------------------------- 
+      u_node_bn_terminal_bg : ENTITY bn_terminal_bg_lib.node_bn_terminal_bg
+      GENERIC MAP(
+        g_sim                     => c_sim,
+        g_sim_level               => g_sim_level,
+        g_use_back                => c_use_back,
+        g_mesh_nof_serial         => c_mesh_nof_serial,
+        g_mesh_use_rx             => c_mesh_use_bidir,
+        g_mesh_ena_reorder        => c_ena_mesh_reorder
+      )
+      PORT MAP(
+        -- System
+        mm_rst                      => mm_rst,
+        mm_clk                      => mm_clk,
+        dp_rst                      => dp_rst,
+        dp_clk                      => dp_clk,
+        dp_pps                      => dp_pps,
+        tr_mesh_clk                 => tr_CLK,
+        tr_back_clk                 => tr_CLK,
+        cal_clk                     => cal_rec_clk,
+        
+        chip_id                     => TO_UVEC(BN +4, c_unb_nof_chip_w),   -- BN chip ID 4,5,6,7 
+        bck_id                      => TO_UVEC(UNB, c_unb_nof_uniboard_w), -- Backplane ID 0,1,2,3 
+    
+        -- MM interface
+        -- . block generator
+        reg_diag_bg_mosi            => bn_reg_diag_bg_mosi_2arr(UNB)(BN),
+        reg_diag_bg_miso            => bn_reg_diag_bg_miso_2arr(UNB)(BN),
+        ram_diag_bg_mosi            => bn_ram_diag_bg_mosi_2arr(UNB)(BN),
+        ram_diag_bg_miso            => bn_ram_diag_bg_miso_2arr(UNB)(BN),
+        -- . tr_nonbonded mesh
+        reg_mesh_tr_nonbonded_mosi  => bn_reg_tr_nonbonded_mesh_mosi_2arr(UNB)(BN),
+        reg_mesh_tr_nonbonded_miso  => bn_reg_tr_nonbonded_mesh_miso_2arr(UNB)(BN),
+        reg_mesh_diagnostics_mosi   => bn_reg_diagnostics_mesh_mosi_2arr(UNB)(BN),
+        reg_mesh_diagnostics_miso   => bn_reg_diagnostics_mesh_miso_2arr(UNB)(BN),    
+        -- . tr_nonbonded back
+        reg_back_tr_nonbonded_mosi  => bn_reg_tr_nonbonded_back_mosi_2arr(UNB)(BN),
+        reg_back_tr_nonbonded_miso  => bn_reg_tr_nonbonded_back_miso_2arr(UNB)(BN),
+        reg_back_diagnostics_mosi   => bn_reg_diagnostics_back_mosi_2arr(UNB)(BN),
+        reg_back_diagnostics_miso   => bn_reg_diagnostics_back_miso_2arr(UNB)(BN),    
+        -- . diag_data_buffer mesh
+        ram_mesh_diag_data_buf_mosi => bn_ram_diag_data_buf_mesh_mosi_2arr(UNB)(BN),
+        ram_mesh_diag_data_buf_miso => bn_ram_diag_data_buf_mesh_miso_2arr(UNB)(BN),
+       
+        -- Mesh interface level
+        -- . Serial (tr_nonbonded)
+        mesh_tx_serial_2arr         => bn_out_mesh_serial_4arr(UNB)(BN),
+        mesh_rx_serial_2arr         => bn_in_mesh_serial_4arr(UNB)(BN),
+
+        -- Back interface level
+        -- . Serial (tr_nonbonded)
+        back_tx_serial_2arr         => bn_out_back_serial_4arr(UNB)(BN),
+        back_rx_serial_2arr         => bn_in_back_serial_4arr(UNB)(BN)
+      );
+ 
+    END GENERATE;
+
+    gen_fn: FOR FN IN 0 TO g_unb_sys.nof_fn-1 GENERATE  
+      ----------------------------------------------------------------------------
+      -- fn_terminal_db: MM <-> file I/O
+      ----------------------------------------------------------------------------
+      --u_mm_file_reg_tr_nonbonded       : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, FN, "FN") & "REG_TR_NONBONDED")
+      --                                              PORT MAP(mm_rst, mm_clk, fn_reg_tr_nonbonded_mosi_2arr(UNB)(FN), fn_reg_tr_nonbonded_miso_2arr(UNB)(FN) );
+
+      --u_mm_file_reg_diagnostics        : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, FN, "FN") & "REG_DIAGNOSTICS_MESH")
+      --                                              PORT MAP(mm_rst, mm_clk, fn_reg_diagnostics_mosi_2arr(UNB)(FN), fn_reg_diagnostics_miso_2arr(UNB)(FN) );
+
+      u_mm_file_ram_diag_data_buf      : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, FN, "FN") & "RAM_DIAG_DATA_BUFFER")
+                                                    PORT MAP(mm_rst, mm_clk, fn_ram_diag_data_buf_mosi_2arr(UNB)(FN), fn_ram_diag_data_buf_miso_2arr(UNB)(FN) );
+
+      u_mm_file_reg_diag_data_buf      : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, FN, "FN") & "REG_DIAG_DATA_BUFFER")
+                                                    PORT MAP(mm_rst, mm_clk, fn_reg_diag_data_buf_mosi_2arr(UNB)(FN), fn_reg_diag_data_buf_miso_2arr(UNB)(FN) );
+
+      --u_mm_file_ram_diag_data_buf_mesh : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, FN, "FN") & "RAM_DIAG_DATA_BUFFER_MESH")
+      --                                              PORT MAP(mm_rst, mm_clk, fn_ram_mesh_diag_data_buf_mosi_2arr(UNB)(FN), fn_ram_mesh_diag_data_buf_miso_2arr(UNB)(FN) );
+
+      --u_mm_file_reg_bsn_monitor        : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, FN, "FN") & "REG_BSN_MONITOR")
+      --                                              PORT MAP(mm_rst, mm_clk, fn_reg_bsn_monitor_mosi_2arr(UNB)(FN), fn_reg_bsn_monitor_miso_2arr(UNB)(FN) );
+
+      --u_mm_file_reg_ppsh               : mm_file GENERIC MAP(mmf_unb_file_prefix(UNB, FN, "FN") & "PIO_PPS") -- Using the old PIO name
+      --                                              PORT MAP(mm_rst, mm_clk, fn_reg_ppsh_mosi_2arr(UNB)(FN), fn_reg_ppsh_miso_2arr(UNB)(FN) );
+
+      -----------------------------------------------------------------------------
+      -- Node function: Terminals and data buffer
+      -----------------------------------------------------------------------------  
+      u_node_fn_terminal_db : ENTITY fn_terminal_db_lib.node_fn_terminal_db
+      GENERIC MAP(
+        g_sim                       => c_sim,
+        g_sim_level                 => g_sim_level,
+        g_use_bsn_align             => TRUE,
+        g_use_data_buf              => TRUE,
+        -- Terminals interface
+        g_multi_unb                 => sel_a_b(g_unb_sys.nof_unb>1, TRUE, FALSE),
+        g_mesh_nof_serial           => c_mesh_nof_serial,
+        g_mesh_use_tx               => c_mesh_use_bidir,
+        g_mesh_ena_reorder          => c_ena_mesh_reorder
+      )
+      PORT MAP(
+        -- System
+        mm_rst                      => mm_rst,
+        mm_clk                      => mm_clk,
+        dp_rst                      => dp_rst,
+        dp_clk                      => dp_clk,
+        dp_pps                      => dp_pps,
+        tr_mesh_clk                 => tr_clk,
+        cal_clk                     => cal_rec_clk,
+    
+        chip_id                     => TO_UVEC(FN, c_unb_nof_chip_w), -- FN chip ID 0,1,2,3
+    
+        -- MM interface
+        -- . tr_nonbonded
+        reg_tr_nonbonded_mosi       => fn_reg_tr_nonbonded_mosi_2arr(UNB)(FN),
+        reg_tr_nonbonded_miso       => fn_reg_tr_nonbonded_miso_2arr(UNB)(FN),
+        reg_diagnostics_mosi        => fn_reg_diagnostics_mosi_2arr(UNB)(FN),
+        reg_diagnostics_miso        => fn_reg_diagnostics_miso_2arr(UNB)(FN),
+        -- . diag_data_buffer
+        ram_diag_data_buf_mosi      => fn_ram_diag_data_buf_mosi_2arr(UNB)(FN),
+        ram_diag_data_buf_miso      => fn_ram_diag_data_buf_miso_2arr(UNB)(FN),
+        reg_diag_data_buf_mosi      => fn_reg_diag_data_buf_mosi_2arr(UNB)(FN),
+        reg_diag_data_buf_miso      => fn_reg_diag_data_buf_miso_2arr(UNB)(FN),
+        -- . diag_data_buffer_mesh
+        ram_mesh_diag_data_buf_mosi => fn_ram_mesh_diag_data_buf_mosi_2arr(UNB)(FN),
+        ram_mesh_diag_data_buf_miso => fn_ram_mesh_diag_data_buf_miso_2arr(UNB)(FN),
+        -- . bsn_monitor
+        reg_bsn_monitor_mosi        => fn_reg_bsn_monitor_mosi_2arr(UNB)(FN),
+        reg_bsn_monitor_miso        => fn_reg_bsn_monitor_miso_2arr(UNB)(FN),
+  
+        -- Mesh interface level
+        -- . Serial (tr_nonbonded)
+        tx_serial_2arr              => fn_out_mesh_serial_4arr(UNB)(FN),  -- Tx support for diagnostics
+        rx_serial_2arr              => fn_in_mesh_serial_4arr(UNB)(FN)    -- Rx
+      );
+ 
+    END GENERATE;
+
+    ------------------------------------------------------------------------------
+    -- Interconnect BN --> FN for each UniBoard
+    --
+    -- . t_unb_mesh_sl_4arr indexing [unb][node][bus][lane]
+    -- . t_unb_back_sl_4arr indexing [unb][  bn][bus][lane]
+    ------------------------------------------------------------------------------
+  
+    -- Direct interconnect BN0<->FN0.
+    no_mesh : IF g_unb_sys.nof_bn=1 AND g_unb_sys.nof_fn=1 GENERATE
+      fn_in_mesh_serial_4arr(UNB)(0) <= bn_out_mesh_serial_4arr(UNB)(0);
+      bn_in_mesh_serial_4arr(UNB)(0) <= fn_out_mesh_serial_4arr(UNB)(0);
+    END GENERATE;
+      
+    -- Mesh model
+    gen_mesh : IF g_unb_sys.nof_bn>1 OR g_unb_sys.nof_fn>1 GENERATE
+      u_mesh_model_serial : ENTITY unb_common_lib.unb_mesh_model_sl
+      GENERIC MAP(
+        g_reorder      => c_ena_mesh_reorder
+      )
+      PORT MAP (
+        -- FN to BN
+        fn_tx_sl_3arr  => fn_out_mesh_serial_4arr(UNB),
+        bn_rx_sl_3arr  => bn_in_mesh_serial_4arr(UNB),
+        
+        -- BN to FN
+        bn_tx_sl_3arr  => bn_out_mesh_serial_4arr(UNB),
+        fn_rx_sl_3arr  => fn_in_mesh_serial_4arr(UNB)
+      );
+    END GENERATE;
+   
+  END GENERATE;
+
+   ------------------------------------------------------------------------------
+   -- Instantiate a backplane model that interconnects all UniBoards...
+   ------------------------------------------------------------------------------  
+  gen_backplane : IF c_use_back=TRUE GENERATE
+    gen_model : ENTITY unb_common_lib.unb_back_model_sl
+    PORT MAP (
+      backplane_in_serial_4arr  => bn_out_back_serial_4arr,
+      backplane_out_serial_4arr => bn_in_back_serial_4arr
+   );
+  END GENERATE;
+
+   ------------------------------------------------------------------------------
+   -- ...or loop back serial TX to RX in case of a single UniBoard.
+   ------------------------------------------------------------------------------  
+  no_backplane: IF c_use_back=FALSE GENERATE
+    bn_in_back_serial_4arr <= bn_out_back_serial_4arr;
+  END GENERATE;
+
+END tb;
-- 
GitLab