diff --git a/libraries/dsp/st/hdllib.cfg b/libraries/dsp/st/hdllib.cfg
index 02987cf05a878d6d473ef63930b6d49de9696b75..a00e04d87086a3e0910487baf04a6c559e4391e5 100644
--- a/libraries/dsp/st/hdllib.cfg
+++ b/libraries/dsp/st/hdllib.cfg
@@ -18,7 +18,6 @@ synth_files =
     src/vhdl/st_histogram.vhd
     src/vhdl/st_histogram_reg.vhd
     src/vhdl/mms_st_histogram.vhd
-    src/vhdl/st_histogram_8_april.vhd
 
     tb/vhdl/tb_st_pkg.vhd 
  
@@ -31,7 +30,9 @@ test_bench_files =
     tb/vhdl/tb_st_xst.vhd
     tb/vhdl/tb_tb_st_xst.vhd
     tb/vhdl/tb_st_histogram.vhd
+
     tb/vhdl/tb_mms_st_histogram.vhd
+    tb/vhdl/tb_st_histogram.vhd
     tb/vhdl/tb_tb_st_histogram.vhd
 
 regression_test_vhdl = 
@@ -39,6 +40,7 @@ regression_test_vhdl =
     tb/vhdl/tb_tb_st_xsq.vhd
     tb/vhdl/tb_tb_st_xst.vhd
     #tb/vhdl/tb_st_calc.vhd   -- tb is not self checking yet
+    tb/vhdl/tb_tb_st_histogram.vhd
 
 
 [modelsim_project_file]
diff --git a/libraries/dsp/st/src/vhdl/mms_st_histogram.vhd b/libraries/dsp/st/src/vhdl/mms_st_histogram.vhd
index 8472efc40742fd61e77675a888cf84c742b56def..a17010950a6dd5c84c5cbece7105364dd6d51c08 100644
--- a/libraries/dsp/st/src/vhdl/mms_st_histogram.vhd
+++ b/libraries/dsp/st/src/vhdl/mms_st_histogram.vhd
@@ -18,37 +18,25 @@
 --
 -------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------
--- 
--- Author: J.W.E. Oudman
--- Purpose: Create a histogram from the input data and present it to the MM bus
--- Description: 
---   mms_st_histogram couples the st_histogram component which works entirely
---   in the dp clock domain through st_histogram_reg that handles the cross
---   domain conversion to the MM bus.
---   
---
---             --------------------------------------
---             | mms_st_histogram                   |
---             |                                    |
---             |   ----------------                 |         -------
---   snk_in -->|-->| st_histogram |                 |             ^
---             |   ----------------                 |             |
---             |      |      ^                      |
---             |      |      |                      |           dp clock domain
---             |    ram_st_histogram_miso           |
---             |      |      |                      |          
---             |      |    ram_st_histogram_mosi    |             |
---             |      v      |                      |             v
---             | --------------------               |         -------
---             | | st_histogram_reg |-- ram_miso -->|-->        mm clock domain
---             | |                  |<-- ram_mosi --|<--
---             | --------------------               |         -------
---             |                                    |
---             --------------------------------------
---
---
--------------------------------------------------------------------------------
+-- Author: 
+-- . Daniel van der Schuur 
+-- Purpose:
+-- . MMS-wrapper that adds registers and multi-instance support to st_histogram.
+-- Description:
+-- . st_histogram_reg implements the registers to control all g_nof_instances
+-- . This MMS wrapper contains logic to fill a local RAM with the contents of
+--   a selected st_histogram instance.
+-- Usage (see st_histogram_reg.vhd for the register map):
+-- . Reading RAM contents:
+--   1) User writes instance to read (0..g_nof_instances-1) to ram_fill_inst
+--      register via reg_mosi
+--   2) Users writes to bit 0 of fill_ram register via reg_mosi
+--      . ram_filling status will go high
+--   3) User reads ram_filling status until it reads zero via reg_mosi
+--   4) User reads freshly filled RAM contents via ram_mosi
+-- . Clearing the RAMs:
+--   . The inactive RAM is cleared automatically just before the next input sync.
+--      . ram_clearing status will go high during this time.
 
 LIBRARY IEEE, common_lib, mm_lib, technology_lib, dp_lib;
 USE IEEE.std_logic_1164.ALL;
@@ -59,67 +47,187 @@ USE technology_lib.technology_select_pkg.ALL;
 
 ENTITY mms_st_histogram IS
   GENERIC (
-    g_in_data_w     : NATURAL := 14;   -- >= 9 when g_nof_bins is 512; (max. c_dp_stream_data_w =768)
-    g_nof_bins      : NATURAL := 512;  -- is a power of 2 and g_nof_bins <= c_data_span; max. 512
-    g_nof_data      : NATURAL;         -- 
-    g_str           : STRING  := "freq.density"  -- to select output to MM bus ("frequency" or "freq.density")
+    g_nof_instances     : NATURAL;
+    g_data_w            : NATURAL;
+    g_nof_bins          : NATURAL;
+    g_nof_data_per_sync : NATURAL        
   );                
   PORT (            
-    dp_rst          : IN  STD_LOGIC;
-    dp_clk          : IN  STD_LOGIC;
-    mm_rst          : IN  STD_LOGIC;
-    mm_clk          : IN  STD_LOGIC;
-                    
-    -- Streaming    
-    snk_in      : IN  t_dp_sosi;
-
-    -- Memory Mapped
-    ram_mosi : IN  t_mem_mosi;
-    ram_miso : OUT t_mem_miso
+    dp_clk     : IN  STD_LOGIC;
+    dp_rst     : IN  STD_LOGIC;
+
+    snk_in_arr : IN  t_dp_sosi_arr(g_nof_instances-1 DOWNTO 0);
+
+    mm_clk     : IN  STD_LOGIC;
+    mm_rst     : IN  STD_LOGIC;               
+
+    reg_mosi   : IN  t_mem_mosi;
+    reg_miso   : OUT t_mem_miso;
+
+    ram_mosi   : IN  t_mem_mosi;
+    ram_miso   : OUT t_mem_miso
   );
 END mms_st_histogram;
 
 ARCHITECTURE str OF mms_st_histogram IS
-  
-  SIGNAL ram_st_histogram_mosi : t_mem_mosi;
-  SIGNAL ram_st_histogram_miso : t_mem_miso;
-  
+
+  CONSTANT c_reg_adr_w : NATURAL := 1;
+  CONSTANT c_ram_adr_w : NATURAL := ceil_log2(g_nof_bins);
+  CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync);
+
+  CONSTANT c_ram                    : t_c_mem := (latency  => 1,
+                                                  adr_w    => c_ram_adr_w, 
+                                                  dat_w    => c_ram_dat_w,
+                                                  nof_dat  => g_nof_bins,
+                                                  init_sl  => '0');
+
+  CONSTANT c_addr_high : NATURAL := g_nof_bins-1;
+
+  SIGNAL common_ram_cr_cw_wr_mosi     : t_mem_mosi;
+  SIGNAL nxt_common_ram_cr_cw_wr_mosi : t_mem_mosi;
+
+  SIGNAL common_ram_cr_cw_rd_mosi : t_mem_mosi;
+  SIGNAL common_ram_cr_cw_rd_miso : t_mem_miso; 
+
+  SIGNAL ram_mosi_arr  : t_mem_mosi_arr(g_nof_instances-1 DOWNTO 0);
+  SIGNAL ram_miso_arr  : t_mem_miso_arr(g_nof_instances-1 DOWNTO 0);
+
+  SIGNAL ram_clearing_arr  : STD_LOGIC_VECTOR(g_nof_instances-1 DOWNTO 0);
+
+  SIGNAL ram_fill_inst     : STD_LOGIC_VECTOR(ceil_log2(g_nof_instances)-1 DOWNTO 0);
+  SIGNAL ram_fill_inst_int : NATURAL;
+
+  SIGNAL ram_fill          : STD_LOGIC;
+  SIGNAL ram_filling       : STD_LOGIC;
+  SIGNAL nxt_ram_filling   : STD_LOGIC;
+  SIGNAL address           : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0);
+  SIGNAL nxt_address       : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0);
+   
 BEGIN 
+
+  -------------------------------------------------------------------------------
+  -- st_histogram instances and their registers
+  -------------------------------------------------------------------------------
+  gen_st_histogram : FOR i IN 0 TO g_nof_instances-1 GENERATE
+    u_st_histogram : ENTITY work.st_histogram
+    GENERIC MAP(
+      g_data_w            => g_data_w,
+      g_nof_bins          => g_nof_bins,
+      g_nof_data_per_sync => g_nof_data_per_sync
+    )
+    PORT MAP (
+      dp_clk       => dp_clk,
+      dp_rst       => dp_rst,
+      
+      snk_in       => snk_in_arr(i),
   
-  u_st_histogram : ENTITY work.st_histogram
-  GENERIC MAP(
-    g_in_data_w => g_in_data_w,
-    g_nof_bins  => g_nof_bins,
-    g_nof_data  => g_nof_data,
-    g_str       => g_str
+      ram_clearing => ram_clearing_arr(i),
+  
+      ram_mosi     => ram_mosi_arr(i),
+      ram_miso     => ram_miso_arr(i)
+    );
+  END GENERATE;
+
+  u_st_histogram_reg : ENTITY work.st_histogram_reg
+  GENERIC MAP (
+    g_nof_instances => g_nof_instances
   )
   PORT MAP (
-    dp_rst      => dp_rst,
-    dp_clk      => dp_clk,
+    dp_clk        => dp_clk,
+    dp_rst        => dp_rst,
+
+    ram_clearing  => ram_clearing_arr(0),
+    ram_filling   => ram_filling,
+
+    mm_clk        => mm_clk,
+    mm_rst        => mm_rst,
+
+    ram_fill_inst => ram_fill_inst,
+    ram_fill      => ram_fill,
     
-    snk_in      => snk_in,
-    sla_in_ram_mosi    => ram_st_histogram_mosi,
-    sla_out_ram_miso    => ram_st_histogram_miso
+    reg_mosi      => reg_mosi,
+    reg_miso      => reg_miso
   );
-  
-  u_st_histogram_reg : ENTITY work.st_histogram_reg
---  GENERIC MAP(
---    g_in_data_w =>
---    g_nof_bins  =>
---    g_nof_data  =>
---    g_str       =>
---  )
+
+
+  -------------------------------------------------------------------------------
+  -- Dual clock RAM: DP write side, MM read side
+  -------------------------------------------------------------------------------
+  u_common_ram_cr_cw : ENTITY common_lib.common_ram_cr_cw
+  GENERIC MAP (
+    g_technology     => c_tech_select_default,
+    g_ram            => c_ram,
+    g_init_file      => "UNUSED"
+  )
   PORT MAP (
-    dp_rst                => dp_rst,
-    dp_clk                => dp_clk,
-    mm_rst                => mm_rst,
-    mm_clk                => mm_clk,
-    
-    mas_out_ram_mosi => ram_st_histogram_mosi,
-    mas_in_ram_miso => ram_st_histogram_miso,
-    
-    ram_mosi              => ram_mosi,
-    ram_miso              => ram_miso
+    wr_clk   => dp_clk,
+    wr_rst   => dp_rst, 
+    wr_clken => '1',
+    wr_en    => common_ram_cr_cw_wr_mosi.wr,
+    wr_adr   => common_ram_cr_cw_wr_mosi.address(c_ram_adr_w-1 DOWNTO 0),
+    wr_dat   => common_ram_cr_cw_wr_mosi.wrdata(c_ram_dat_w-1 DOWNTO 0),
+    rd_clk   => mm_clk,
+    rd_rst   => mm_rst, 
+    rd_clken => '1',
+    rd_en    => common_ram_cr_cw_rd_mosi.rd,
+    rd_adr   => common_ram_cr_cw_rd_mosi.address(c_ram_adr_w-1 DOWNTO 0),
+    rd_dat   => common_ram_cr_cw_rd_miso.rddata(c_ram_dat_w-1 DOWNTO 0),
+    rd_val   => common_ram_cr_cw_rd_miso.rdval
   );
-  
+ 
+  -- User side MM bus for histogram readout
+  common_ram_cr_cw_rd_mosi <= ram_mosi;
+  ram_miso <= common_ram_cr_cw_rd_miso;
+
+
+  -------------------------------------------------------------------------------
+  -- Logic to move st_histogram RAM contents into the dual clock RAM above
+  -------------------------------------------------------------------------------
+
+  -- Keep track of ram_filling status and address
+  nxt_ram_filling <= '0' WHEN TO_UINT(address)=c_addr_high ELSE '1' WHEN ram_fill='1' ELSE ram_filling;
+  nxt_address <= (OTHERS=>'0') WHEN ram_filling='0' ELSE INCR_UVEC(address, 1) WHEN ram_filling='1' ELSE address;
+
+  -- Help signal for bus selection
+  ram_fill_inst_int <= TO_UINT(ram_fill_inst);
+
+  -- Do read request on ram_mosi when ram_filling
+  p_mosi_arr: PROCESS (ram_filling, address, ram_fill_inst_int)
+  BEGIN
+    FOR i IN 0 TO g_nof_instances-1 LOOP
+      ram_mosi_arr(i) <= c_mem_mosi_rst;
+      IF i = ram_fill_inst_int THEN
+        ram_mosi_arr(i).rd                              <= ram_filling;
+        ram_mosi_arr(i).address(c_ram_adr_w-1 DOWNTO 0) <= address;
+      END IF;
+    END LOOP;
+  END PROCESS;
+
+  -- Forward the read histogram data from ram_miso into write mosi of dual clock RAM
+  p_rd_miso_to_wr_mosi : PROCESS(ram_miso_arr, ram_fill_inst_int, address)
+  BEGIN
+    nxt_common_ram_cr_cw_wr_mosi <= common_ram_cr_cw_wr_mosi;
+    FOR i IN 0 TO g_nof_instances-1 LOOP
+      IF i = ram_fill_inst_int THEN
+        nxt_common_ram_cr_cw_wr_mosi.wr                              <= ram_miso_arr(i).rdval;
+        nxt_common_ram_cr_cw_wr_mosi.wrdata(c_ram_dat_w-1 DOWNTO 0)  <= ram_miso_arr(i).rddata(c_ram_dat_w-1 DOWNTO 0);
+        nxt_common_ram_cr_cw_wr_mosi.address(c_ram_adr_w-1 DOWNTO 0) <= address;
+      END IF;
+    END LOOP;
+  END PROCESS;
+
+  -- Registers
+  p_clk : PROCESS(dp_clk, dp_rst) IS
+  BEGIN
+    IF dp_rst = '1' THEN
+      common_ram_cr_cw_wr_mosi <= c_mem_mosi_rst;
+      address <= (OTHERS=>'0');
+      ram_filling <= '0';
+    ELSIF RISING_EDGE(dp_clk) THEN
+      common_ram_cr_cw_wr_mosi <= nxt_common_ram_cr_cw_wr_mosi;
+      address <= nxt_address;
+      ram_filling <= nxt_ram_filling;
+    END IF;
+  END PROCESS;
+
 END str;
diff --git a/libraries/dsp/st/src/vhdl/st_histogram.vhd b/libraries/dsp/st/src/vhdl/st_histogram.vhd
index 13b57e0ee13a3d5d2d04a7702d4a33686c2f0c31..f99a130b80b589f0a82b7120404d6c8267d09205 100644
--- a/libraries/dsp/st/src/vhdl/st_histogram.vhd
+++ b/libraries/dsp/st/src/vhdl/st_histogram.vhd
@@ -1,4 +1,4 @@
--------------------------------------------------------------------------------
+------------------------------------------------------------------------------
 --
 -- Copyright 2020
 -- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
@@ -18,68 +18,65 @@
 --
 -------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------
--- 
--- Author: J.W.E. Oudman
--- Purpose: Create a histogram from the input data and present it to 
---   st_histogram_reg
+-- Author: 
+-- . Daniel van der Schuur
+-- . Jan Oudman 
+-- Purpose: 
+-- . Count incoming data values and keep the counts in RAM as a histogram
 -- Description: 
---   The histogram component separates it's input samples in counter bins based
---   on the value of the MSbits of the input. These bins are adresses on a RAM
---   block that is swapped with another RAM block at every sync pulse plus 3 
---   cycles. While one RAM block is used to count the input samples, the other
---   is read by the MM bus through st_histogram_reg.
---
--- 
---           ram_pointer        ram_pointer
---               |                  |
---               | /o--- RAM_0 ---o |
---               |/                 |
---               /                  |
---  snk_in ----o/                   | /o----- ram_miso (st_histogram_reg)
---                                  |/           _mosi
---                                  /
---                  o--- RAM_1 ---o/
---
---
--- The input data is a dp stream which obviously uses a dp_clk. Because the
--- RAM is swapped after every sync both RAM blocks need to use the dp_clk.
--- If the MM bus needs to acces the data in a RAM block it has to acces it
--- through st_histogram_reg as the mm_clk can't be used.
---
--- The design is basically devided in the following blocks of code:
--- . Assign inputs of RAM
---   . Bin reader
---   . Bin Writer
---   . Bin Arbiter
--- . RAM selector & Dual swapped RAM instances
--- . Connect interface to DUAL swapped RAM, read out histogram statistics
--- 
+--  . See st_histogram.txt for the original design description.
+--  . The contents of the inactive RAM is cleared automatically just before the
+--    next sync interval. This way, no data is lost and all valid input data
+--    contributes to the histogram. The ram_clearing status output is high
+--    during this automated clearing.
+--  . All valid data of a DC input contributes to the histogram, no data is 
+--    lost.
+--  . The block schematic below shows the data flow from snk_in to ram_mosi:
+--    . snk_in.data is interpreted as address (bin) to read from RAM by bin_reader.
+--      . a RAM pointer 0 or 1 is kept as MS part of the address.
+--        . snk_in.sync determines the RAM pointer 0 or 1.
+--    . The data read from that adress, the bin count, is incremented and written
+--      back by bin_writer.
+--    . bin_arbiter decides whether a read or write accessw takes precedence, in case
+--      of simultanious RAM access requests by both bin_reader and bin_writer.
+--    . Upon request (ram_miso), the bin counts (the histogram) are output on 
+--      ram_mosi.
+--                             bin_reader_miso    bin_arbiter_rd_miso             
+--               __________    |   ___________    |   ___________                 
+--              |          |   |  |           |   |  |           |                
+-- ---snk_in--->|bin_reader|<--+--|           |<--+--|           |                
+--              |__________|      |           |      |           |                
+--                   |            |           |      |           |                
+--                   |            |           |      |           |                
+--     bin_reader_to_writer_mosi  |bin_arbiter|      | RAM(1..0) |----ram_mosi--->
+--                   |            |           |      |           |                
+--               ____v_____       |           |      |           |                
+--              |          |      |           |      |           |                
+--              |bin_writer|---+->|           |---+->|           |                
+--              |__________|   |  |___________|   |  |___________|                
+--                             |                  |                               
+--                             bin_writer_mosi    bin_arbiter_wr_mosi             
+-- Usage:
+-- . The ram_mosi input applies to the RAM page that is inactive (not
+--   being written to from data path) *at that time*. The user should take care to
+--   time these controls such that the active RAM page does not swap before these
+--   operation (ram_mosi readout) has finished.
 -- Remarks:
--- . Because the values of the generics g_nof_bins depends on g_in_data_w
---   (you should not have more bins than data values) an assert is made to
---   warn in the simulation when the maximum value of g_nof_bins is reached.
---   If exceeded the simulator will throw fatal error ("...Port length (#) does
---   not match actual length (#)...")
---
--- . when an adress is determined it takes 2 cycles to receive it's value and
---   another cycle before the calculated value can be written into that RAM
---   adress (1st cycle: address; 3rd cycle: data available; 5th cycle: write 
---   data). There is also the limitation of not being able to read and write 
---   on the same adress at the same time. These limitations cause the following
---   complications in the implementation:
---   . repeating samples of the same adress have to be counted first till 
---     another adress appears before written (as you would miss the second and
---     further consecutive samples and have the read/write limitation)
---   . If adresses are toggling at every cycle (e.g. adress 0; 1; 0; 1) you
---     have to remember the data to be written and increment it as you have the
---     read/write limitation (missing samples) and writing takes priority 
---     in this case
---   . When a sync signal appears the RAM has to be swapped 4 cycles later so 
---     the first 3 cycles may/can not ask a read from the old RAM block (the 
---     read_enable takes one cycle hence the difference of 3 against 4 cycles) 
---   
--------------------------------------------------------------------------------
+-- . The RAM block we use basically needs 3 ports:
+--   1 - read port in dp_clk domain to read current bin value
+--   2 - write port in dp_clk domain to write back incremented bin value
+--   3 - read port in mm_clk domain to read the inactive page
+-- . common_ram_r_w
+--   . Why common_ram_r_w was selected: it uses a single clock
+--     . We need to read and write back bins in the dp_clk clock domain, so our RAM
+--       block needs to have 2 separate address inputs - but in the same clock domain.
+--       . The other, dual clock, RAM blocks (e.g. common_ram_cr_cw) are based on 
+--         common_ram_crw_crw and use 2 address inputs (adr_a,adr_b), each in 
+--         its own (clk_a,clk_b) clock domain, which is not what we need here.
+--   . Downside of common_ram_r_w: it uses a single clock
+--     . This st_histogram.vhd operates in dp_clk domain only, so we need to 
+--       provide MM access to the user, in the mm_clk domain, elsewhere. This
+--       has been done in mms_st_histogram.vhd.
 
 LIBRARY IEEE, common_lib, mm_lib, technology_lib, dp_lib;
 USE IEEE.std_logic_1164.ALL;
@@ -90,704 +87,332 @@ USE technology_lib.technology_select_pkg.ALL;
 
 ENTITY st_histogram IS
   GENERIC (
-    g_in_data_w         : NATURAL := 14;   -- >= 9 when g_nof_bins is 512; (max. c_dp_stream_data_w =768)         <-- maybe just g_data_w ??
-    g_nof_bins          : NATURAL := 512;  -- is a power of 2 and g_nof_bins <= c_data_span; max. 512
-    g_nof_data          : NATURAL;         -- 
-    g_str               : STRING  := "freq.density";  -- to select output to MM bus ("frequency" or "freq.density")
-    g_ram_miso_sim_mode : BOOLEAN := FALSE -- when TRUE the ram_miso bus will get a copy of the data written into the RAM.
-  );                
+    g_data_w            : NATURAL := 8;
+    g_nof_bins          : NATURAL := 256;
+    g_nof_data_per_sync : NATURAL := 1024
+  );
   PORT (            
-    dp_rst              : IN  STD_LOGIC;
-    dp_clk              : IN  STD_LOGIC;
+    dp_clk       : IN  STD_LOGIC;
+    dp_rst       : IN  STD_LOGIC;
                     
-    -- Streaming    
-    snk_in              : IN  t_dp_sosi;
-    
-    -- DP clocked memory bus
-    sla_in_ram_mosi     : IN  t_mem_mosi;  -- Beware, works in dp clock domain !
-    sla_out_ram_miso    : OUT t_mem_miso;   --  ''                              !
---    ram_mosi : IN  t_mem_mosi;  -- Beware, works in dp clock domain !
---    ram_miso : OUT t_mem_miso   --  ''                              !
-    -- Debug bus
-    dbg_ram_miso        : OUT t_mem_miso
+    snk_in       : IN  t_dp_sosi; -- Active RAM page swaps on snk_in.sync
+
+    ram_clearing : OUT STD_LOGIC; -- Status output: high while RAM is being cleared
+
+    ram_mosi     : IN  t_mem_mosi; -- MM access to the inactive RAM page
+    ram_miso     : OUT t_mem_miso
   );
 END st_histogram;
 
 
 ARCHITECTURE rtl OF st_histogram IS
 
---  CONSTANT c_data_span    : NATURAL  := pow2(g_in_data_w);      -- any use?
---  CONSTANT c_bin_w        : NATURAL  := ceil_log2(g_nof_data);  -- any use?
-  CONSTANT c_clear        : NATURAL := g_nof_data - g_nof_bins;
-  CONSTANT c_adr_w        : NATURAL := ceil_log2(g_nof_bins);
-  CONSTANT c_adr_low_calc : INTEGER := g_in_data_w-c_adr_w;          -- Calculation might yield a negative number
-  CONSTANT c_adr_low      : NATURAL := largest(0, c_adr_low_calc);   -- Override any negative value of c_adr_low_calc
-  CONSTANT c_ram          : t_c_mem := (latency  => 1,
-                                        adr_w    => c_adr_w,          -- 9 bits needed to adress/select 512 adresses
-                                        dat_w    => c_word_w,         -- 32bit, def. in common_pkg; >= c_bin_w
-                                        nof_dat  => g_nof_bins,       -- 512 adresses with 32 bit words, so 512
-                                        init_sl  => '0');             -- MM side : sla_in, sla_out
-                                 
---  CONSTANT c_mem_miso_setting     : t_mem_miso := (rddata => mem_miso_init,  -- c_mem_miso_rst; -- limit to 32 bit 
---                                                   rdval => '0',
---                                                   waitrequest => '0' );
-  
---  SIGNAL mem_miso_init    : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := (OTHERS => '0');
+  -------------------------------------------------------------------------------
+  -- Constants derived from generics
+  -------------------------------------------------------------------------------
+  CONSTANT c_ram_adr_w : NATURAL := ceil_log2(g_nof_bins);
+  CONSTANT c_adr_low   : NATURAL := g_data_w-c_ram_adr_w; 
+  CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync)+1;
 
-  SIGNAL snk_in_p                : t_dp_sosi;
-  SIGNAL snk_in_pp               : t_dp_sosi;
-  SIGNAL snk_in_pppp             : t_dp_sosi;
-  
-  SIGNAL bin_reader_mosi         : t_mem_mosi := c_mem_mosi_rst;
-  SIGNAL prev_bin_reader_mosi    : t_mem_mosi := c_mem_mosi_rst;
-  SIGNAL bin_reader_mosi_pp      : t_mem_mosi := c_mem_mosi_rst;
-  SIGNAL bin_reader_mosi_ppp     : t_mem_mosi := c_mem_mosi_rst;
+  -------------------------------------------------------------------------------
+  -- ram_pointer
+  -------------------------------------------------------------------------------
+  SIGNAL toggle_ram_pointer     : STD_LOGIC;
+  SIGNAL nxt_toggle_ram_pointer : STD_LOGIC;
+  SIGNAL ram_pointer            : STD_LOGIC;
+  SIGNAL prv_ram_pointer        : STD_LOGIC;
 
-  SIGNAL nxt_bin_writer_mosi     : t_mem_mosi;
-  SIGNAL bin_writer_mosi         : t_mem_mosi;
+  -------------------------------------------------------------------------------
+  -- bin_reader
+  -------------------------------------------------------------------------------
+  SIGNAL bin_reader_mosi     : t_mem_mosi;
+  SIGNAL bin_reader_miso     : t_mem_miso;
 
-  SIGNAL nxt_bin_arbiter_wr_mosi : t_mem_mosi;
-  SIGNAL bin_arbiter_wr_mosi     : t_mem_mosi;
+  SIGNAL prv_bin_reader_mosi : t_mem_mosi;
 
-  SIGNAL nxt_bin_arbiter_rd_mosi : t_mem_mosi;
-  SIGNAL bin_arbiter_rd_mosi     : t_mem_mosi;
+  -------------------------------------------------------------------------------
+  -- bin_writer
+  -------------------------------------------------------------------------------
+  SIGNAL bin_reader_to_writer_mosi : t_mem_mosi;
 
-  SIGNAL bin_arbiter_rd_miso     : t_mem_miso := c_mem_miso_rst;
-  SIGNAL bin_reader_rd_miso      : t_mem_miso := c_mem_miso_rst;
-  SIGNAL common_ram_r_w_miso   : t_mem_miso := c_mem_miso_rst;
-  
-  SIGNAL init_phase              : STD_LOGIC := '1';
-  SIGNAL nxt_init_phase          : STD_LOGIC;
-                                
-  SIGNAL rd_cnt_allowed          : STD_LOGIC := '0';
-  SIGNAL rd_cnt_allowed_pp       : STD_LOGIC := '0';
-  
-  SIGNAL toggle_detect           : STD_LOGIC := '0';
-  SIGNAL toggle_detect_pp        : STD_LOGIC;
-  SIGNAL toggle_detect_false     : STD_LOGIC := '1';
-  SIGNAL nxt_toggle_detect_false : STD_LOGIC;
-  
-  SIGNAL nxt_prev_wrdata         : NATURAL;
-  SIGNAL prev_wrdata             : NATURAL;
-  SIGNAL prev_prev_wrdata        : NATURAL;
-  SIGNAL prev_prev_prev_wrdata   : NATURAL;
-  
-  SIGNAL sync_detect             : STD_LOGIC := '0';
-  SIGNAL sync_detect_pp          : STD_LOGIC;
-                                 
-  SIGNAL same_r_w_address        : STD_LOGIC;
-  SIGNAL same_r_w_address_pp     : STD_LOGIC;
-  
-  --debug signals
-  SIGNAL dbg_state_string        : STRING(1 TO 3) := "   ";
-  SIGNAL dbg_snk_data            : STD_LOGIC_VECTOR(g_in_data_w-1 DOWNTO 0);
+  SIGNAL nxt_bin_writer_mosi       : t_mem_mosi;
+  SIGNAL bin_writer_mosi           : t_mem_mosi;
+
+  -------------------------------------------------------------------------------
+  -- bin_arbiter
+  -------------------------------------------------------------------------------
+  SIGNAL bin_arbiter_wr_ram_pointer     : STD_LOGIC;
+  SIGNAL bin_arbiter_rd_ram_pointer     : STD_LOGIC;
+  SIGNAL prv_bin_arbiter_rd_ram_pointer : STD_LOGIC;
+
+  SIGNAL read_allowed                   : BOOLEAN;
+  SIGNAL prv_read_allowed               : BOOLEAN;
+
+  SIGNAL nxt_bin_arbiter_wr_mosi        : t_mem_mosi;
+  SIGNAL bin_arbiter_wr_mosi            : t_mem_mosi;
+  SIGNAL bin_arbiter_rd_mosi            : t_mem_mosi;
+  SIGNAL bin_arbiter_rd_miso            : t_mem_miso;
+
+  -------------------------------------------------------------------------------
+  -- 2x RAM (common_ram_r_w) instances
+  -------------------------------------------------------------------------------
+  CONSTANT c_nof_ram_pages     : NATURAL := 2;
+
+  CONSTANT c_ram                    : t_c_mem := (latency  => 1,
+                                                  adr_w    => c_ram_adr_w, 
+                                                  dat_w    => c_ram_dat_w,
+                                                  nof_dat  => g_nof_bins,
+                                                  init_sl  => '0');
+
+  SIGNAL common_ram_r_w_wr_mosi_arr : t_mem_mosi_arr(1 DOWNTO 0);
+  SIGNAL common_ram_r_w_rd_mosi_arr : t_mem_mosi_arr(1 DOWNTO 0);
+  SIGNAL common_ram_r_w_rd_miso_arr : t_mem_miso_arr(1 DOWNTO 0); 
+
+  SIGNAL histogram_wr_mosi          : t_mem_mosi;
+  SIGNAL histogram_rd_mosi          : t_mem_mosi;
+  SIGNAL histogram_rd_miso          : t_mem_miso;
+
+  -------------------------------------------------------------------------------
+  -- ram_clear 
+  -------------------------------------------------------------------------------
+  CONSTANT c_data_cnt_w        : NATURAL := ceil_log2(g_nof_data_per_sync);
+
+  SIGNAL data_cnt              : STD_LOGIC_VECTOR(c_data_cnt_w-1 DOWNTO 0);
+  SIGNAL nxt_data_cnt          : STD_LOGIC_VECTOR(c_data_cnt_w-1 DOWNTO 0);
+
+  SIGNAL ram_clear             : STD_LOGIC;
+
+  SIGNAL ram_clear_address     : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0);
+  SIGNAL nxt_ram_clear_address : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0);
+
+  SIGNAL i_ram_clearing        : STD_LOGIC;
+  SIGNAL nxt_ram_clearing      : STD_LOGIC;
 
-  
-  SIGNAL ram_pointer       : STD_LOGIC  := '0';
-  SIGNAL cycle_cnt         : NATURAL    :=  0 ;
-  SIGNAL nxt_cycle_cnt     : NATURAL    :=  0 ;
---  SIGNAL wr_en           : STD_LOGIC  := '0';
---  SIGNAL nxt_wr_en       : STD_LOGIC;
---  SIGNAL wr_dat          : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
---  SIGNAL nxt_wr_dat      : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
---  SIGNAL wr_adr             : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
---  SIGNAL rd_adr             : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
---  SIGNAL rd_en           : STD_LOGIC  := '0';
---  SIGNAL rd_dat          : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
---  SIGNAL rd_val          : STD_LOGIC;
-  
-  SIGNAL mm_adr_cnt        : NATURAL   :=  0 ;
-  SIGNAL mm_adr_illegal    : STD_LOGIC := '0';
-  SIGNAL mm_adr_illegal_pp : STD_LOGIC := '0';
-  
-  
-  SIGNAL ram_0_wr_en       : STD_LOGIC;
-  SIGNAL ram_0_wr_dat      : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
-  SIGNAL ram_0_wr_adr      : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
-  SIGNAL ram_0_rd_adr      : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
-  SIGNAL ram_0_rd_en       : STD_LOGIC;
-  SIGNAL ram_0_rd_dat      : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
-  SIGNAL ram_0_rd_val      : STD_LOGIC;
-                          
-  SIGNAL ram_1_wr_en       : STD_LOGIC;
-  SIGNAL ram_1_wr_dat      : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
-  SIGNAL ram_1_wr_adr      : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
-  SIGNAL ram_1_rd_adr      : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
-  SIGNAL ram_1_rd_en       : STD_LOGIC;
-  SIGNAL ram_1_rd_dat      : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
-  SIGNAL ram_1_rd_val      : STD_LOGIC;
-  
-  SIGNAL ram_out_wr_en     : STD_LOGIC;
-  SIGNAL ram_out_wr_dat    : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
-  SIGNAL ram_out_wr_adr    : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
-  SIGNAL ram_out_rd_adr    : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
-  SIGNAL ram_out_rd_en     : STD_LOGIC;
-  SIGNAL ram_out_rd_dat    : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0);
-  SIGNAL ram_out_rd_val    : STD_LOGIC;
-  
-  SIGNAL prev_ram_out_wr_adr  : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
-  SIGNAL ram_out_same_w_r_adr : STD_LOGIC;
-  
 BEGIN 
-  
-  -----------------------------------------------------------------------------
-  -- Check Generics
-  -----------------------------------------------------------------------------
-  ASSERT c_adr_low_calc>0 REPORT "ceil_log2(g_nof_bins) is as large as g_in_data_w, don't increase g_nof_bins" SEVERITY WARNING;
-  
-  -----------------------------------------------------------------------------
-  -- Assign inputs of RAM:                                                                  <-- use parts of description for bin_writer
-  -- . Determine address based on input data
-  -- . Compare adress with the two previous adresses and if:
-  --   . it is the same as the last adress increase a counter
-  --   . it is the same as 2 cycles back but not the last copy the data to be  
-  --     written directly into a local counter instead of trying to read (ask)
-  --     it back from RAM at the same clock cycle (which is impossible)
-  --   . it is not the same enable the nxt_wr_dat data to be written           .
-  --     at the next cycle by making nxt_wr_en high                            .
-  -- . Write the wr_dat data to the RAM
-  -- . At the snk_in.sync pulse:
-  --   . let first 3 cycles start counting from 0 again
-  --   . (plus 3 cycles) let counting depend on values in RAM (which should
-  --     be 0)
-  -- . Restart or pause counting when a snk_in.valid = '0' appears:
-  --   . pause when adress is the same as the previous adress
-  --   . restart from 0 when adress is not the same as previous adress
-  --   . restart from 0 when also a sync appears
-  --
-  --
-  -- . in  : snk_in                (latency: 0)
-  --       : common_ram_r_w_miso   (latency: 2)
-  -- . out : snk_in_pppp.sync      (latency: 4)
-  --       : bin_arbiter_wr_mosi   (latency: 4)
-  --       : bin_arbiter_rd_mosi   (latency: 1)
-  -- 
-  ----------------------------------------------------------------------------
-  
-  -----------------------------------------------------------------------------
-  -- Bin reader: Convert snk_in data to bin_reader_mosi with read request 
-  --             and generate signals for detection of problems in the 
-  --             consecutive data.
-  -- . in  : snk_in               (latency: 0)
-  --       : bin_arbiter_rd_miso  (latency: 2)
-  -- . out : init_phase           (latency: 0 ?
-  --       : bin_reader_mosi      (latency: 0)
-  --       : prev_bin_reader_mosi (latency: 1)
-  --       : bin_reader_mosi_pp   (latency: 2)
-  --       : bin_reader_mosi_ppp  (latency: 3)
-  --       : bin_reader_rd_miso   (latency: 2)
-  --       : rd_cnt_allowed_pp    (latency: 2)
-  --       : same_r_w_address_pp  (latency: 2)
-  --       : toggle_detect_pp     (latency: 2)
-  --       : sync_detect          (latency: 0)
-  --       : sync_detect_pp       (latency: 2)
-  -----------------------------------------------------------------------------
-  bin_reader_mosi.rd                          <= snk_in.valid; -- when 1, count allowed
-  bin_reader_mosi.address(c_adr_w-1 DOWNTO 0) <= snk_in.data(g_in_data_w-1 DOWNTO c_adr_low); 
-  bin_reader_rd_miso                          <= bin_arbiter_rd_miso;
-  
-  --snk_in pipeline; Enable sync and valid comparisons
-  u_dp_pipeline_snk_in_1_cycle : ENTITY dp_lib.dp_pipeline
-  GENERIC MAP (
-    g_pipeline   => 1  -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    rst          => dp_rst,
-    clk          => dp_clk,
-    snk_in       => snk_in,
-    src_out      => snk_in_p
-  );
-  
---  init_phase <= '0' WHEN snk_in_p.sync = '1'; -- ELSE will be impossible since the init_phase may only be triggered once on the first sync
-  nxt_init_phase <= '0' WHEN snk_in.sync='1' ELSE init_phase;
-  
-  p_init_phase : PROCESS(dp_clk, dp_rst)
+
+  -------------------------------------------------------------------------------
+  -- ram_pointer: Keep track of what RAM to target
+  -- . Target either RAM 0 or 1 per sync period
+  -- . RD/WR sides of RAM have shifted sync periods due to rd>wr latency
+  --   . e.g. a new sync period is read while an old sync period is written
+  --   . Solution: treat the RAM pointer as MS address bit in separate RD/WR buses
+  --   . ram_pointer is synchronous to snk_in.sync
+  -------------------------------------------------------------------------------
+  p_ram_pointer : PROCESS(dp_rst, dp_clk) IS
   BEGIN
-    IF dp_rst = '1' THEN
-      init_phase          <= '1';
-      toggle_detect_false <= '1';
+    IF dp_rst='1' THEN
+      prv_ram_pointer    <= '0';
+      toggle_ram_pointer <= '0';
     ELSIF RISING_EDGE(dp_clk) THEN
-      init_phase          <= nxt_init_phase;
-      toggle_detect_false <= nxt_toggle_detect_false;
+      toggle_ram_pointer <= nxt_toggle_ram_pointer;
+      prv_ram_pointer    <= ram_pointer;
     END IF;
   END PROCESS;
-  
-  -- Enable sync comparisons
-  u_dp_pipeline_snk_in_2_cycle : ENTITY dp_lib.dp_pipeline
-  GENERIC MAP (
-    g_pipeline   => 2  -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    rst          => dp_rst,
-    clk          => dp_clk,
-    snk_in       => snk_in,
-    src_out      => snk_in_pp
-  );
-  
-  -- Enable switching the ram_pointer
-  u_dp_pipeline_snk_in_4_cycle : ENTITY dp_lib.dp_pipeline
-  GENERIC MAP (
-    g_pipeline   => 4  -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    rst          => dp_rst,
-    clk          => dp_clk,
-    snk_in       => snk_in,
-    src_out      => snk_in_pppp
-  );
-  
-  dbg_snk_data <= snk_in_pp.data(g_in_data_w-1 DOWNTO 0);
-  
---  toggle_detect_false <= '0' WHEN snk_in_pp.sync = '1'; -- ELSE will be impossible since the toggle_detect_false may only be triggered once on the first sync
-  nxt_toggle_detect_false <= '0' WHEN snk_in_p.sync='1' ELSE toggle_detect_false;
-  sync_detect <= snk_in.valid WHEN (snk_in.sync='1' OR snk_in_p.sync='1' OR snk_in_pp.sync='1') ELSE '0'; -- @sync, first 3 cycles would try to read from the wrong (old) RAM block, detect this problem
-  
-  -- Line up to p_nxt_bin_writer_mosi process  
-  u_common_pipeline_sl_sync_detect_2_cycle : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => sync_detect,
-    out_dat => sync_detect_pp
-  );
-  
-  -- Enable adress comparisons 1 cycle back  
-  -- Skip unvalid data with trigger bin_reader_mosi.rd to make comparisons between unvalid-data-seperated data possible.
-  u_common_pipeline_bin_reader_mosi_1_cycle : ENTITY common_lib.common_pipeline
-  GENERIC MAP (
-    g_representation => "UNSIGNED", --orig. signed
-    g_pipeline       => 1,
-    g_in_dat_w       => c_adr_w, -- c_mem_address_w
-    g_out_dat_w      => c_adr_w
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    clken   => bin_reader_mosi.rd, -- '1',
-    in_dat  => STD_LOGIC_VECTOR(bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)),
-    out_dat => prev_bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)
-  );
-  
-  -- Enable adress comparisons 2 cycles back
-  u_common_pipeline_bin_reader_mosi_2_cycle : ENTITY common_lib.common_pipeline
-  GENERIC MAP (
-    g_representation => "UNSIGNED", --orig. signed
-    g_pipeline       => 1,
-    g_in_dat_w       => c_adr_w,
-    g_out_dat_w      => c_adr_w
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => STD_LOGIC_VECTOR(prev_bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)),
-    out_dat => bin_reader_mosi_pp.address(c_adr_w-1 DOWNTO 0)
-  );
-  
-  -- Enable adress comparisons 3 cycles back
-  u_common_pipeline_bin_reader_mosi_3_cycle : ENTITY common_lib.common_pipeline
-  GENERIC MAP (
-    g_representation => "UNSIGNED", --orig. signed
-    g_pipeline       => 2,
-    g_in_dat_w       => c_adr_w,
-    g_out_dat_w      => c_adr_w
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => STD_LOGIC_VECTOR(prev_bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)),
-    out_dat => bin_reader_mosi_ppp.address(c_adr_w-1 DOWNTO 0)
-  );
-  
-  
-  -- Only count sequential valid data on the same address when: address is the same as last and 1 or 2 cycles after the sync when in sync_detect; address is the same as last and past the initialisation and outside sync_detect
-  rd_cnt_allowed <= snk_in.valid WHEN ( bin_reader_mosi.address = prev_bin_reader_mosi.address AND ( snk_in_p.sync='1' OR (snk_in_pp.sync='1' AND snk_in_p.valid='1') ) )
-                                 OR (bin_reader_mosi.address = prev_bin_reader_mosi.address AND init_phase='0' AND sync_detect='0')
-                                 ELSE '0';
-  
-  -- Line rd_cnt_allowed up to p_nxt_bin_writer_mosi process
-  u_common_pipeline_sl_rd_cnt_allowed : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => rd_cnt_allowed,
-    out_dat => rd_cnt_allowed_pp
-  );
-  
-  -- Detect a (valid) repeating address seperated by one other address past the initialisation and outside the first two cycles of a (new) sync                                        --also @sync, one wil be true; use  NOT(1 or 1) instead of (0 or 0)
-  toggle_detect  <= snk_in.valid WHEN (bin_reader_mosi_pp.address = bin_reader_mosi.address AND bin_reader_mosi_pp.address /= prev_bin_reader_mosi.address AND toggle_detect_false = '0' AND NOT(snk_in.sync='1' OR snk_in_p.sync='1') ) 
-                                 ELSE '0';
 
-  
-  -- Line up to p_nxt_bin_writer_mosi process
-  u_common_pipeline_sl_toggle_detect : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => toggle_detect,
-    out_dat => toggle_detect_pp
-  );
-  
-  -- Detect an (valid) address that has to be read as well as written at the same time
-  same_r_w_address <= snk_in.valid WHEN (bin_reader_mosi.address = bin_reader_mosi_ppp.address AND init_phase = '0' AND sync_detect = '0') ELSE '0';
-  
-  -- Line up top p_nxt_bin_writer_mosi process
-  u_common_pipeline_sl_same_r_w_address : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => same_r_w_address,
-    out_dat => same_r_w_address_pp
-  );
+  -- Don't toggle the RAM pointer on the first sync as we're already reading the RAM at that point.
+  nxt_toggle_ram_pointer <= '1' WHEN snk_in.sync='1' ELSE toggle_ram_pointer;
+  -- Toggle the RAM pointer starting from 2nd sync onwards
+  ram_pointer <= NOT prv_ram_pointer WHEN snk_in.sync='1' AND toggle_ram_pointer='1' ELSE prv_ram_pointer;
 
 
-  -----------------------------------------------------------------------------
-  -- Bin writer : increments current bin value and sets up write request
-  -- . in  : toggle_detect_pp      (latency: 2)
-  -- . in  : same_r_w_address_pp   (latency: 2)
-  -- . in  : bin_reader_mosi_pp    (latency: 2)
-  -- . in  : bin_reader_rd_miso    (latency: 2)  aka bin_arbiter_rd_miso or common_ram_r_w_miso
-  -- . in  : rd_cnt_allowed_pp     (latency: 2)
-  -- . in  : sync_detect_pp
-  -- . out : bin_writer_mosi  (latency: 3)
-  -----------------------------------------------------------------------------
-  p_nxt_bin_writer_mosi : PROCESS(bin_reader_rd_miso, 
-                                  bin_reader_mosi_pp.address, toggle_detect_pp, rd_cnt_allowed_pp, prev_wrdata, prev_prev_wrdata, prev_prev_prev_wrdata, sync_detect_pp, same_r_w_address_pp) IS
-  BEGIN
-    nxt_bin_writer_mosi <= c_mem_mosi_rst;
-    dbg_state_string <= "unv";
-    IF bin_reader_rd_miso.rdval='1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= INCR_UVEC(bin_reader_rd_miso.rddata, 1);
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= TO_UINT(bin_reader_rd_miso.rddata) + 1;
-      dbg_state_string <= "val";
-
-    ELSIF toggle_detect_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_prev_wrdata+1), c_mem_data_w);
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= prev_prev_wrdata+1;
-      dbg_state_string <= "td ";
-      
-    ELSIF rd_cnt_allowed_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_wrdata + 1), c_mem_data_w);
-      nxt_prev_wrdata             <= prev_wrdata + 1;
-      dbg_state_string <= "r# ";
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      
-    ELSIF sync_detect_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC(1, c_mem_data_w); -- snk_in.sync: 1; snk_in_p.sync (thus new adress): 1; snk_in_pp.sync (thus new adress): 1
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= 1;
-      dbg_state_string  <= "sd ";
-      
-    ELSIF same_r_w_address_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_prev_prev_wrdata+1), c_mem_data_w);
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= prev_prev_prev_wrdata + 1;
-      dbg_state_string  <= "srw";
-    END IF;
-  END PROCESS; 
-  
-  p_prev_wrdata : PROCESS(dp_clk, dp_rst, nxt_bin_writer_mosi.wr) IS  --seperated from p_bin_writer_mosi since the implementation was unwanted
+  -------------------------------------------------------------------------------
+  -- bin_reader : reads bin from RAM, sends bin to bin_writer.
+  -- . Input  : snk_in          (input data stream)
+  --            bin_reader_miso (reply to RAM read request: rddata = bin count)
+  --            ram_pointer (to put in MOSI buses as MS address bit)
+  -- . Output : bin_reader_mosi (RAM read request, address = bin)
+  --            bin_reader_to_writer_mosi (address = bin, wrdata = bin count)
+  -------------------------------------------------------------------------------
+  -- Fetch the bin from RAM
+  bin_reader_mosi.wrdata  <= (OTHERS=>'0');
+  bin_reader_mosi.wr      <= '0';
+  bin_reader_mosi.rd      <= snk_in.valid;
+  bin_reader_mosi.address <= RESIZE_UVEC(ram_pointer & snk_in.data(g_data_w-1 DOWNTO c_adr_low), c_word_w); 
+
+  -- Store the rd address as bin_writer needs to know where to write the bin count
+  p_prv_bin_reader_mosi : PROCESS(dp_clk, dp_rst) IS
   BEGIN
     IF dp_rst = '1' THEN
-      prev_wrdata           <= 0;
-      prev_prev_wrdata      <= 0;
-      prev_prev_prev_wrdata <= 0;
-    ELSIF nxt_bin_writer_mosi.wr='1' AND RISING_EDGE(dp_clk) THEN
-      prev_wrdata           <= nxt_prev_wrdata;
-      prev_prev_wrdata      <= prev_wrdata;
-      prev_prev_prev_wrdata <= prev_prev_wrdata;
+      prv_bin_reader_mosi <= c_mem_mosi_rst;
+    ELSIF RISING_EDGE(dp_clk) THEN
+      prv_bin_reader_mosi  <= bin_reader_mosi;
     END IF;
   END PROCESS;
 
-  p_bin_writer_mosi : PROCESS(dp_clk, dp_rst) IS  --, nxt_bin_writer_mosi, nxt_prev_wrdata, prev_wrdata, prev_prev_wrdata
+  -- Forward the read bin + count to bin writer
+  bin_reader_to_writer_mosi.wr      <= bin_reader_miso.rdval;
+  bin_reader_to_writer_mosi.wrdata  <= RESIZE_UVEC(bin_reader_miso.rddata(c_ram_dat_w-1 DOWNTO 0), c_mem_data_w);
+  bin_reader_to_writer_mosi.address <= prv_bin_reader_mosi.address;
+
+
+  -------------------------------------------------------------------------------
+  -- bin_writer : Increment the bin, forward write request to bin_arbiter
+  -- . Input  : bin_reader_to_writer_mosi (from bin_reader = bin + bin count)
+  -- . Output : bin_writer_mosi (to bin_arbiter = bin + incremented bin count)
+  -------------------------------------------------------------------------------
+  nxt_bin_writer_mosi.rd      <= '0';
+  nxt_bin_writer_mosi.wr      <= bin_reader_to_writer_mosi.wr;
+  nxt_bin_writer_mosi.address <= bin_reader_to_writer_mosi.address;
+  nxt_bin_writer_mosi.wrdata  <= INCR_UVEC(bin_reader_to_writer_mosi.wrdata, 1) WHEN bin_reader_to_writer_mosi.wr='1' ELSE bin_writer_mosi.wrdata; 
+ 
+  -- Register the outputs to bin_arbiter (above we have a combinational adder = propagation delay)
+  p_bin_writer_mosi : PROCESS(dp_clk, dp_rst) IS
   BEGIN
     IF dp_rst = '1' THEN
-       bin_writer_mosi       <= c_mem_mosi_rst;
---       prev_wrdata           <= 0;
---       prev_prev_wrdata      <= 0;
---       prev_prev_prev_wrdata <= 0;
+      bin_writer_mosi     <= c_mem_mosi_rst;
     ELSIF RISING_EDGE(dp_clk) THEN
-       bin_writer_mosi <= nxt_bin_writer_mosi;
---       IF nxt_bin_writer_mosi.wr = '1' THEN
---         prev_wrdata     <= nxt_prev_wrdata;
---         prev_prev_wrdata<= prev_wrdata;
---         prev_prev_prev_wrdata <= prev_prev_wrdata;
---       END IF;
+      bin_writer_mosi     <= nxt_bin_writer_mosi;
     END IF;
   END PROCESS;
 
 
-  -----------------------------------------------------------------------------
-  -- Bin Arbiter: Determine next RAM access
-  -- . in  : bin_reader_mosi       (latency: 0)
-  --       : init_phase            (latency: 0)
-  --       : prev_bin_reader_mosi  (latency: 1)
-  --       : bin_reader_mosi_pp    (latency: 2)
-  --       : bin_reader_mosi_ppp   (latency: 3)
-  --       : bin_writer_mosi       (latency: 3)
-  --       : sync_detect           (latency:    0? or 3?
-  --       : common_ram_r_w_miso   (latency: 2)
-  -- . out : bin_arbiter_rd_mosi   (latency: 1)
-  -- .     : bin_arbiter_rd_miso   (latency: 2)
-  -- .     : bin_arbiter_wr_mosi   (latency: 4)
-  -----------------------------------------------------------------------------
-  nxt_bin_arbiter_wr_mosi <= bin_writer_mosi;
-  -- Read RAM when subsequent addresses are not the same, when there is no toggle detected and only when the same address is not going to be written to. When a sync is detected don't read in the old RAM block.
-  nxt_bin_arbiter_rd_mosi.rd <= bin_reader_mosi.rd WHEN (bin_reader_mosi.address /= prev_bin_reader_mosi.address AND bin_reader_mosi.address /= bin_reader_mosi_pp.address 
-                                                         AND NOT(bin_reader_mosi.address = bin_reader_mosi_ppp.address) AND sync_detect='0')
-                                                   OR (init_phase = '1') ELSE '0';
-  nxt_bin_arbiter_rd_mosi.address <= bin_reader_mosi.address;
-
-  p_bin_arbiter_mosi : PROCESS(dp_clk, dp_rst) IS --, nxt_bin_arbiter_wr_mosi, nxt_bin_arbiter_rd_mosi
+  -------------------------------------------------------------------------------
+  -- bin_arbiter : Take care of simultaneous rd/wr to the same RAM address
+  -- . Input: bin_reader_mosi (wants to read bins)
+  --          bin_writer_mosi (wants to write to bins)
+  --          bin_arbiter_rd_miso (carries the bins requested by bin_reader)
+  -- . Output: bin_arbiter_wr_mosi (wr requests to RAM)
+  --           bin_arbiter_rd_mosi (rd requests to RAM)
+  --           bin_reader_miso (carries the bins requested by bin_reader)
+  -------------------------------------------------------------------------------
+  -- Really simple arbitration: always allow writes, only allow reads when possible (rd_addr != wr_addr).
+  read_allowed <= FALSE WHEN bin_writer_mosi.wr='1' AND bin_writer_mosi.address=bin_reader_mosi.address ELSE TRUE;
+  -- save previous read_allowed
+  p_prv_read_allowed: PROCESS(dp_rst, dp_clk) IS
   BEGIN
-    IF dp_rst = '1' THEN
-      bin_arbiter_wr_mosi <= c_mem_mosi_rst;
-      bin_arbiter_rd_mosi <= c_mem_mosi_rst;
+    IF dp_rst='1' THEN
+      prv_read_allowed <= FALSE;
     ELSIF RISING_EDGE(dp_clk) THEN
-      bin_arbiter_wr_mosi <= nxt_bin_arbiter_wr_mosi;
-      bin_arbiter_rd_mosi <= nxt_bin_arbiter_rd_mosi;
+      prv_read_allowed <= read_allowed;
     END IF;
   END PROCESS;
-  
---  -- Temporary debug data
---  sla_out_ram_miso.rddata <= bin_arbiter_wr_mosi.wrdata;
-  
-  -- Make RAM data available for the bin_reader (or bin_writer)
-  bin_arbiter_rd_miso <= common_ram_r_w_miso;
-  
-  
-  -----------------------------------------------------------------------------
-  -- RAM selector & Dual swapped RAM instances:
-  --  4 cycles after a sync the RAM block is swapped for an empty one to allow
-  --  the block to be read out till the next sync+3 cycles
-  --  The input is the st side, the output is the dp clocked mm side.
-  --
-  -- Depending on ram_pointer:
-  -- ram_pointer = '0': input RAM_0, output RAM_1
-  -- ram_pointer = '1': input RAM_1, output RAM_0
-  --
-  -- input in:  snk_in_pppp.sync      (latency: 4)
-  --            bin_arbiter_wr_mosi   (latency: 4)
-  --            bin_arbiter_rd_mosi   (latency: 1)
-  --       out: common_ram_r_w_miso   (latency: 2)
-  --
-  -- output in:  ram_out_wr_en; ram_out_wr_dat; ram_out_wr_adr; ram_out_rd_adr;
-  --             ram_out_rd_en
-  --        out: ram_out_rd_dat; ram_out_rd_val
-  -----------------------------------------------------------------------------
-  p_ram_pointer_at_sync : PROCESS(snk_in_pppp) IS -- needs nxt_ram_pointer ??
+
+  -- Forward MOSI buses
+  -- . RD MOSI
+  bin_arbiter_rd_mosi.wr      <= '0';
+  bin_arbiter_rd_mosi.rd      <= bin_reader_mosi.rd WHEN read_allowed ELSE '0';
+  bin_arbiter_rd_mosi.address <= bin_reader_mosi.address;
+  -- . WR MOSI
+  bin_arbiter_wr_mosi.rd      <= '0';
+  bin_arbiter_wr_mosi.wr      <= bin_writer_mosi.wr;
+  bin_arbiter_wr_mosi.wrdata  <= bin_writer_mosi.wrdata;
+  bin_arbiter_wr_mosi.address <= bin_writer_mosi.address;
+
+  -- Loop back the WR data to the RD side when read was not allowed or on second read of same address
+  p_bin_reader_miso : PROCESS(prv_read_allowed, bin_reader_mosi, bin_reader_miso, bin_writer_mosi, read_allowed, bin_arbiter_rd_miso) IS
   BEGIN
-    IF snk_in_pppp.sync = '1' THEN                                             --needs snk_in_pppp                                                      <--
-      ram_pointer <= NOT(ram_pointer);
+    bin_reader_miso <= bin_arbiter_rd_miso;
+    IF prv_bin_reader_mosi.rd = '1' AND prv_read_allowed = FALSE THEN -- Fake succesful readback when read was not allowed
+      bin_reader_miso.rdval  <= '1';
+      bin_reader_miso.rddata <= bin_writer_mosi.wrdata;
+    ELSIF read_allowed = TRUE THEN
+      bin_reader_miso <= bin_arbiter_rd_miso;
+    ELSIF (prv_bin_reader_mosi.rd = '1' AND bin_reader_mosi.rd='1') AND (prv_bin_reader_mosi.address=bin_reader_mosi.address) THEN -- 2 reads on same address in row: 2nd read is outdated so return wrdata here
+      bin_reader_miso.rdval  <= '1';
+      bin_reader_miso.rddata <= bin_writer_mosi.wrdata;
     END IF;
   END PROCESS;
-  
-  p_ram_pointer : PROCESS(ram_pointer, bin_arbiter_wr_mosi, bin_arbiter_rd_mosi, ram_0_rd_dat, ram_0_rd_val, 
-                          ram_out_wr_en, ram_out_wr_dat, ram_out_wr_adr, ram_out_rd_adr, ram_out_rd_en, ram_1_rd_dat, ram_1_rd_val) IS
-  BEGIN
-    IF ram_pointer='0' THEN
-    
-      -- ST side (RAM 0)
-      ram_0_wr_en  <= bin_arbiter_wr_mosi.wr;                            -- bin_arbiter_wr_mosi.wr        wr_en
-      ram_0_wr_dat <= bin_arbiter_wr_mosi.wrdata(c_word_w-1 DOWNTO 0);   -- bin_arbiter_wr_mosi.wrdata    wr_dat
-      ram_0_wr_adr <= bin_arbiter_wr_mosi.address(c_adr_w-1 DOWNTO 0);   -- bin_arbiter_wr_mosi.address   wr_adr
-      ram_0_rd_adr <= bin_arbiter_rd_mosi.address(c_adr_w-1 DOWNTO 0);   -- bin_arbiter_rd_mosi.address   rd_adr
-      ram_0_rd_en  <= bin_arbiter_rd_mosi.rd;                            -- bin_arbiter_rd_mosi.rd        rd_en
-      common_ram_r_w_miso.rddata(c_word_w-1 DOWNTO 0) <= ram_0_rd_dat;   -- common_ram_r_w_miso.rddata  rd_dat
-      common_ram_r_w_miso.rdval  <= ram_0_rd_val;                        -- common_ram_r_w_miso.rdval   rd_val
-      
-      
-      -- dp_clk'd  MM side (RAM 1)
-      ram_1_wr_en <= ram_out_wr_en;
-      ram_1_wr_dat <= ram_out_wr_dat;
-      ram_1_wr_adr <= ram_out_wr_adr;
-      ram_1_rd_adr <= ram_out_rd_adr;
-      ram_1_rd_en <= ram_out_rd_en;
-      ram_out_rd_dat <= ram_1_rd_dat;
-      ram_out_rd_val <= ram_1_rd_val;
-      
-      
-    ELSE -- ram_pointer='1'
-    
-      -- ST side (RAM 1)
-      ram_1_wr_en  <= bin_arbiter_wr_mosi.wr;      
-      ram_1_wr_dat <= bin_arbiter_wr_mosi.wrdata(c_word_w-1 DOWNTO 0);  
-      ram_1_wr_adr <= bin_arbiter_wr_mosi.address(c_adr_w-1 DOWNTO 0); 
-      ram_1_rd_adr <= bin_arbiter_rd_mosi.address(c_adr_w-1 DOWNTO 0); 
-      ram_1_rd_en  <= bin_arbiter_rd_mosi.rd;      
-      common_ram_r_w_miso.rddata(c_word_w-1 DOWNTO 0) <= ram_1_rd_dat;
-      common_ram_r_w_miso.rdval  <= ram_1_rd_val;
-      
-      --dp_clk'd  MM side (RAM 0)
-      ram_0_wr_en <= ram_out_wr_en;
-      ram_0_wr_dat <= ram_out_wr_dat;
-      ram_0_wr_adr <= ram_out_wr_adr;
-      ram_0_rd_adr <= ram_out_rd_adr;
-      ram_0_rd_en <= ram_out_rd_en;
-      ram_out_rd_dat <= ram_0_rd_dat;
-      ram_out_rd_val <= ram_0_rd_val;
 
-    END IF;
-  END PROCESS;
-  
-  
-  -- Dual swapped RAM instances
-  ram_0: ENTITY common_lib.common_ram_r_w
-  GENERIC MAP (
-    g_technology     => c_tech_select_default,
-    g_ram            => c_ram,
-    g_init_file      => "UNUSED"
-  )
-  PORT MAP (
-    rst      => dp_rst, 
-    clk      => dp_clk,
-    clken    => '1',            -- only necessary for Stratix iv
-    wr_en    => ram_0_wr_en,
-    wr_adr   => ram_0_wr_adr,
-    wr_dat   => ram_0_wr_dat,
-    rd_en    => ram_0_rd_en,
-    rd_adr   => ram_0_rd_adr,
-    rd_dat   => ram_0_rd_dat,
-    rd_val   => ram_0_rd_val
-  );
-  
-  ram_1: ENTITY common_lib.common_ram_r_w
-  GENERIC MAP (
-    g_technology     => c_tech_select_default,
-    g_ram            => c_ram,
-    g_init_file      => "UNUSED"
-  )
-  PORT MAP (
-    rst      => dp_rst, 
-    clk      => dp_clk,
-    clken    => '1',            -- only necessary for Stratix iv
-    wr_en    => ram_1_wr_en,
-    wr_adr   => ram_1_wr_adr,
-    wr_dat   => ram_1_wr_dat,
-    rd_en    => ram_1_rd_en,
-    rd_adr   => ram_1_rd_adr,
-    rd_dat   => ram_1_rd_dat,
-    rd_val   => ram_1_rd_val
-  );
-  
-  
-  
-  -----------------------------------------------------------------------------
-  -- Connect interface to DUAL swapped RAM, read out histogram statistics:
-  -- . Limit the data read by the MM master to the RAM block where it started
-  --   to read (the values read after a new sync will be OTHERS => '0')
-  -- . In the last g_nof_bins cycles all addresses will sequentially be cleared
-  --
-  -- RAM selector:
-  -- input: ram_out_rd_dat; ram_out_rd_val
-  -- output: ram_out_wr_en; ram_out_wr_dat; ram_out_wr_adr; ram_out_rd_adr;
-  --         ram_out_wr_en 
-  -- (PORT):
-  -- input: snk_in; sla_in_ram_mosi
-  -- output: sla_out_ram_miso
-  -----------------------------------------------------------------------------
-  
-  -- Pipeline for identified illegal read requests after new sync
-  u_common_pipeline_sl_mm_adr_illegal : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => mm_adr_illegal,
-    out_dat => mm_adr_illegal_pp
-  );
-  
-  p_mm_adr_illegal : PROCESS(snk_in.sync, mm_adr_cnt) IS
+
+  -------------------------------------------------------------------------------
+  -- Two RAM (common_ram_r_w) instances. The user can read the histogram from the 
+  -- instance that is not being written to by the bin_arbiter.
+  -- . Input:  bin_arbiter_wr_mosi (writes bins)
+  --           bin_arbiter_rd_mosi (requests to read bins to increment bin count)
+  --           histogram_rd_mosi (requests to read the bins on the user side)
+  --           histogram_wr_mosi (on user side, auto clears RAM every sync)
+  -- . Output: histogram_rd_miso (carries the bins the user wants to read)
+  --           bin_arbiter_miso (carries then bins the bin_reader wants to read)
+  -- . Note: the ram_pointer is carried (with different latencies) as MSbit in:
+  --         . bin_arbiter_wr_mosi.address
+  --         . bin_arbiter_rd_mosi.address 
+  -------------------------------------------------------------------------------
+  bin_arbiter_wr_ram_pointer <= bin_arbiter_wr_mosi.address(c_ram_adr_w);
+  bin_arbiter_rd_ram_pointer <= bin_arbiter_rd_mosi.address(c_ram_adr_w);  
+
+  -- Store the previous RAM pointer of the read bus
+  p_prv_ram_pointer : PROCESS(dp_clk, dp_rst) IS
   BEGIN
-    IF snk_in.sync = '1' AND mm_adr_cnt /= 0 THEN
-      mm_adr_illegal <= '1';
-    ELSIF mm_adr_cnt = g_nof_bins-1 THEN
-      mm_adr_illegal <= '0';
-    ELSE
+    IF dp_rst = '1' THEN
+      prv_bin_arbiter_rd_ram_pointer <= '0';
+    ELSIF RISING_EDGE(dp_clk) THEN
+      prv_bin_arbiter_rd_ram_pointer <= bin_arbiter_rd_ram_pointer;
     END IF;
   END PROCESS;
-  
-  mm_adr_cnt <= TO_UINT(sla_in_ram_mosi.address(c_ram.adr_w-1 DOWNTO 0)) WHEN sla_in_ram_mosi.rd = '1';
-  ram_out_same_w_r_adr <= '1' WHEN ram_out_wr_adr = sla_in_ram_mosi.address(c_ram.adr_w-1 DOWNTO 0) ELSE '0';
-  
-  p_ram_to_fifo : PROCESS(snk_in_pp.sync, cycle_cnt, sla_in_ram_mosi.address, sla_in_ram_mosi.rd, ram_out_rd_dat, ram_out_rd_val, prev_ram_out_wr_adr, mm_adr_illegal_pp, ram_out_same_w_r_adr, bin_arbiter_wr_mosi.wrdata) IS
+
+  -- Let bin_arbiter write RAM 0 while user reads RAM 1 and vice versa
+  common_ram_r_w_wr_mosi_arr(0) <= bin_arbiter_wr_mosi WHEN bin_arbiter_wr_ram_pointer='0' ELSE histogram_wr_mosi;
+  common_ram_r_w_rd_mosi_arr(0) <= bin_arbiter_rd_mosi WHEN bin_arbiter_rd_ram_pointer='0' ELSE histogram_rd_mosi;
+  common_ram_r_w_wr_mosi_arr(1) <= bin_arbiter_wr_mosi WHEN bin_arbiter_wr_ram_pointer='1' ELSE histogram_wr_mosi; 
+  common_ram_r_w_rd_mosi_arr(1) <= bin_arbiter_rd_mosi WHEN bin_arbiter_rd_ram_pointer='1' ELSE histogram_rd_mosi;
+  
+  -- Let bin_arbiter read RAM 0 while user reads RAM 1 and vice versa
+  -- . We always want the MISO bus to switch 1 cycle later than the MOSI (such that the MM operation can finish); hence using prv_bin_arbiter_rd_ram_pointer.
+  bin_arbiter_rd_miso  <= common_ram_r_w_rd_miso_arr(0) WHEN prv_bin_arbiter_rd_ram_pointer='0' ELSE common_ram_r_w_rd_miso_arr(1);
+  histogram_rd_miso    <= common_ram_r_w_rd_miso_arr(1) WHEN prv_bin_arbiter_rd_ram_pointer='0' ELSE common_ram_r_w_rd_miso_arr(0);
+
+  gen_common_ram_r_w : FOR i IN 0 TO c_nof_ram_pages-1 GENERATE
+    u_common_ram_r_w : ENTITY common_lib.common_ram_r_w
+    GENERIC MAP (
+      g_technology     => c_tech_select_default,
+      g_ram            => c_ram,
+      g_init_file      => "UNUSED"
+    )
+    PORT MAP (
+      rst      => dp_rst, 
+      clk      => dp_clk,
+      clken    => '1',
+      wr_en    => common_ram_r_w_wr_mosi_arr(i).wr,
+      wr_adr   => common_ram_r_w_wr_mosi_arr(i).address(c_ram_adr_w-1 DOWNTO 0),
+      wr_dat   => common_ram_r_w_wr_mosi_arr(i).wrdata(c_ram_dat_w-1 DOWNTO 0),
+      rd_en    => common_ram_r_w_rd_mosi_arr(i).rd,
+      rd_adr   => common_ram_r_w_rd_mosi_arr(i).address(c_ram_adr_w-1 DOWNTO 0),
+      rd_dat   => common_ram_r_w_rd_miso_arr(i).rddata(c_ram_dat_w-1 DOWNTO 0),
+      rd_val   => common_ram_r_w_rd_miso_arr(i).rdval
+    );
+  END GENERATE;
+
+
+  -------------------------------------------------------------------------------
+  -- Clear the RAM just before the next sync interval
+  -------------------------------------------------------------------------------
+  -- Count input data for automatic RAM clear before next sync interval
+  nxt_data_cnt <= (OTHERS=>'0') WHEN TO_UINT(data_cnt)=g_nof_data_per_sync-1 ELSE INCR_UVEC(data_cnt, 1) WHEN snk_in.valid='1' ELSE data_cnt;
+
+  -- Clear all g_nof_bins RAM addresses just before the next sync
+  ram_clear <= '1' WHEN TO_UINT(data_cnt)=g_nof_data_per_sync-g_nof_bins-1 ELSE '0';
+
+  -- Signal to indicate when RAM is being cleared
+  nxt_ram_clearing <= '1' WHEN ram_clear='1' ELSE '0' WHEN TO_UINT(ram_clear_address)=g_nof_bins-1 ELSE i_ram_clearing;
+
+  -- Address counter: 0 to g_nof_bins-1.
+  nxt_ram_clear_address <= INCR_UVEC(ram_clear_address, 1) WHEN i_ram_clearing='1' ELSE (OTHERS=>'0');
+
+  histogram_wr_mosi.wr                              <= i_ram_clearing;
+  histogram_wr_mosi.address(c_ram_adr_w-1 DOWNTO 0) <= ram_clear_address;
+  histogram_wr_mosi.wrdata                          <= (OTHERS=>'0');
+  histogram_wr_mosi.rd                              <= '0';
+
+  -- Registers
+  p_ram_clearing : PROCESS(dp_clk, dp_rst) IS
   BEGIN
-    IF g_ram_miso_sim_mode = FALSE THEN
-      IF snk_in_pppp.sync = '1' THEN
-        ram_out_wr_en <= '0';
-        nxt_cycle_cnt <= 0;
-      ELSIF cycle_cnt = c_clear THEN
-        ram_out_wr_adr <= (OTHERS => '0');
-        ram_out_wr_dat <= (OTHERS => '0');
-        ram_out_wr_en <= '1';
-        IF ram_out_same_w_r_adr = '1' THEN
-          ram_out_rd_en                           <= '0';
-          sla_out_ram_miso.rddata(c_ram.dat_w-1 DOWNTO 0) <= (OTHERS => '0');
-          sla_out_ram_miso.rdval                          <= ram_out_rd_val;
-        ELSE
-          ram_out_rd_adr                          <= sla_in_ram_mosi.address(c_ram.adr_w-1 DOWNTO 0);
-          ram_out_rd_en                           <= sla_in_ram_mosi.rd;
-          sla_out_ram_miso.rddata(c_ram.dat_w-1 DOWNTO 0) <= ram_out_rd_dat;
-          sla_out_ram_miso.rdval                          <= ram_out_rd_val;
-        END IF;
-        nxt_cycle_cnt <= cycle_cnt +1;
-      ELSIF cycle_cnt > c_clear THEN
-        ram_out_wr_adr <= INCR_UVEC(prev_ram_out_wr_adr, 1);
-        ram_out_wr_dat <= (OTHERS => '0');
-        nxt_cycle_cnt <= cycle_cnt +1;
-        IF ram_out_same_w_r_adr = '1' OR snk_in.sync = '1' THEN
-          sla_out_ram_miso.rddata(c_ram.dat_w-1 DOWNTO 0) <= (OTHERS => '0');
-          sla_out_ram_miso.rdval                          <= ram_out_rd_val;
-        ELSE
-          ram_out_rd_adr                          <= sla_in_ram_mosi.address(c_ram.adr_w-1 DOWNTO 0);
-          ram_out_rd_en                           <= sla_in_ram_mosi.rd;
-          sla_out_ram_miso.rddata(c_ram.dat_w-1 DOWNTO 0) <= ram_out_rd_dat;
-          sla_out_ram_miso.rdval                          <= ram_out_rd_val;
-        END IF;
-        ram_out_wr_en <= '1';
-      ELSIF mm_adr_illegal_pp = '1' THEN
-        ram_out_rd_adr                          <= sla_in_ram_mosi.address(c_ram.adr_w-1 DOWNTO 0);
-        ram_out_rd_en                           <= sla_in_ram_mosi.rd;
-        sla_out_ram_miso.rddata(c_ram.dat_w-1 DOWNTO 0) <= (OTHERS => '0');
-        sla_out_ram_miso.rdval                          <= ram_out_rd_val;
-        nxt_cycle_cnt                           <= cycle_cnt +1;
-        ram_out_wr_en                           <= '0';
-      ELSE
-        ram_out_rd_adr                          <= sla_in_ram_mosi.address(c_ram.adr_w-1 DOWNTO 0);
-        ram_out_rd_en                           <= sla_in_ram_mosi.rd;
-        sla_out_ram_miso.rddata(c_ram.dat_w-1 DOWNTO 0) <= ram_out_rd_dat;
-        sla_out_ram_miso.rdval                          <= ram_out_rd_val;
-        nxt_cycle_cnt                           <= cycle_cnt +1;
-        ram_out_wr_en                           <= '0';
-      END IF;
-      dbg_ram_miso.rddata     <= bin_arbiter_wr_mosi.wrdata;
-    ELSE
-      sla_out_ram_miso.rddata <= bin_arbiter_wr_mosi.wrdata;
+    IF dp_rst = '1' THEN
+      ram_clear_address <= (OTHERS=>'0');
+      i_ram_clearing    <= '0';
+      data_cnt          <= (OTHERS=>'0');
+    ELSIF RISING_EDGE(dp_clk) THEN
+      ram_clear_address <= nxt_ram_clear_address;
+      i_ram_clearing    <= nxt_ram_clearing;
+      data_cnt          <= nxt_data_cnt;
     END IF;
   END PROCESS;
-  
-  
-  p_clk : PROCESS(dp_clk, dp_rst)
-  BEGIN
-  IF dp_rst='1' THEN
-    cycle_cnt <= 0;
-  ELSIF rising_edge(dp_clk) THEN
-    cycle_cnt <= nxt_cycle_cnt;
-    prev_ram_out_wr_adr <= ram_out_wr_adr;
-  END IF; 
-  END PROCESS;    
-      
+
+  ram_clearing <= i_ram_clearing;
+
+  -------------------------------------------------------------------------------
+  -- Expose the MM buses to the user
+  -------------------------------------------------------------------------------
+  ram_miso <= histogram_rd_miso;
+  histogram_rd_mosi <= ram_mosi;
 
 END rtl;
diff --git a/libraries/dsp/st/src/vhdl/st_histogram_8_april.vhd b/libraries/dsp/st/src/vhdl/st_histogram_8_april.vhd
deleted file mode 100644
index ed7f5e442446030567452187cff9bf95bc72c0bc..0000000000000000000000000000000000000000
--- a/libraries/dsp/st/src/vhdl/st_histogram_8_april.vhd
+++ /dev/null
@@ -1,413 +0,0 @@
-
--- Daniel's suggested restructured st_hitogram.vhd.
-
-LIBRARY IEEE, common_lib, mm_lib, technology_lib, dp_lib;
-USE IEEE.std_logic_1164.ALL;
-USE common_lib.common_pkg.ALL;
-USE common_lib.common_mem_pkg.ALL;
-USE dp_lib.dp_stream_pkg.ALL;
-USE technology_lib.technology_select_pkg.ALL;
-
-ENTITY st_histogram_8_april IS
-  GENERIC (
-    g_in_data_w         : NATURAL := 14;   -- >= 9 when g_nof_bins is 512; (max. c_dp_stream_data_w =768)         <-- maybe just g_data_w ??
-    g_nof_bins          : NATURAL := 512;  -- is a power of 2 and g_nof_bins <= c_data_span; max. 512
-    g_nof_data          : NATURAL         
---    g_sim_ram_miso_mode : BOOLEAN := FALSE -- when TRUE the ram_miso bus will get a copy of the data written into the RAM.
-  );                
-  PORT (            
-    dp_rst   : IN  STD_LOGIC;
-    dp_clk   : IN  STD_LOGIC;
-                    
-    -- Streaming    
-    snk_in   : IN  t_dp_sosi;
-    
-    -- DP clocked memory bus
-    ram_mosi : IN  t_mem_mosi;
-    ram_miso : OUT t_mem_miso 
-  );
-END st_histogram_8_april;
-
-
-ARCHITECTURE rtl OF st_histogram_8_april IS
-
-  CONSTANT c_adr_w : NATURAL := ceil_log2(g_nof_bins);
-  CONSTANT c_ram   : t_c_mem := (latency  => 1,
-                                 adr_w    => c_adr_w,          -- 9 bits needed to adress/select 512 adresses
-                                 dat_w    => c_word_w,         -- 32bit, def. in common_pkg; >= c_bin_w
-                                 nof_dat  => g_nof_bins,       -- 512 adresses with 32 bit words, so 512
-                                 init_sl  => '0');             -- MM side : sla_in, sla_out
-                                 
---  CONSTANT c_mem_miso_setting     : t_mem_miso := (rddata => mem_miso_init,  -- c_mem_miso_rst; -- limit to 32 bit 
---                                                   rdval => '0',
---                                                   waitrequest => '0' );
-
-  CONSTANT c_adr_low_calc : INTEGER  := g_in_data_w-c_adr_w;          -- Calculation might yield a negative number
-  CONSTANT c_adr_low      : NATURAL  := largest(0, c_adr_low_calc);   -- Override any negative value of c_adr_low_calc
-  
---  SIGNAL mem_miso_init    : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := (OTHERS => '0');
-
-  SIGNAL bin_reader_mosi          : t_mem_mosi := c_mem_mosi_rst;
-
-  SIGNAL nxt_bin_writer_mosi      : t_mem_mosi;
-  SIGNAL bin_writer_mosi          : t_mem_mosi;
-
-  SIGNAL nxt_bin_arbiter_wr_mosi  : t_mem_mosi;
-  SIGNAL bin_arbiter_wr_mosi      : t_mem_mosi;
-
-  SIGNAL nxt_bin_arbiter_rd_mosi  : t_mem_mosi;
-  SIGNAL bin_arbiter_rd_mosi      : t_mem_mosi;
-
-  SIGNAL bin_arbiter_rd_miso      : t_mem_miso := c_mem_miso_rst;
-  SIGNAL bin_reader_rd_miso       : t_mem_miso := c_mem_miso_rst;
-  SIGNAL common_ram_r_w_0_miso    : t_mem_miso := c_mem_miso_rst;
-  
-  SIGNAL init_phase           : STD_LOGIC := '1';
-  SIGNAL nxt_init_phase       : STD_LOGIC;
-  SIGNAL rd_cnt_allowed       : STD_LOGIC := '0';
-  SIGNAL rd_cnt_allowed_pp    : STD_LOGIC := '0';
-  SIGNAL toggle_detect        : STD_LOGIC := '0';
-  SIGNAL toggle_detect_pp     : STD_LOGIC;
-  SIGNAL toggle_detect_false  : STD_LOGIC := '1';
-  SIGNAL nxt_prev_wrdata      : NATURAL;
-  SIGNAL prev_wrdata          : NATURAL;
-  SIGNAL prev_prev_wrdata     : NATURAL;
-  SIGNAL prev_prev_prev_wrdata: NATURAL;
-  SIGNAL sync_detect          : STD_LOGIC := '0';
-  SIGNAL sync_detect_pp       : STD_LOGIC;
-  SIGNAL same_r_w_address     : STD_LOGIC;
-  SIGNAL same_r_w_address_pp  : STD_LOGIC;
-  
-  --pipelined signals
-  SIGNAL snk_in_p    : t_dp_sosi;
-  SIGNAL snk_in_pp   : t_dp_sosi;
-  SIGNAL prev_bin_reader_mosi     : t_mem_mosi := c_mem_mosi_rst ;
-  SIGNAL bin_reader_mosi_pp       : t_mem_mosi := c_mem_mosi_rst;
-  SIGNAL bin_reader_mosi_ppp      : t_mem_mosi := c_mem_mosi_rst;
-  
-  --debug signals
---  SIGNAL nxt_dbg_sync_detect : STD_LOGIC;
---  SIGNAL dbg_sync_detect     : STD_LOGIC;
-  SIGNAL dbg_state_string    : STRING(1 TO 3) := "   ";
-  SIGNAL dbg_snk_data        : STD_LOGIC_VECTOR(g_in_data_w-1 DOWNTO 0);
-
-  
-BEGIN 
-
-  -----------------------------------------------------------------------------
-  -- Bin reader: Convert snk_in data to bin_reader_mosi with read request 
-  --             and generate signals for detection of problems in the 
-  --             consecutive data.
-  -- . in  : snk_in               (latency: 0)
-  --       : bin_arbiter_rd_miso  (latency: 2)
-  -- . out : init_phase           (latency: 0 ?
-  --       : bin_reader_mosi      (latency: 0)
-  --       : prev_bin_reader_mosi (latency: 1)
-  --       : bin_reader_mosi_pp   (latency: 2)
-  --       : bin_reader_mosi_ppp  (latency: 3)
-  --       : bin_reader_rd_miso   (latency: 2)
-  --       : rd_cnt_allowed_pp    (latency: 2)
-  --       : same_r_w_address_pp  (latency: 2)
-  --       : toggle_detect_pp     (latency: 2)
-  --       : sync_detect          (latency: 0)
-  --       : sync_detect_pp       (latency: 2)
-  -----------------------------------------------------------------------------
-  bin_reader_mosi.rd                          <= snk_in.valid; -- when 1, count allowed
-  bin_reader_mosi.address(c_adr_w-1 DOWNTO 0) <= snk_in.data(g_in_data_w-1 DOWNTO c_adr_low); 
-  bin_reader_rd_miso                          <= bin_arbiter_rd_miso;
-  
-  --snk_in pipeline; Enable sync and valid comparisons
-  u_dp_pipeline_snk_in_1_cycle : ENTITY dp_lib.dp_pipeline
-  GENERIC MAP (
-    g_pipeline   => 1  -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    rst          => dp_rst,
-    clk          => dp_clk,
-    snk_in       => snk_in,
-    src_out      => snk_in_p
-  );
-  
-  init_phase <= '0' WHEN snk_in_p.sync = '1'; -- ELSE will be impossible since the init_phase may only be triggered once on the first sync
---  nxt_init_phase <= '0' WHEN snk_in_p_.sync='1' ELSE init_phase;
-  
---  p_init_phase : PROCESS(dp_clk, dp_rst)
---  BEGIN
---    IF dp_rst = '1' THEN
---      init_phase <= '1';
---    ELSIF RISING_EDGE(dp_clk) THEN
---      init_phase <= nxt_init_phase;
---    END IF;
---  END PROCESS;
-  
-  -- Enable sync comparisons
-  u_dp_pipeline_snk_in_2_cycle : ENTITY dp_lib.dp_pipeline
-  GENERIC MAP (
-    g_pipeline   => 2  -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    rst          => dp_rst,
-    clk          => dp_clk,
-    snk_in       => snk_in,
-    src_out      => snk_in_pp
-  );
-  
-  dbg_snk_data <= snk_in_pp.data(g_in_data_w-1 DOWNTO 0);
-  
-  toggle_detect_false <= '0' WHEN snk_in_pp.sync = '1'; -- ELSE will be impossible since the toggle_detect_false may only be triggered once on the first sync
-  sync_detect <= snk_in.valid WHEN (snk_in.sync='1' OR snk_in_p.sync='1' OR snk_in_pp.sync='1') ELSE '0'; -- @sync, first 3 cycles would try to read from the wrong (old) RAM block, detect this problem
-  
-  -- Line up to p_nxt_bin_writer_mosi process  
-  u_common_pipeline_sl_sync_detect_2_cycle : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => sync_detect,
-    out_dat => sync_detect_pp
-  );
-  
-  -- Enable adress comparisons 1 cycle back  
-  -- Skip unvalid data with trigger bin_reader_mosi.rd to make comparisons between unvalid-data-seperated data possible.
-  u_common_pipeline_bin_reader_mosi_1_cycle : ENTITY common_lib.common_pipeline
-  GENERIC MAP (
-    g_representation => "UNSIGNED", --orig. signed
-    g_pipeline       => 1,
-    g_in_dat_w       => c_adr_w, -- c_mem_address_w
-    g_out_dat_w      => c_adr_w
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    clken   => bin_reader_mosi.rd, -- '1',
-    in_dat  => STD_LOGIC_VECTOR(bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)),
-    out_dat => prev_bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)
-  );
-  
-  -- Enable adress comparisons 2 cycles back
-  u_common_pipeline_bin_reader_mosi_2_cycle : ENTITY common_lib.common_pipeline
-  GENERIC MAP (
-    g_representation => "UNSIGNED", --orig. signed
-    g_pipeline       => 1,
-    g_in_dat_w       => c_adr_w,
-    g_out_dat_w      => c_adr_w
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => STD_LOGIC_VECTOR(prev_bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)),
-    out_dat => bin_reader_mosi_pp.address(c_adr_w-1 DOWNTO 0)
-  );
-  
-  -- Enable adress comparisons 3 cycles back
-  u_common_pipeline_bin_reader_mosi_3_cycle : ENTITY common_lib.common_pipeline
-  GENERIC MAP (
-    g_representation => "UNSIGNED", --orig. signed
-    g_pipeline       => 2,
-    g_in_dat_w       => c_adr_w,
-    g_out_dat_w      => c_adr_w
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => STD_LOGIC_VECTOR(prev_bin_reader_mosi.address(c_adr_w-1 DOWNTO 0)),
-    out_dat => bin_reader_mosi_ppp.address(c_adr_w-1 DOWNTO 0)
-  );
-  
-  
-  -- Only count sequential valid data on the same address when: address is the same as last and 1 or 2 cycles after the sync when in sync_detect; address is the same as last and past the initialisation and outside sync_detect
-  rd_cnt_allowed <= snk_in.valid WHEN ( bin_reader_mosi.address = prev_bin_reader_mosi.address AND ( snk_in_p.sync='1' OR (snk_in_pp.sync='1' AND snk_in_p.valid='1') ) )
-                                 OR (bin_reader_mosi.address = prev_bin_reader_mosi.address AND init_phase='0' AND sync_detect='0')
-                                 ELSE '0';
-  
-  -- Line rd_cnt_allowed up to p_nxt_bin_writer_mosi process
-  u_common_pipeline_sl_rd_cnt_allowed : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => rd_cnt_allowed,
-    out_dat => rd_cnt_allowed_pp
-  );
-  
-  -- Detect a (valid) repeating address seperated by one other address past the initialisation and outside the first two cycles of a (new) sync                                        --also @sync, one wil be true; use  NOT(1 or 1) instead of (0 or 0)
-  toggle_detect  <= snk_in.valid WHEN (bin_reader_mosi_pp.address = bin_reader_mosi.address AND bin_reader_mosi_pp.address /= prev_bin_reader_mosi.address AND toggle_detect_false = '0' AND NOT(snk_in.sync='1' OR snk_in_p.sync='1') ) 
-                                 ELSE '0';
-
-  
-  -- Line up to p_nxt_bin_writer_mosi process
-  u_common_pipeline_sl_toggle_detect : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => toggle_detect,
-    out_dat => toggle_detect_pp
-  );
-  
-  -- Detect an (valid) address that has to be read as well as written at the same time
-  same_r_w_address <= snk_in.valid WHEN (bin_reader_mosi.address = bin_reader_mosi_ppp.address AND init_phase = '0' AND sync_detect = '0') ELSE '0';
-  
-  -- Line up top p_nxt_bin_writer_mosi process
-  u_common_pipeline_sl_same_r_w_address : ENTITY common_lib.common_pipeline_sl
-  GENERIC MAP(
-    g_pipeline       => 2 -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    clk     => dp_clk,
-    in_dat  => same_r_w_address,
-    out_dat => same_r_w_address_pp
-  );
-
-
-  -----------------------------------------------------------------------------
-  -- Bin writer : increments current bin value and sets up write request
-  -- . in  : toggle_detect_pp      (latency: 2)
-  -- . in  : same_r_w_address_pp   (latency: 2)
-  -- . in  : bin_reader_mosi_pp    (latency: 2)
-  -- . in  : bin_reader_rd_miso    (latency: 2)  aka bin_arbiter_rd_miso or common_ram_r_w_0_miso
-  -- . in  : rd_cnt_allowed_pp     (latency: 2)
-  -- . in  : sync_detect_pp
-  -- . out : bin_writer_mosi  (latency: 3)
-  -----------------------------------------------------------------------------
-  p_nxt_bin_writer_mosi : PROCESS(bin_reader_rd_miso, 
-                                  bin_reader_mosi_pp.address, toggle_detect_pp, rd_cnt_allowed_pp, init_phase, prev_wrdata, prev_prev_wrdata, prev_prev_prev_wrdata, sync_detect_pp, same_r_w_address_pp) IS -- init_phase unnecesary? ; removed: common_ram_r_w_0_miso.rdval, common_ram_r_w_0_miso.rddata,
-  BEGIN
-    nxt_bin_writer_mosi <= c_mem_mosi_rst;
-    dbg_state_string <= "unv";
-    IF bin_reader_rd_miso.rdval='1' THEN  --  common_ram_r_w_0_miso
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= INCR_UVEC(bin_reader_rd_miso.rddata, 1); -- common_ram_r_w_0_miso
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= TO_UINT(bin_reader_rd_miso.rddata) + 1;  -- common_ram_r_w_0_miso
-      dbg_state_string <= "val";
-
-    ELSIF toggle_detect_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_prev_wrdata+1), c_mem_data_w);
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= prev_prev_wrdata+1;
-      dbg_state_string <= "td ";
-      
-    ELSIF rd_cnt_allowed_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_wrdata + 1), c_mem_data_w);
-      nxt_prev_wrdata             <= prev_wrdata + 1;
-      dbg_state_string <= "r# ";
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      
-    ELSIF sync_detect_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC(1, c_mem_data_w); -- snk_in.sync: 1; snk_in_p.sync (thus new adress): 1; snk_in_pp.sync (thus new adress): 1
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= 1;
-      dbg_state_string  <= "sd ";
-      
-    ELSIF same_r_w_address_pp = '1' THEN
-      nxt_bin_writer_mosi.wr      <= '1';
-      nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_prev_prev_wrdata+1), c_mem_data_w);
-      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
-      nxt_prev_wrdata             <= prev_prev_prev_wrdata + 1;
-      dbg_state_string  <= "srw";
-    END IF;
-  END PROCESS; 
-  
-  p_prev_wrdata : PROCESS(dp_clk, dp_rst, nxt_bin_writer_mosi.wr) IS  --seperated from p_bin_writer_mosi since the implementation was unwanted
-  BEGIN
-    IF dp_rst = '1' THEN
-      prev_wrdata           <= 0;
-      prev_prev_wrdata      <= 0;
-      prev_prev_prev_wrdata <= 0;
-    ELSIF nxt_bin_writer_mosi.wr='1' AND RISING_EDGE(dp_clk) THEN
-      prev_wrdata           <= nxt_prev_wrdata;
-      prev_prev_wrdata      <= prev_wrdata;
-      prev_prev_prev_wrdata <= prev_prev_wrdata;
-    END IF;
-  END PROCESS;
-
-  p_bin_writer_mosi : PROCESS(dp_clk, dp_rst) IS  --, nxt_bin_writer_mosi, nxt_prev_wrdata, prev_wrdata, prev_prev_wrdata
-  BEGIN
-    IF dp_rst = '1' THEN
-       bin_writer_mosi       <= c_mem_mosi_rst;
---       prev_wrdata           <= 0;
---       prev_prev_wrdata      <= 0;
---       prev_prev_prev_wrdata <= 0;
-    ELSIF RISING_EDGE(dp_clk) THEN
-       bin_writer_mosi <= nxt_bin_writer_mosi;
---       IF nxt_bin_writer_mosi.wr = '1' THEN
---         prev_wrdata     <= nxt_prev_wrdata;
---         prev_prev_wrdata<= prev_wrdata;
---         prev_prev_prev_wrdata <= prev_prev_wrdata;
---       END IF;
-    END IF;
-  END PROCESS;
-
-
-  -----------------------------------------------------------------------------
-  -- Bin Arbiter: Determine next RAM access
-  -- . in  : bin_reader_mosi       (latency: 0)
-  --       : init_phase            (latency: 0)
-  --       : prev_bin_reader_mosi  (latency: 1)
-  --       : bin_reader_mosi_pp    (latency: 2)
-  --       : bin_reader_mosi_ppp   (latency: 3)
-  --       : bin_writer_mosi       (latency: 3)
-  --       : sync_detect           (latency:    0? or 3?
-  --       : common_ram_r_w_0_miso (latency: 2)
-  -- . out : bin_arbiter_rd_mosi   (latency: 1)
-  -- .     : bin_arbiter_rd_miso   (latency: 2)
-  -- .     : bin_arbiter_wr_mosi   (latency: 4)
-  -----------------------------------------------------------------------------
-  nxt_bin_arbiter_wr_mosi <= bin_writer_mosi;
-  -- Read RAM when subsequent addresses are not the same, when there is no toggle detected and only when the same address is not going to be written to. When a sync is detected don't read in the old RAM block.
-  nxt_bin_arbiter_rd_mosi.rd <= bin_reader_mosi.rd WHEN (bin_reader_mosi.address /= prev_bin_reader_mosi.address AND bin_reader_mosi.address /= bin_reader_mosi_pp.address 
-                                                         AND NOT(bin_reader_mosi.address = bin_reader_mosi_ppp.address) AND sync_detect='0')
-                                                   OR (init_phase = '1') ELSE '0';
-  nxt_bin_arbiter_rd_mosi.address <= bin_reader_mosi.address;
-
-  p_bin_arbiter_mosi : PROCESS(dp_clk, dp_rst) IS  --, nxt_bin_arbiter_wr_mosi, nxt_bin_arbiter_rd_mosi
-  BEGIN
-    IF dp_rst = '1' THEN
-      bin_arbiter_wr_mosi <= c_mem_mosi_rst;
-      bin_arbiter_rd_mosi <= c_mem_mosi_rst;
-    ELSIF RISING_EDGE(dp_clk) THEN
-      bin_arbiter_wr_mosi <= nxt_bin_arbiter_wr_mosi;
-      bin_arbiter_rd_mosi <= nxt_bin_arbiter_rd_mosi;
-    END IF;
-  END PROCESS;
-  
-  -- Temporary debug data
-  ram_miso.rddata <= bin_arbiter_wr_mosi.wrdata;
-  
-  -- Make RAM data available for the bin_reader (or bin_writer)
-  bin_arbiter_rd_miso <= common_ram_r_w_0_miso;
-
-
-  -----------------------------------------------------------------------------
-  -- RAM that contains the bins
-  -- . in  : bin_arbiter_wr_mosi   (latency: 4)
-  -- . in  : bin_arbiter_rd_mosi   (latency: 1)
-  -- . out : common_ram_r_w_0_miso (latency: 2)
-  -----------------------------------------------------------------------------
-  common_ram_r_w_0: ENTITY common_lib.common_ram_r_w
-  GENERIC MAP (
-    g_technology     => c_tech_select_default,
-    g_ram            => c_ram,
-    g_init_file      => "UNUSED"
-  )
-  PORT MAP (
-    rst      => dp_rst, 
-    clk      => dp_clk,
-    clken    => '1', 
-    wr_en    => bin_arbiter_wr_mosi.wr,
-    wr_adr   => bin_arbiter_wr_mosi.address(c_adr_w-1 DOWNTO 0),
-    wr_dat   => bin_arbiter_wr_mosi.wrdata(c_word_w-1 DOWNTO 0),
-    rd_en    => bin_arbiter_rd_mosi.rd,
-    rd_adr   => bin_arbiter_rd_mosi.address(c_adr_w-1 DOWNTO 0),
-    rd_dat   => common_ram_r_w_0_miso.rddata(c_word_w-1 DOWNTO 0),
-    rd_val   => common_ram_r_w_0_miso.rdval
-  );
-
-
-  
-END rtl;
-
diff --git a/libraries/dsp/st/src/vhdl/st_histogram_reg.vhd b/libraries/dsp/st/src/vhdl/st_histogram_reg.vhd
index 94b5895787d93f9e24bba470440a8a18b13e70a6..9230e11503c35feb7cbe26464f04d10776d48d51 100644
--- a/libraries/dsp/st/src/vhdl/st_histogram_reg.vhd
+++ b/libraries/dsp/st/src/vhdl/st_histogram_reg.vhd
@@ -18,98 +18,186 @@
 --
 -------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------
--- 
--- Author: J.W.E. Oudman
--- Purpose: Provide MM slave register for st_histogram
--- Description: 
---   Because the st_histogram component uses 2 RAM blocks that are swapped
---   after every sync pulse, both blocks have to work in the dp clock domain
---   and the Memory Mapped bus coming out of the component consequently also 
---   works in the dp clock domain. 
---   
---   To convert the signals to the mm clock domain the common_reg_cross_domain
---   component is used. Because the inner workings of that component is 
---   dependent on some components that take time to reliably stabialize the 
---   conversion takes 12 mm clock cycles before the next address may be 
---   requested.
---
---
---   [Alternative: shared dual clocked RAM block]
---
---
--------------------------------------------------------------------------------
+-- Author:
+-- . Daniel van der Schuur
+-- Purpose:
+-- . Provide MM registers for st_histogram
+-- Description:
+-- . Address 0, bit 0 = RAM clear
+--   . Read : 'ram_clearing' status output of st_histogram.vhd. '1' when RAM is clearing.
+-- . Address 1 = select RAM instance to fill (read out)
+--   . Read : read back selected instance
+--   . Write: select RAM instance to fill
+-- . Address 2, bit 0 = RAM fill
+--   . Read : 'ram_filling' status.  '1' right after write of ram_fill. '0' when not filling RAM (anymore).
+--   . Write: 'ram_fill '   control. '1' to fill RAM on write event.
 
-LIBRARY IEEE, common_lib, dp_lib;-- mm_lib, technology_lib,
+
+LIBRARY IEEE, common_lib;
 USE IEEE.std_logic_1164.ALL;
 USE common_lib.common_pkg.ALL;
 USE common_lib.common_mem_pkg.ALL;
-USE dp_lib.dp_stream_pkg.ALL;
---USE technology_lib.technology_select_pkg.ALL;
 
 ENTITY st_histogram_reg IS
---  GENERIC (
---    g_nof_bins      : NATURAL := 512;  -- is a power of 2 and g_nof_bins <= c_data_span; max. 512
---    g_str           : STRING  := "freq.density"  -- to select output to MM bus ("frequency" or "freq.density")
---  );                
+  GENERIC (
+    g_nof_instances : NATURAL
+  );
   PORT (            
-    dp_rst          : IN  STD_LOGIC;
-    dp_clk          : IN  STD_LOGIC;
-    mm_rst          : IN  STD_LOGIC;
-    mm_clk          : IN  STD_LOGIC;
-                    
-    -- DP clocked memory bus
-    mas_out_ram_mosi : OUT t_mem_mosi ;--:= c_mem_mosi_rst;  -- Beware, works in dp clock domain !
-    mas_in_ram_miso  : IN  t_mem_miso ;--:= c_mem_miso_rst;  --  ''                              !
---    ram_st_histogram_mosi : OUT  t_mem_mosi;  -- Beware, works in dp clock domain !
---    ram_st_histogram_miso : IN t_mem_miso;    --  ''                              !
-
-    -- Memory Mapped
-    ram_mosi : IN  t_mem_mosi;
-    ram_miso : OUT t_mem_miso
+    dp_clk        : IN  STD_LOGIC;
+    dp_rst        : IN  STD_LOGIC;
+  
+    ram_clearing  : IN  STD_LOGIC;
+  
+    ram_fill_inst : OUT STD_LOGIC_VECTOR(ceil_log2(g_nof_instances)-1 DOWNTO 0);
+    ram_fill      : OUT STD_LOGIC;
+    ram_filling   : IN  STD_LOGIC;
+  
+    mm_clk        : IN  STD_LOGIC;
+    mm_rst        : IN  STD_LOGIC;               
+  
+    reg_mosi      : IN  t_mem_mosi;
+    reg_miso      : OUT t_mem_miso
   );
 END st_histogram_reg;
 
-ARCHITECTURE str OF st_histogram_reg IS
-  
---  CONSTANT c_mm_reg : t_c_mem := (latency  => 1,
---                                  adr_w    => 1,
---                                  dat_w    => c_word_w,
---                                  nof_dat  => 1,
---                                  init_sl  => g_default_value);  
+ARCHITECTURE rtl OF st_histogram_reg IS
 
+  CONSTANT c_nof_addresses : NATURAL := 3;
+
+  CONSTANT c_mm_reg : t_c_mem := (latency  => 1,
+                                  adr_w    => ceil_log2(c_nof_addresses),
+                                  dat_w    => c_word_w, -- Use MM bus data width = c_word_w = 32 for all MM registers
+                                  nof_dat  => c_nof_addresses,
+                                  init_sl  => '0');                                              
+
+  SIGNAL mm_ram_clearing : STD_LOGIC; 
+
+  SIGNAL mm_ram_fill_inst : STD_LOGIC_VECTOR(ceil_log2(g_nof_instances)-1 DOWNTO 0);
+  SIGNAL mm_ram_fill      : STD_LOGIC; 
+  SIGNAL mm_ram_filling   : STD_LOGIC; 
   
 BEGIN 
   
+  ------------------------------------------------------------------------------
+  -- MM register access in the mm_clk domain
+  -- . Hardcode the shared MM slave register directly in RTL instead of using
+  --   the common_reg_r_w instance. Directly using RTL is easier when the large
+  --   MM register has multiple different fields and with different read and
+  --   write options per field in one MM register.
+  ------------------------------------------------------------------------------
+  p_mm_reg : PROCESS (mm_clk, mm_rst)
+  BEGIN
+    IF mm_rst = '1' THEN
+      -- Read access
+      reg_miso <= c_mem_miso_rst;
+      
+      -- Access event, register values
+      mm_ram_fill <= '0';
+      mm_ram_fill_inst <= (OTHERS=>'0');
+ 
+    ELSIF rising_edge(mm_clk) THEN
+      -- Read access defaults
+      reg_miso.rdval <= '0';
+      
+      -- Access event defaults
+      mm_ram_fill  <= '0';
+      
+      -- Write access: set register value
+      IF reg_mosi.wr = '1' THEN
+        CASE TO_UINT(reg_mosi.address(c_mm_reg.adr_w-1 DOWNTO 0)) IS
+          WHEN 1 =>
+            mm_ram_fill_inst <= reg_mosi.wrdata(ceil_log2(g_nof_instances)-1 DOWNTO 0);
+          WHEN 2 =>
+            mm_ram_fill <= '1';
+          WHEN OTHERS => NULL;  -- unused MM addresses
+        END CASE;
+        
+      -- Read access: get register value
+      ELSIF reg_mosi.rd = '1' THEN
+        reg_miso       <= c_mem_miso_rst;    -- set unused rddata bits to '0' when read
+        reg_miso.rdval <= '1';               -- c_mm_reg.latency = 1
+        CASE TO_UINT(reg_mosi.address(c_mm_reg.adr_w-1 DOWNTO 0)) IS
+          WHEN 0 =>
+            -- Read RAM clearing status
+            reg_miso.rddata(0) <= mm_ram_clearing;
+          WHEN 1 =>
+            -- Read selected RAM instance to fill
+            reg_miso.rddata(ceil_log2(g_nof_instances)-1 DOWNTO 0) <= mm_ram_fill_inst;
+          WHEN 2 =>
+            -- Read RAM filling status
+            reg_miso.rddata(0) <= mm_ram_filling;
+          WHEN OTHERS => NULL;  -- unused MM addresses
+        END CASE;
+      END IF;
+    END IF;
+  END PROCESS;
 
-  u_common_reg_cross_domain_mosi_address : ENTITY common_lib.common_reg_cross_domain
+  ------------------------------------------------------------------------------
+  -- Transfer register value between mm_clk and st_clk domain.
+  -- If the function of the register ensures that the value will not be used
+  -- immediately when it was set, then the transfer between the clock domains
+  -- can be done by wires only. Otherwise if the change in register value can
+  -- have an immediate effect then the bit or word value needs to be transfered
+  -- using:
+  --
+  -- . common_async            --> for single-bit level signal
+  -- . common_spulse           --> for single-bit pulse signal
+  -- . common_reg_cross_domain --> for a multi-bit (a word) signal
+  --
+  -- Typically always use a crossing component for the single bit signals (to
+  -- be on the save side) and only use a crossing component for the word
+  -- signals if it is necessary (to avoid using more logic than necessary).
+  ------------------------------------------------------------------------------
+  
+  -- ST --> MM
+  u_common_async_clear : ENTITY common_lib.common_async
+  GENERIC MAP (
+    g_rst_level => '0'
+  )
   PORT MAP (
-    in_rst     => mm_rst,
-    in_clk     => mm_clk,
-    
-    in_new     => ram_mosi.rd,
-    in_dat     => ram_mosi.address,
+    clk  => mm_clk,
+    rst  => mm_rst,
 
-    out_rst    => dp_rst,
-    out_clk    => dp_clk,
+    din  => ram_clearing,
+    dout => mm_ram_clearing
+  );
+
+ u_common_async_fill : ENTITY common_lib.common_async
+  GENERIC MAP (
+    g_rst_level => '0'
+  )
+  PORT MAP (
+    clk  => mm_clk,
+    rst  => mm_rst,
 
-    out_dat    => mas_out_ram_mosi.address,
-    out_new    => mas_out_ram_mosi.rd
+    din  => ram_filling,
+    dout => mm_ram_filling
   );
-  
-  u_reg_cross_domain_miso_rddata : ENTITY common_lib.common_reg_cross_domain
+
+  u_common_spulse_fill : ENTITY common_lib.common_spulse
   PORT MAP (
-    in_rst     => dp_rst,
-    in_clk     => dp_clk,
-    
-    in_new     => mas_in_ram_miso.rdval,
-    in_dat     => mas_in_ram_miso.rddata,
+    in_clk    => mm_clk,
+    in_rst    => mm_rst,
 
-    out_rst    => mm_rst,
-    out_clk    => mm_clk,
+    in_pulse  => mm_ram_fill,
+    in_busy   => OPEN,
 
-    out_dat    => ram_miso.rddata,
-    out_new    => ram_miso.rdval
-  );
-  
-END str;
+    out_clk   => dp_clk,
+    out_rst   => dp_rst,
+
+    out_pulse => ram_fill
+  ); 
+
+  u_common_reg_cross_domain : ENTITY common_lib.common_reg_cross_domain
+    PORT MAP (
+      in_clk      => mm_clk,
+      in_rst      => mm_rst,
+      in_dat      => mm_ram_fill_inst,
+      in_done     => OPEN,
+      out_clk     => dp_clk,
+      out_rst     => dp_rst,
+      out_dat     => ram_fill_inst,
+      out_new     => OPEN
+    );
+
+END rtl;
diff --git a/libraries/dsp/st/tb/vhdl/tb_mms_st_histogram.vhd b/libraries/dsp/st/tb/vhdl/tb_mms_st_histogram.vhd
index fbb57a6c0ff7b8c3037c3adad36ed70083133620..0e8fea35b4f7ce3e88e4db243d208345db39ef2a 100644
--- a/libraries/dsp/st/tb/vhdl/tb_mms_st_histogram.vhd
+++ b/libraries/dsp/st/tb/vhdl/tb_mms_st_histogram.vhd
@@ -20,283 +20,231 @@
 
 -------------------------------------------------------------------------------
 -- 
--- Author: J.W.E. Oudman
--- Purpose: Create a histogram from the input data and present it to the MM bus
--- Description: 
---  
---
---
+-- Author: 
+-- . Daniel van der Schuur
+-- Purpose:
+-- . 
+-- ModelSim usage:
+-- . (open project, compile)
+-- . (load simulation config)
+-- . as 8
+-- . run -a
+-- Description:
+-- . 
 -------------------------------------------------------------------------------
 
 LIBRARY IEEE, common_lib, mm_lib, dp_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.tb_common_mem_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_mms_st_histogram IS
   GENERIC(
-    g_sync_length          : NATURAL := 338;
-    g_nof_sync             : NATURAL := 3;
-    g_data_w               : NATURAL := 4;
-    g_nof_bins             : NATURAL := 8;
-    g_nof_data             : NATURAL := 338;
-    g_str                  : STRING  := "freq.density";
-    g_valid_gap            : BOOLEAN := FALSE;
-    g_snk_in_data_sim_type : STRING  := "counter"  -- "counter" or "toggle"
-    );
+    g_nof_sync          : NATURAL := 4;
+    g_nof_instances     : NATURAL := 12;
+    g_data_w            : NATURAL := 14;
+    g_nof_bins          : NATURAL := 512;
+    g_nof_data_per_sync : NATURAL := 40000
+  );
 END tb_mms_st_histogram;
 
 
 ARCHITECTURE tb OF tb_mms_st_histogram IS
-  
-  CONSTANT c_adr_w              : NATURAL  := ceil_log2(g_nof_bins);
-  
-  CONSTANT c_mm_init_time       : NATURAL   := 5;
-  CONSTANT c_dp_inti_time       : NATURAL   := 5;
-  
-  SIGNAL tb_end                 : STD_LOGIC := '0';
-  SIGNAL first_sync             : STD_LOGIC := '0';
-
-  ----------------------------------------------------------------------------
+ 
+  ---------------------------------------------------------------------------
   -- Clocks and resets
-  ----------------------------------------------------------------------------   
-  CONSTANT c_mm_clk_period      : TIME := 20 ns;
-  CONSTANT c_dp_clk_period      : TIME := 5 ns;
+  ---------------------------------------------------------------------------
+  CONSTANT c_dp_clk_period : TIME := 5 ns;
+  CONSTANT c_mm_clk_period : TIME := 20 ns;
 
+  SIGNAL dp_clk            : STD_LOGIC := '1';
+  SIGNAL dp_rst            : STD_LOGIC;
 
-  SIGNAL mm_rst                 : STD_LOGIC := '1';
-  SIGNAL mm_clk                 : STD_LOGIC := '1';
+  SIGNAL mm_clk            : STD_LOGIC := '1';
+  SIGNAL mm_rst            : STD_LOGIC;
+
+  SIGNAL tb_end            : STD_LOGIC := '0';
 
-  SIGNAL dp_rst                 : STD_LOGIC;
-  SIGNAL dp_clk                 : STD_LOGIC := '1';
-  
-  
-  
-  
   ----------------------------------------------------------------------------
-  -- Streaming Input
+  -- stimuli
   ----------------------------------------------------------------------------
-  
-  SIGNAL st_histogram_snk_in : t_dp_sosi;
-  
+  SIGNAL stimuli_en : STD_LOGIC := '1';
+
+  SIGNAL stimuli_src_out : t_dp_sosi;
+  SIGNAL stimuli_src_in  : t_dp_siso;
+   
   ----------------------------------------------------------------------------
-  -- Memory Mapped Input
+  -- st_histogram
   ----------------------------------------------------------------------------
-  
-  SIGNAL st_histogram_ram_mosi : t_mem_mosi;
-  SIGNAL st_histogram_ram_miso : t_mem_miso;
-  
-  
+  SIGNAL st_histogram_snk_in_arr : t_dp_sosi_arr(g_nof_instances-1 DOWNTO 0);
+
+  SIGNAL st_histogram_reg_mosi   : t_mem_mosi;
+  SIGNAL st_histogram_reg_miso   : t_mem_miso;
+
+  SIGNAL st_histogram_ram_mosi   : t_mem_mosi;
+  SIGNAL st_histogram_ram_miso   : t_mem_miso;
+
+   
+  ----------------------------------------------------------------------------
+  -- Readout & verification
+  ----------------------------------------------------------------------------
+  CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync)+1;
+
+  CONSTANT c_expected_ram_content : NATURAL := g_nof_data_per_sync/g_nof_bins;
+
+  SIGNAL ram_filling : STD_LOGIC;
+
+  SIGNAL ram_rd_word           : STD_LOGIC_VECTOR(c_ram_dat_w-1 DOWNTO 0);
+  SIGNAL ram_rd_word_int       : NATURAL;
+  SIGNAL ram_rd_word_valid     : STD_LOGIC;
+  SIGNAL nxt_ram_rd_word_valid : STD_LOGIC;
+
 BEGIN 
   
   ----------------------------------------------------------------------------
   -- Clock and reset generation
   ----------------------------------------------------------------------------
+  dp_clk <= NOT dp_clk OR tb_end AFTER c_dp_clk_period/2;
+  dp_rst <= '1', '0' AFTER c_dp_clk_period*10;
+
   mm_clk <= NOT mm_clk OR tb_end AFTER c_mm_clk_period/2;
-  mm_rst <= '1', '0' AFTER c_mm_clk_period*c_mm_init_time;
+  mm_rst <= '1', '0' AFTER c_mm_clk_period*10;
+ 
 
-  dp_clk <= NOT dp_clk OR tb_end AFTER c_dp_clk_period/2;
-  dp_rst <= '1', '0' AFTER c_dp_clk_period*c_dp_inti_time;
-  
-  
-  
-  
-  ----------------------------------------------------------------------------
-  -- Source: counter stimuli 
-  ----------------------------------------------------------------------------
-  
-  p_data : PROCESS(dp_rst, dp_clk, st_histogram_snk_in)
-  BEGIN
-    IF g_snk_in_data_sim_type = "counter" THEN
-      IF dp_rst='1' THEN
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= (OTHERS=>'0');
-      ELSIF rising_edge(dp_clk) AND st_histogram_snk_in.valid='1' THEN
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_snk_in.data(g_data_w-1 DOWNTO 0), 1);
-      END IF;
-    ELSIF g_snk_in_data_sim_type = "toggle" THEN
-      IF dp_rst='1' THEN
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= (OTHERS=>'0');
-      ELSIF rising_edge(dp_clk) AND st_histogram_snk_in.valid='1' THEN
-        IF st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) = TO_UVEC(0, g_data_w) THEN
-          st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= TO_UVEC(1, g_data_w);
-        ELSE
-          st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= TO_UVEC(0, g_data_w);
-        END IF;
-      END IF;
-    END IF;
-  END PROCESS;
-  
-  p_stimuli : PROCESS
-  BEGIN
-    IF g_valid_gap = FALSE THEN
---      dp_rst <= '1';
-      st_histogram_snk_in.sync <= '0';
-      st_histogram_snk_in.valid <= '0';
-      WAIT UNTIL rising_edge(dp_clk);
---      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
---      dp_rst <= '0';
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      st_histogram_snk_in.valid <= '1';
-      
-      
-      FOR I IN 0 TO g_nof_sync-1 LOOP
-        st_histogram_snk_in.sync <= '1';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.sync <= '0';
-        FOR I IN 0 TO g_sync_length-1 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-        
-      END LOOP;
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      tb_end <= '1';
-      WAIT;
-      
-    ELSIF g_valid_gap = TRUE THEN
---      dp_rst <= '1';
-      st_histogram_snk_in.sync <= '0';
-      st_histogram_snk_in.valid <= '0';
-      WAIT UNTIL rising_edge(dp_clk);
---      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
---      dp_rst <= '0';
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      st_histogram_snk_in.valid <= '1';
-      
-      
-      FOR I IN 0 TO g_nof_sync-2 LOOP
-        st_histogram_snk_in.sync <= '1';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.sync <= '0';
-        FOR I IN 0 TO (g_sync_length/2)-1 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-        st_histogram_snk_in.valid <= '0';
-        WAIT UNTIL rising_edge(dp_clk);
-        --WAIT UNTIL rising_edge(dp_clk);
-        --WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.valid <= '1';
-        FOR I IN 0 TO (g_sync_length/4)-1 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-        st_histogram_snk_in.valid <= '0';
-        WAIT UNTIL rising_edge(dp_clk);
-        --st_histogram_snk_in.valid <= '0';
-        st_histogram_snk_in.sync <= '1';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.valid <= '1';
-        st_histogram_snk_in.sync <= '0';
-        FOR I IN 0 TO (g_sync_length/4)-1 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-        
-      END LOOP;
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      tb_end <= '1';
-      WAIT;
-    END IF;
-  END PROCESS;
-  
   ----------------------------------------------------------------------------
-  -- Source: read MM bus stimuli
-  ----------------------------------------------------------------------------
-  
---  p_mm_stimuli : PROCESS --(st_histogram_snk_in.sync)
---  BEGIN
---    IF mm_rst='1' THEN
---      st_histogram_ram_mosi <= c_mem_mosi_rst;  --.address(c_adr_w-1 DOWNTO 0) <= (OTHERS=>'0');
-----    ELSIF rising_edge(mm_clk) THEN --AND st_histogram_snk_in.valid='1'
---    ELSE
---      IF first_sync = '0' THEN
---        WAIT UNTIL st_histogram_snk_in.sync = '1';
---        first_sync <= '1';
---        -- wait till one RAM block is written
---        FOR I IN 0 TO (g_sync_length/4) LOOP WAIT UNTIL rising_edge(mm_clk); END LOOP;
---        -- wait for some more cycles
---        FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(mm_clk); END LOOP;
-----      ELSIF rising_edge(mm_clk) THEN
---      ELSE
---        FOR I IN 0 TO g_nof_bins-1
---        -- 
---        st_histogram_ram_mosi.rd <= '1';
---        st_histogram_ram_mosi.address(c_adr_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_ram_mosi.address(c_adr_w-1 DOWNTO 0), 1);
---      END IF;
---    END IF;
---  END PROCESS;
-  
-  p_mm_stimuli : PROCESS --(st_histogram_snk_in.sync)
+  -- DP Stimuli: generate st_histogram input data
+  ---------------------------------------------------------------------------- 
+  stimuli_src_in <= c_dp_siso_rdy;
+
+  -- Generate g_nof_sync packets of g_nof_data_per_sync words
+  p_generate_packets : PROCESS
+    VARIABLE v_sosi : t_dp_sosi := c_dp_sosi_rst;
   BEGIN
-    --IF mm_rst='1' THEN
-      st_histogram_ram_mosi <= c_mem_mosi_rst;  --.address(c_adr_w-1 DOWNTO 0) <= (OTHERS=>'0');
---    ELSIF rising_edge(mm_clk) THEN --AND st_histogram_snk_in.valid='1'
-    --ELSE
-      --IF first_sync = '0' THEN
-        WAIT UNTIL st_histogram_snk_in.sync = '1';
-        --first_sync <= '1';
-        -- wait till one RAM block is written
-        FOR I IN 0 TO (g_sync_length/4) LOOP WAIT UNTIL rising_edge(mm_clk); END LOOP;
-        -- wait for some more cycles
-        FOR I IN 0 TO 2 LOOP WAIT UNTIL rising_edge(mm_clk); END LOOP;
---      ELSIF rising_edge(mm_clk) THEN
-      --ELSE
-        FOR I IN 0 TO g_nof_bins-1 LOOP
-          proc_mem_mm_bus_rd(I, mm_clk, st_histogram_ram_mosi);
-          proc_common_wait_some_cycles(mm_clk, 11);
-          -- miso.rddata arrives
-        END LOOP;
-        -- 
-        --st_histogram_ram_mosi.rd <= '1';
-        --st_histogram_ram_mosi.address(c_adr_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_ram_mosi.address(c_adr_w-1 DOWNTO 0), 1);
-      --END IF;
-    --END IF;
+    stimuli_src_out <= c_dp_sosi_rst;
+    proc_common_wait_until_low(dp_clk, dp_rst);
+    proc_common_wait_some_cycles(dp_clk, 5);
+
+    FOR I IN 0 TO g_nof_sync-1 LOOP
+      v_sosi.sync    := '1';
+      v_sosi.data    := RESIZE_DP_DATA(v_sosi.data(g_data_w-1 DOWNTO 0));  -- wrap when >= 2**g_data_w    
+      proc_dp_gen_block_data(g_data_w, TO_UINT(v_sosi.data), g_nof_data_per_sync, TO_UINT(v_sosi.channel), TO_UINT(v_sosi.err), v_sosi.sync, v_sosi.bsn, dp_clk, stimuli_en, stimuli_src_in, stimuli_src_out);
+    END LOOP;     
+
+    proc_common_wait_some_cycles(dp_clk, 50);
+    tb_end <= '1';
+    WAIT;
   END PROCESS;
-  
---  -- Read data request to the MM bus
---  -- Use proc_mem_mm_bus_rd_latency() to wait for the MM MISO rd_data signal
---  -- to show the data after some read latency
---  PROCEDURE proc_mem_mm_bus_rd(CONSTANT rd_addr : IN  NATURAL;
---                               SIGNAL   mm_clk  : IN  STD_LOGIC;
---                               SIGNAL   mm_miso : IN  t_mem_miso;
---                               SIGNAL   mm_mosi : OUT t_mem_mosi) IS
---  BEGIN
---    mm_mosi.address <= TO_MEM_ADDRESS(rd_addr);
---    proc_mm_access(mm_clk, mm_miso.waitrequest, mm_mosi.rd);
---  END proc_mem_mm_bus_rd;
-
----- Issues a rd or a wr MM access and wait for it to have finished
---  PROCEDURE proc_mm_access(SIGNAL mm_clk     : IN  STD_LOGIC;
---                           SIGNAL mm_waitreq : IN  STD_LOGIC;
---                           SIGNAL mm_access  : OUT STD_LOGIC) IS
---  BEGIN
---    mm_access <= '1';
---    WAIT UNTIL rising_edge(mm_clk);
---    WHILE mm_waitreq='1' LOOP
---      WAIT UNTIL rising_edge(mm_clk);
---    END LOOP;
---    mm_access <= '0';
---  END proc_mm_access;
-
---    proc_mem_mm_bus_rd(0, mm_clk, mm_mosi);   -- Read nof_early_syncs
---    proc_common_wait_some_cycles(mm_clk, 1);
---    mm_nof_early_syncs <= mm_miso.rddata(c_word_w-1 DOWNTO 0);
-  
+
   ----------------------------------------------------------------------------
-  -- DUT: Device Under Test
+  -- mms_st_histogram
   ----------------------------------------------------------------------------
-  
+  gen_snk_in_arr: FOR i IN 0 TO g_nof_instances-1 GENERATE
+    st_histogram_snk_in_arr(i) <= stimuli_src_out;
+  END GENERATE;
+
   u_mms_st_histogram : ENTITY work.mms_st_histogram
   GENERIC MAP(
-    g_in_data_w  => g_data_w,
-    g_nof_bins   => g_nof_bins,
-    g_nof_data   => g_nof_data,
-    g_str        => g_str
+    g_nof_instances     => g_nof_instances,
+    g_data_w            => g_data_w,
+    g_nof_bins          => g_nof_bins,
+    g_nof_data_per_sync => g_nof_data_per_sync
   )
   PORT MAP (
+    dp_clk       => dp_clk,           
     dp_rst       => dp_rst,
-    dp_clk       => dp_clk,
+
+    mm_clk       => mm_clk,           
     mm_rst       => mm_rst,
-    mm_clk       => mm_clk,
-             
-    -- Streaming
-    snk_in       => st_histogram_snk_in,
-  
-    -- Memory Mapped
+
+    snk_in_arr   => st_histogram_snk_in_arr,
+
+    reg_mosi     => st_histogram_reg_mosi,
+    reg_miso     => st_histogram_reg_miso,
+ 
     ram_mosi     => st_histogram_ram_mosi,
-    ram_miso     => st_histogram_ram_miso --OPEN
+    ram_miso     => st_histogram_ram_miso
   );
-  
+
+
+  ----------------------------------------------------------------------------
+  -- MM Readout of st_histogram instances
+  ---------------------------------------------------------------------------- 
+  p_ram_clear : PROCESS
+  BEGIN
+    st_histogram_ram_mosi <= c_mem_mosi_rst;
+    st_histogram_reg_mosi <= c_mem_mosi_rst;
+    ram_filling <= '0';
+    ram_rd_word <= (OTHERS=>'0');
+     -- The first sync indicates start of incoming data - let it pass
+     proc_common_wait_until_high(dp_clk, stimuli_src_out.sync);
+     proc_common_wait_some_cycles(mm_clk, 10);
+     FOR i IN 0 TO g_nof_sync-2 LOOP 
+       -- Wiat for a full sync period of data
+       proc_common_wait_until_high(dp_clk, stimuli_src_out.sync);
+        -- The sync has passed, we can start reading the resulting histogram
+       FOR j IN 0 TO g_nof_instances-1 LOOP
+         -- Select st_histogram instance to read out
+         proc_mem_mm_bus_wr(1, j, mm_clk, st_histogram_reg_mosi);
+         proc_common_wait_some_cycles(mm_clk, 2);
+
+         -- Enable RAM filling
+         proc_mem_mm_bus_wr(2, 1, mm_clk, st_histogram_reg_mosi);
+         proc_common_wait_some_cycles(mm_clk, 10);
+
+         -- Wait until RAM filling is done
+         proc_mem_mm_bus_rd(2, mm_clk, st_histogram_reg_mosi);
+         ram_filling <= st_histogram_reg_miso.rddata(0);
+         proc_common_wait_some_cycles(mm_clk, 2);
+         WHILE ram_filling='1' LOOP
+            -- Read filling status
+           proc_mem_mm_bus_rd(2, mm_clk, st_histogram_reg_mosi);
+           ram_filling <= st_histogram_reg_miso.rddata(0);
+           proc_common_wait_some_cycles(mm_clk, 1);
+         END LOOP;
+
+         -- Read out the RAM contents
+        FOR k IN 0 TO g_nof_bins-1 LOOP
+           proc_mem_mm_bus_rd(k, mm_clk, st_histogram_ram_mosi);
+           ram_rd_word <= st_histogram_ram_miso.rddata(c_ram_dat_w-1 DOWNTO 0);
+           ram_rd_word_int <= TO_UINT(ram_rd_word);
+        END LOOP;
+      END LOOP;
+    END LOOP;
+  END PROCESS;
+
+  -- Register st_histogram_ram_miso.rdval so we read only valid data
+  p_nxt_ram_rd_word_valid : PROCESS(mm_rst, mm_clk)
+  BEGIN
+   IF mm_rst = '1' THEN
+      ram_rd_word_valid <= '0';   
+    ELSIF RISING_EDGE(mm_clk) THEN
+      ram_rd_word_valid <= nxt_ram_rd_word_valid;
+    END IF;
+  END PROCESS;
+  nxt_ram_rd_word_valid <= st_histogram_ram_miso.rdval;
+
+
+  ----------------------------------------------------------------------------
+  -- Perform verification of ram_rd_word when ram_rd_word_valid
+  ----------------------------------------------------------------------------
+  p_verify_assert : PROCESS
+  BEGIN
+    FOR i IN 0 TO g_nof_sync-1 LOOP
+      proc_common_wait_until_high(dp_clk, stimuli_src_out.sync);  
+      proc_common_wait_until_high(dp_clk, ram_rd_word_valid);      
+      IF i=0 THEN -- Sync period 0: we expect RAM to contain zeros
+        ASSERT ram_rd_word_int=0                      REPORT "RAM contains wrong bin count (expected 0, actual " & INTEGER'IMAGE(ram_rd_word_int) & ")" SEVERITY ERROR;
+      ELSE -- Sync period 1 onwards
+        ASSERT ram_rd_word_int=c_expected_ram_content REPORT "RAM contains wrong bin count (expected " & INTEGER'IMAGE(c_expected_ram_content) & ", actual " & INTEGER'IMAGE(ram_rd_word_int) & ")" SEVERITY ERROR;
+      END IF;
+    END LOOP;
+    WAIT FOR 5 ns;
+  END PROCESS;
+
+
 END tb;
diff --git a/libraries/dsp/st/tb/vhdl/tb_st_histogram.vhd b/libraries/dsp/st/tb/vhdl/tb_st_histogram.vhd
index faad666ee4410b764b11291d621bd29abdc68728..6b4d3eeadd9b5807ab58e9ae606dcd72d3df91c7 100644
--- a/libraries/dsp/st/tb/vhdl/tb_st_histogram.vhd
+++ b/libraries/dsp/st/tb/vhdl/tb_st_histogram.vhd
@@ -20,521 +20,201 @@
 
 -------------------------------------------------------------------------------
 -- 
--- Author: J.W.E. Oudman
--- Purpose: Testing the st_histogram component on it's pecularities
--- Description: 
---   The st_histogram component is mainly about saving counter data and 
---   making the saved data available for the MM master. The working of the 
---   RAM blocks has a big influence on this. That is why the testbench is made
---   to generate data that can make related problems with that vissible.
---
---   To know if there can constantly new data be witten to the RAM blocks 
---   a counter would be sufficient.
---   
---   Because there is a delay between requesting and writing back of data of 
---   3 cycles and it is illegal to read and write on the same adres at the 
---   same time, there are 2 special situations that can happen. One where the 
---   addresses can toggle (e.g. 0; 1; 0; 1) and one where a simultanious read 
---   and write are triggered (e.g. 0; 1; 1; 0). Both would cause incorrect 
---   counting as the address count can't be updated (written) before it's 
---   address is requested again. Due to this the counter in st_histogram can 
---   not be a simple counter that only counts and compares on repeating 
---   addresses. It also has to compare on 2 and 3 cycles back - which makes 
---   it complicated enough that it requires additional test stimuli. 
---   To simulate with the required stimuli the g_snk_in_data_sim_type can be 
---   set to 'counter', 'toggle', 'same rw' or a 'mix' of it.
---
---   Only incoming data while snk_in.valid = '1' may be counted. To keep the
---   simulation simple there is the option to let there be some gap's in the
---   valid data (or not) where snk_in.valid = '0' by setting the g_valid_gap 
---   to 'true', 'false' or 'custom'.
---
+-- Author: 
+-- . Daniel van der Schuur
+-- Purpose:
+-- . Generate st_histogram input data, verify RAM contents. TB is self checking.
+-- ModelSim usage:
+-- . (open project, compile)
+-- . (load simulation config)
+-- . as 8
+-- . run -a
+-- Description:
+-- . Verification be eye (wave window) - observe that:
+--   . There are 4 sync periods in which 3 packets of 1024 words are generated;
+--   . histogram_snk_in.data = 0..1023, 3 times per sync
+--     . st_histogram has 256 bins so uses the 8 MS bits of snk_in.data
+--     . st_histogram will count 4*0..255 instead of 0..1023 per packet
+--     . st_histogram will count 12 occurences (3 packets * 4 * 0..255) per sync.
+--   . bin_writer_mosi writes bin counts 1..12 per sync interval;
+--   . Both RAMs are used twice: RAM 0, RAM 1, RAM 0, RAM 1;
+--   . RAM clearing completes just before the end of each sync interval.
+-- . Automatic verification:
+--   . In each sync period the RAM contents are read out via ram_mosi/miso and 
+--     compared to the expected bin counts.
 -------------------------------------------------------------------------------
 
 LIBRARY IEEE, common_lib, mm_lib, dp_lib;
 USE IEEE.std_logic_1164.ALL;
-USE IEEE.numeric_std.ALL;           -- needed by TO_UNSIGNED
+USE IEEE.numeric_std.ALL; 
 USE common_lib.common_pkg.ALL;
 USE common_lib.common_mem_pkg.ALL;
+USE common_lib.tb_common_mem_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_st_histogram IS
   GENERIC(
-    g_sync_length          : NATURAL := 200;
-    g_nof_sync             : NATURAL := 3;
-    g_data_w               : NATURAL := 4; --4 ; 1
-    g_nof_bins             : NATURAL := 8; --8 ; 2
-    g_nof_data             : NATURAL := 200;
-    --g_str                  : STRING  := "freq.density";
-    g_valid_gap            : STRING  := "custom"; -- "false" or "true" or "custom" --BOOLEAN := TRUE
-    g_snk_in_data_sim_type : STRING  := "same rw"  -- "counter" or "toggle" or "same rw" or "mix"
+    g_nof_sync             : NATURAL := 4; -- We're simulating at least 4 g_nof_sync so both RAMs are written and cleared twice.
+    g_data_w               : NATURAL := 8; -- Determines maximum number of bins (2^g_data_w)
+    g_nof_bins             : NATURAL := 256; -- Lower than or equal to 2^g_data_w. Higher is allowed but makes no sense.
+    g_nof_data_per_sync    : NATURAL := 1024 -- Determines max required RAM data width. e.g. 11b to store max bin count '1024'.
     );
 END tb_st_histogram;
 
 
 ARCHITECTURE tb OF tb_st_histogram IS
-  
-  CONSTANT c_adr_w              : NATURAL  := ceil_log2(g_nof_bins);
-  CONSTANT c_adr_low_calc       : INTEGER  := g_data_w-c_adr_w;             -- Calculation might yield a negative number
-  CONSTANT c_adr_low            : NATURAL  := largest(0, c_adr_low_calc);   -- Override any negative value of c_adr_low_calc
-  --SIGNAL position               : INTEGER range g_data_w'RANGE;
 
-  CONSTANT c_dp_inti_time       : NATURAL   := 5;
-  
-  SIGNAL tb_end                 : STD_LOGIC := '0';
-  SIGNAL pre_valid              : STD_LOGIC := '0';
-  SIGNAL prev_unvalid           : STD_LOGIC := '0';
-  SIGNAL init_phase             : STD_LOGIC := '1';
-  SIGNAL toggle_start           : STD_LOGIC := '0';
-  SIGNAL pre_sync               : STD_LOGIC := '0';
-  
-  
-  ----------------------------------------------------------------------------
-  -- Same read write test stimuli
-  ----------------------------------------------------------------------------
-  TYPE t_srw_arr IS ARRAY (NATURAL RANGE <>) OF INTEGER;
-  CONSTANT c_srw_arr            : t_srw_arr := (0,0,1,1,0,0,1,2,3, 1, 2, 3, 0, 3, 3, 0, 3);
-                                            --  1.2.3.4.5.6.7.8.9.10.11.12.13.14.15.16.17
-                                            --0:1.2.    3.4.               05.      06.
-                                            --1:    1.2.    3.    04.
-                                            --2:              1.     02.
-                                            --3:                1.      02.   03.04.   05.
-                                            --srw:      x.  x.     x. x. x.       x. x. u.
-  
-  SIGNAL srw_index_cnt          : NATURAL   := 0;
-  
-  
-  ----------------------------------------------------------------------------
-  -- Valid stimuli
-  ----------------------------------------------------------------------------
-  TYPE t_val_arr IS ARRAY (NATURAL RANGE <>) OF INTEGER;
-  CONSTANT c_val_arr            : t_val_arr := (1,1,1,1,0,1,1,1,1, 1, 1, 1, 1, 0, 1, 1, 1);
-                                            --  1.2.3.4.5.6.7.8.9.10.11.12.13.14.15.16.17
-  
-  SIGNAL val_index_cnt          : NATURAL   := 0;
-  SIGNAL dbg_valid              : NATURAL;
-  
-  
-  ----------------------------------------------------------------------------
+  ---------------------------------------------------------------------------
+  -- Constants derived from generics
+  ---------------------------------------------------------------------------
+  CONSTANT c_expected_ram_content      : NATURAL := g_nof_data_per_sync/g_nof_bins;
+
+  CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync)+1;
+    
+  ---------------------------------------------------------------------------
   -- Clocks and resets
-  ----------------------------------------------------------------------------   
+  ---------------------------------------------------------------------------
   CONSTANT c_dp_clk_period      : TIME := 5 ns;
 
   SIGNAL dp_rst                 : STD_LOGIC;
   SIGNAL dp_clk                 : STD_LOGIC := '1';
-  
-  
-  
-  
-  ----------------------------------------------------------------------------
-  -- Streaming Input
-  ----------------------------------------------------------------------------
-  
-  SIGNAL st_histogram_snk_in : t_dp_sosi;
-  
-  
+
+  SIGNAL tb_end                 : STD_LOGIC := '0';
+   
   ----------------------------------------------------------------------------
-  -- Streaming Output
+  -- stimuli
   ----------------------------------------------------------------------------
-  
-  SIGNAL st_histogram_ram_miso     : t_mem_miso;
-  SIGNAL st_histogram_dbg_ram_miso : t_mem_miso;
-  
-  
+  SIGNAL stimuli_en : STD_LOGIC := '1';
+
+  SIGNAL stimuli_src_out : t_dp_sosi;
+  SIGNAL stimuli_src_in  : t_dp_siso;
+
   ----------------------------------------------------------------------------
-  -- Self check array
+  -- st_histogram
   ----------------------------------------------------------------------------
-  TYPE t_data_check_arr IS ARRAY (0 TO g_nof_bins) OF INTEGER;
-  SIGNAL data_check_arr         : t_data_check_arr := (OTHERS=> 0);
-                                            
-  SIGNAL check_adr               : NATURAL := 0;
-  SIGNAL prev_check_adr          : NATURAL;
-  SIGNAL nxt_check_arr_cnt       : NATURAL;
-  
-  SIGNAL st_histogram_snk_in_ppp : t_dp_sosi;
-  SIGNAL st_histogram_snk_in_pppp: t_dp_sosi;
---  SIGNAL dbg_check_adr           :STD_LOGIC_VECTOR(g_data_w-1 DOWNTO c_adr_low); --  : NATURAL;
-  
-  SIGNAL dbg_error_location      : STD_LOGIC;
-  SIGNAL error_cnt               : NATURAL;
-  SIGNAL dbg_int_data_miso       : NATURAL;
-  SIGNAL dbg_int_data_arr        : NATURAL;
-  
+  SIGNAL st_histogram_snk_in    : t_dp_sosi;
+  SIGNAL st_histogram_ram_mosi  : t_mem_mosi;
+  SIGNAL st_histogram_ram_miso  : t_mem_miso;
   
+   ----------------------------------------------------------------------------
+   -- Automatic verification of RAM readout
+   ----------------------------------------------------------------------------
+  SIGNAL ram_rd_word           : STD_LOGIC_VECTOR(c_ram_dat_w-1 DOWNTO 0);
+  SIGNAL ram_rd_word_int       : NATURAL;
+  SIGNAL ram_rd_word_valid     : STD_LOGIC;
+  SIGNAL nxt_ram_rd_word_valid : STD_LOGIC;
+
 BEGIN 
   
   ----------------------------------------------------------------------------
   -- Clock and reset generation
   ----------------------------------------------------------------------------
   dp_clk <= NOT dp_clk OR tb_end AFTER c_dp_clk_period/2;
-  dp_rst <= '1', '0' AFTER c_dp_clk_period*c_dp_inti_time;
-  
-  
-  
-  
+  dp_rst <= '1', '0' AFTER c_dp_clk_period*10;
+ 
+ 
   ----------------------------------------------------------------------------
-  -- Source: stimuli
-  --  st_histogram_snk_in.data    counter or toggle or same_rw stimuli
-  --                     .valid   with or without gap's in valid stimuli
-  --                     .sync    sync stimuli
+  -- Stimuli: generate st_histogram input data and clear the RAM
   ---------------------------------------------------------------------------- 
-  
-  init_phase <= '0' WHEN st_histogram_snk_in.sync = '1';
+  stimuli_src_in <= c_dp_siso_rdy;
 
-  p_data : PROCESS(dp_rst, dp_clk, st_histogram_snk_in)
-  BEGIN
-    IF g_snk_in_data_sim_type = "counter" THEN
-      IF dp_rst='1' THEN
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= (OTHERS=>'0');
-      ELSIF rising_edge(dp_clk) AND pre_valid='1' THEN -- st_histogram_snk_in.valid='1' THEN  -- maybe needs init_cnt_start = '1' instead?
-        IF prev_unvalid = '0' THEN
-          st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_snk_in.data(g_data_w-1 DOWNTO 0), 1);
-        ELSIF prev_unvalid = '1' THEN
-          st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_snk_in.data(g_data_w-1 DOWNTO 0), -1);
-          prev_unvalid <= '0';
-        END IF;
-      ELSIF rising_edge(dp_clk) AND pre_valid='0' AND init_phase='0' THEN -- st_histogram_snk_in.valid='0' AND init_phase = '0' THEN
-        IF prev_unvalid = '0' THEN
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_snk_in.data(g_data_w-1 DOWNTO 0), 2);
-        prev_unvalid <= '1';
-        END IF;
-      END IF;
-      
-    ELSIF g_snk_in_data_sim_type = "toggle" THEN
-      IF dp_rst='1' THEN
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= (OTHERS=>'0');
-      ELSIF rising_edge(dp_clk) AND st_histogram_snk_in.valid='1' THEN  -- maybe needs init_cnt_start = '1' instead?
-        IF st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) = TO_UVEC(0, g_data_w) THEN  -- c_adr_low
-          st_histogram_snk_in.data(c_adr_low) <= '1'; -- TO_UVEC(1, g_data_w); --g_data_w-1 DOWNTO 0
-        ELSE
-          st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= TO_UVEC(0, g_data_w);
-        END IF;
-      END IF;
-      
-    ELSIF g_snk_in_data_sim_type = "same rw" THEN
-      IF dp_rst='1' THEN
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= (OTHERS=>'0');
-      ELSIF rising_edge(dp_clk) AND pre_sync='1' THEN -- AND init_phase='0'   didn't work
-        st_histogram_snk_in.data(g_data_w-1 DOWNTO c_adr_low) <= TO_UVEC(c_srw_arr(srw_index_cnt), c_adr_w); --placeholder !
-        IF srw_index_cnt = c_srw_arr'LENGTH -1 THEN
-          srw_index_cnt <= 0;
-        ELSE
-          srw_index_cnt <= srw_index_cnt+1;
-        END IF;
-      END IF;
-      
-    ELSIF g_snk_in_data_sim_type = "mix" THEN
-      IF toggle_start = '1' THEN
-        -- toggle part
-          IF dp_rst='1' THEN
-          st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= (OTHERS=>'0');
-        ELSIF rising_edge(dp_clk) AND st_histogram_snk_in.valid='1' THEN  -- maybe needs init_cnt_start = '1' instead?
-          IF st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) = TO_UVEC(0, g_data_w) THEN  -- c_adr_low
-            st_histogram_snk_in.data(c_adr_low) <= '1'; -- TO_UVEC(1, g_data_w); --g_data_w-1 DOWNTO 0
-          ELSE
-            st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= TO_UVEC(0, g_data_w);
-          END IF;
-        END IF;
-        -- end toggle part
-      ELSE
-        -- counter part
-        IF dp_rst='1' THEN
-          st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= (OTHERS=>'0');
-        ELSIF rising_edge(dp_clk) AND pre_valid='1' THEN -- st_histogram_snk_in.valid='1' THEN  -- maybe needs init_cnt_start = '1' instead?
-          IF prev_unvalid = '0' THEN
-            st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_snk_in.data(g_data_w-1 DOWNTO 0), 1);
-          ELSIF prev_unvalid = '1' THEN
-            st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_snk_in.data(g_data_w-1 DOWNTO 0), -1);
-            prev_unvalid <= '0';
-          END IF;
-        ELSIF rising_edge(dp_clk) AND pre_valid='0' AND init_phase='0' THEN -- st_histogram_snk_in.valid='0' AND init_phase = '0' THEN
-          IF prev_unvalid = '0' THEN
-            st_histogram_snk_in.data(g_data_w-1 DOWNTO 0) <= INCR_UVEC(st_histogram_snk_in.data(g_data_w-1 DOWNTO 0), 2);
-            prev_unvalid <= '1';
-          END IF;
-        END IF;
-        -- end counter part
-      END IF;
-    END IF;
-  END PROCESS;
-  
-  
-  p_stimuli : PROCESS
+  -- Generate g_nof_sync packets of g_nof_data_per_sync words
+  p_generate_packets : PROCESS
+    VARIABLE v_sosi : t_dp_sosi := c_dp_sosi_rst;
   BEGIN
-    IF g_valid_gap = "false" THEN
-    
-      -- initializing
-      st_histogram_snk_in.sync <= '0';
-      st_histogram_snk_in.valid <= '0';
-      WAIT UNTIL rising_edge(dp_clk);
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      pre_valid <= '1';
-      st_histogram_snk_in.valid <= '1';
-      -- generating g_nof_sync sync pulses with g_sync_length cycles between
-      FOR I IN 0 TO g_nof_sync-1 LOOP
-        toggle_start <= '1';
-        st_histogram_snk_in.sync <= '1';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.sync <= '0';
-        proc_common_wait_some_cycles(dp_clk, 2);
-        toggle_start <= '0';
-        FOR I IN 0 TO g_sync_length-1 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP; -- -4 ipv -1 ?
-      END LOOP;
-      -- ending
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      tb_end <= '1';
-      WAIT;
-      
-    ELSIF g_valid_gap = "true" THEN
-    
-      -- initializing
-      st_histogram_snk_in.sync <= '0';
-      st_histogram_snk_in.valid <= '0';
-      WAIT UNTIL rising_edge(dp_clk);
-      FOR I IN 0 TO 8 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      pre_sync <= '1';
-      WAIT UNTIL rising_edge(dp_clk);
-      pre_valid <= '1';
-      st_histogram_snk_in.valid <= '1';
-      -- generating g_nof_sync-1 sync pulses with gaps in 'valid'
-      FOR I IN 0 TO g_nof_sync-2 LOOP
-        toggle_start <= '1';
-        st_histogram_snk_in.sync <= '1';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.sync <= '0';
-        proc_common_wait_some_cycles(dp_clk, 2);
-        toggle_start <= '0';
-        FOR I IN 0 TO (g_sync_length/2)-5 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP; -- -5 ipv -2 ?
-        pre_valid <= '0';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.valid <= '0';
-        pre_valid <= '1';                 -- gap 1 clock cycles
-        WAIT UNTIL rising_edge(dp_clk);
-        --WAIT UNTIL rising_edge(dp_clk); -- gap 2 clock cycles
-        --WAIT UNTIL rising_edge(dp_clk); -- gap 3 clock cycles
-        st_histogram_snk_in.valid <= '1';
-        FOR I IN 0 TO (g_sync_length/4)-2 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-        pre_valid <= '0';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.valid <= '0';
-        WAIT UNTIL rising_edge(dp_clk);
-        --st_histogram_snk_in.valid <= '0'; -- gap while sync --should not happen, impossible
-        st_histogram_snk_in.sync <= '1';
-        pre_valid <= '1';
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.valid <= '1';
-        st_histogram_snk_in.sync <= '0';
-        FOR I IN 0 TO (g_sync_length/4)-1 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      END LOOP;
-      -- ending
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      tb_end <= '1';
-      WAIT;
-      
-    ELSIF g_valid_gap = "custom" THEN
-      
-      -- initializing
-      st_histogram_snk_in.sync <= '0';
-      st_histogram_snk_in.valid <= '0';
-      WAIT UNTIL rising_edge(dp_clk);
-      FOR I IN 0 TO 8 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      pre_sync <= '1';
-      WAIT UNTIL rising_edge(dp_clk);
-      pre_valid <= '1';
- --     st_histogram_snk_in.valid <= '1';
-      -- generating g_nof_sync-1 sync pulses with gaps in 'valid'
-      FOR I IN 0 TO g_nof_sync-2 LOOP
-        toggle_start <= '1';
-        st_histogram_snk_in.sync <= '1';
-        st_histogram_snk_in.valid <= STD_LOGIC( TO_UNSIGNED(c_val_arr(0),1)(0) ); -- TO_UVEC(c_val_arr(0), c_adr_w); --placeholder !
-        WAIT UNTIL rising_edge(dp_clk);
-        st_histogram_snk_in.sync <= '0';
-        FOR I IN 1 TO c_val_arr'LENGTH -1 LOOP
-          st_histogram_snk_in.valid <= STD_LOGIC( TO_UNSIGNED( c_val_arr(I) ,1)(0) ); -- TO_UVEC(c_val_arr(J), c_adr_w);
-          dbg_valid <= I;
-          WAIT UNTIL rising_edge(dp_clk);
-        END LOOP;
-        proc_common_wait_some_cycles(dp_clk, (g_sync_length - (c_val_arr'LENGTH -2) )); --the -2 has to be ditched as the sync happens 2 cycles to soon
-      END LOOP;
-      -- ending
-      FOR I IN 0 TO 9 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
-      tb_end <= '1';
-      WAIT;
-    END IF;
+    stimuli_src_out <= c_dp_sosi_rst;
+    proc_common_wait_until_low(dp_clk, dp_rst);
+    proc_common_wait_some_cycles(dp_clk, 5);
+
+    FOR I IN 0 TO g_nof_sync-1 LOOP
+      v_sosi.sync    := '1';
+      v_sosi.data    := RESIZE_DP_DATA(v_sosi.data(g_data_w-1 DOWNTO 0));  -- wrap when >= 2**g_data_w    
+      proc_dp_gen_block_data(g_data_w, TO_UINT(v_sosi.data), g_nof_data_per_sync, TO_UINT(v_sosi.channel), TO_UINT(v_sosi.err), v_sosi.sync, v_sosi.bsn, dp_clk, stimuli_en, stimuli_src_in, stimuli_src_out);
+    END LOOP;     
+
+    proc_common_wait_some_cycles(dp_clk, 50);
+    tb_end <= '1';
+    WAIT;
   END PROCESS;
-  
-  
-  
---  p_mm_stimuli : PROCESS --(st_histogram_snk_in.sync)
---  BEGIN
---    st_histogram_ram_mosi <= c_mem_mosi_rst;  --.address(c_adr_w-1 DOWNTO 0) <= (OTHERS=>'0');
---    WAIT UNTIL st_histogram_snk_in.sync = '1';
---    -- wait till one RAM block is written
---    FOR I IN 0 TO (g_sync_length) LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
---    -- wait for some more cycles
---    FOR I IN 0 TO 2 LOOP WAIT UNTIL rising_edge(dp_clk); END LOOP;
---    -- read all bins
---    FOR I IN 0 TO g_nof_bins-1 LOOP
---      proc_mem_mm_bus_rd(I, dp_clk, st_histogram_ram_mosi);
---      proc_common_wait_some_cycles(dp_clk, 1);
---    END LOOP;
---  END PROCESS;
-  
+ 
+
   ----------------------------------------------------------------------------
-  -- DUT: Device Under Test
+  -- st_histogram
   ----------------------------------------------------------------------------
-  
-  u_st_histogram : ENTITY work.st_histogram --_8_april
+  st_histogram_snk_in <= stimuli_src_out;
+
+  u_st_histogram : ENTITY work.st_histogram
   GENERIC MAP(
-    g_in_data_w         => g_data_w,
+    g_data_w            => g_data_w,
     g_nof_bins          => g_nof_bins,
-    g_nof_data          => g_nof_data,
-    g_ram_miso_sim_mode => FALSE         -- TRUE
+    g_nof_data_per_sync => g_nof_data_per_sync
   )
   PORT MAP (
+    dp_clk       => dp_clk,           
     dp_rst       => dp_rst,
-    dp_clk       => dp_clk,
-             
-    -- Streaming
+
     snk_in       => st_histogram_snk_in,
   
-    -- Memory Mapped
-    sla_in_ram_mosi     => c_mem_mosi_rst,-- sla_in_
-    sla_out_ram_miso     => st_histogram_ram_miso, --OPEN -- sla_out_
-    dbg_ram_miso        => st_histogram_dbg_ram_miso
+    ram_mosi     => st_histogram_ram_mosi,
+    ram_miso     => st_histogram_ram_miso
   );
-  
-  
-  
-  ----------------------------------------------------------------------------
-  -- Selfcheck:
-  --  The selfcheck is done by counting the adresses created from 3 cycles 
-  --  delayed snk_in data into an address separated array (when in the array, 
-  --  the data is 4 cycles delayed). This data is used as reference for 
-  --  comparing it with the data written into a RAM block in st_histogram. 
-  --  Because the data in st_histogram is written 4 cycles later than it got 
-  --  in, both data are in sync and can be compared directly. 
-  --  When the data is valid but is not the same as the reference data the 
-  --  debug signal dbg_error_location becomes '1' so the location can be 
-  --  easily spotted in the wave window and a report is made.
+
   ----------------------------------------------------------------------------
-  
-  
-  u_dp_pipeline_st_histogram_snk_in_3_cycle : ENTITY dp_lib.dp_pipeline
-  GENERIC MAP (
-    g_pipeline   => 3  -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    rst          => dp_rst,
-    clk          => dp_clk,
-    snk_in       => st_histogram_snk_in,
-    src_out      => st_histogram_snk_in_ppp
-  );
-  
-  u_dp_pipeline_st_histogram_snk_in_4_cycle : ENTITY dp_lib.dp_pipeline
-  GENERIC MAP (
-    g_pipeline   => 4  -- 0 for wires, > 0 for registers, 
-  )
-  PORT MAP (
-    rst          => dp_rst,
-    clk          => dp_clk,
-    snk_in       => st_histogram_snk_in,
-    src_out      => st_histogram_snk_in_pppp
-  );
-  
-  ---------------------------------------
-  -- create address from the source data 
-  check_adr <= TO_UINT( st_histogram_snk_in_ppp.data(g_data_w-1 DOWNTO c_adr_low) );
---  dbg_check_adr <= st_histogram_snk_in_ppp.data(g_data_w -1 DOWNTO c_adr_low);
-  
-  p_prev_check_adr : PROCESS (dp_rst, dp_clk, check_adr)
+  -- Readout and verification of RAM contents
+  -- . The table below shows what RAM we are reading here ('RAM read') via the
+  --   ram_mosi/miso interface, and what the expected RAM contents are.
+  --                                         
+  ---+-------------+-------------+----------+--------------+ 
+  -- | Sync period | RAM written | RAM read | RAM contents |
+  -- +-------------+-------------+----------+--------------+
+  -- | 0           | 0           | 1        | 256 * 0      |
+  -- | 1           | 1           | 0        | 256 * 12     |
+  -- | 2           | 0           | 1        | 256 * 12     |
+  -- | 3           | 1           | 0        | 256 * 12     |
+  -- +-------------+-------------+----------+--------------+
+  -- 
+  ----------------------------------------------------------------------------
+  -- Perform MM read and put result in ram_rd_word
+  p_verify_mm_read : PROCESS
   BEGIN
-    IF dp_rst='1' THEN
-      prev_check_adr <= 0;
-    ELSIF rising_edge(dp_clk) THEN
-      prev_check_adr <= check_adr;
-    END IF;
-  END PROCESS;
-  
-  -----------------------------
-  -- when valid increase array based on address 
-  nxt_check_arr_cnt <= data_check_arr(check_adr) + 1 WHEN st_histogram_snk_in_ppp.valid = '1' ELSE data_check_arr(check_adr);
-  
-  
-  --------------------
-  -- filling the array
-  p_cumulate_testdata : PROCESS (dp_rst, dp_clk, nxt_check_arr_cnt, check_adr, st_histogram_snk_in_ppp.sync) --misses prev_check_adr
-  BEGIN 
-    --PROCESS
-    --c_data_check_arr(check_adr) <= nxt_check_arr_cnt;
-    IF dp_rst='1' THEN
-    data_check_arr(0 TO g_nof_bins) <= (OTHERS => 0);
-    ELSIF rising_edge(dp_clk) THEN
-      --data_check_arr(prev_check_adr) <= nxt_check_arr_cnt;
-      data_check_arr(check_adr) <= nxt_check_arr_cnt; --old timing
-      IF st_histogram_snk_in_ppp.sync='1' THEN
-        data_check_arr(0 TO g_nof_bins) <= (check_adr => 1, OTHERS => 0 );  -- null except check_adr
-        --
-      END IF;
-    END IF; 
+    st_histogram_ram_mosi.wr <= '0';
+    FOR i IN 0 TO g_nof_sync-1 LOOP
+      proc_common_wait_until_high(dp_clk, stimuli_src_out.sync);  -- Wait for sync
+      proc_common_wait_some_cycles(dp_clk, 10); -- give it a couple of more cycles
+      FOR j IN 0 TO g_nof_bins-1 LOOP
+        proc_mem_mm_bus_rd(j, dp_clk, st_histogram_ram_mosi); 
+        ram_rd_word <= st_histogram_ram_miso.rddata(c_ram_dat_w-1 DOWNTO 0);
+        ram_rd_word_int <= TO_UINT(ram_rd_word);
+      END LOOP;
+    END LOOP;
   END PROCESS;
-  
-  ---------------------
-  -- extra dbg signals 
-  dbg_int_data_miso <= TO_UINT(st_histogram_dbg_ram_miso.rddata);
-  dbg_int_data_arr <= data_check_arr(prev_check_adr);
-  
-  ---------------------
-  -- selftest
---  p_selfcheck : PROCESS (dp_rst, dp_clk, data_check_arr, prev_check_adr, st_histogram_dbg_ram_miso.rddata)
---  BEGIN 
---    --PROCESS
---    -- compare cumulated testdata with ram_mosi
---    
---    --dbg_int_data_miso <= TO_UINT(st_histogram_dbg_ram_miso.rddata);
---    --dbg_int_data_arr <= data_check_arr(check_adr);
---    IF rising_edge(dp_clk) THEN
---      --dbg_error_location <= '0';
---      --dbg_int_data_miso <= TO_UINT(st_histogram_dbg_ram_miso.rddata);
---      --dbg_int_data_arr <= data_check_arr(check_adr);
---      IF data_check_arr(prev_check_adr) /= TO_UINT(st_histogram_dbg_ram_miso.rddata) AND st_histogram_snk_in_pppp.valid='1' THEN
---        dbg_error_location <= '1';
---        REPORT "The value written to the RAM is not what it should be. See signal 'dbg_int_data_arr'. The failure concerns the bin (and array) address: " &integer'image(prev_check_adr) SEVERITY ERROR;
---        error_cnt <= error_cnt + 1;
---      ELSE
---        dbg_error_location <= '0';
---      END IF;
---    END IF;
---
-----    IF dp_rst='1' THEN
-----    data_check_arr(0 TO g_nof_bins) <= (OTHERS => 0);
-----    ELSIF rising_edge(dp_clk) THEN
-----      data_check_arr(check_adr) <= nxt_check_arr_cnt;
-----    END IF; 
---  END PROCESS;
-
-  
-  -- show the location of an error after a small delay (to prevent spikes) when the data written is not the same as the reference and only when the data was initially valid. Do not allow to be triggered at the testbench end.
-  dbg_error_location <= '1' AFTER c_dp_clk_period/5 WHEN ( (data_check_arr(prev_check_adr) /= TO_UINT(st_histogram_dbg_ram_miso.rddata) ) AND st_histogram_snk_in_pppp.valid='1' AND tb_end='0' ) ELSE '0';
-  ASSERT dbg_error_location='0' REPORT "The value written to the RAM is not what it should be. Comparison failed on (bin and array) address: " &integer'image(prev_check_adr) SEVERITY ERROR;
-  
 
-  --error count
-  p_count_total_error_cnt : PROCESS (dp_clk, dbg_error_location)
+  -- Register st_histogram_ram_miso.rdval so we read only valid ram_rd_word
+  p_nxt_ram_rd_word_valid : PROCESS(dp_rst, dp_clk)
   BEGIN
-    IF dp_rst='1' THEN
-      error_cnt <= 0;
-    ELSIF dbg_error_location='1' AND tb_end='0' AND rising_edge(dp_clk) THEN
-      error_cnt <= error_cnt + 1;
+   IF dp_rst = '1' THEN
+      ram_rd_word_valid <= '0';     
+    ELSIF RISING_EDGE(dp_clk) THEN
+      ram_rd_word_valid <= nxt_ram_rd_word_valid;
     END IF;
   END PROCESS;
+  nxt_ram_rd_word_valid <= st_histogram_ram_miso.rdval;
 
-  p_view_total_error_cnt : PROCESS (tb_end, error_cnt)
+  -- Perform verification of ram_rd_word when ram_rd_word_valid
+  p_verify_assert : PROCESS
   BEGIN
-    IF tb_end='1' AND error_cnt>0 THEN
-      REPORT "When comparing there were " &integer'image(error_cnt) &" cycles where the value in the RAM address was not the value expected" SEVERITY ERROR;
-    END IF;
+    FOR i IN 0 TO g_nof_sync-1 LOOP
+      proc_common_wait_until_high(dp_clk, stimuli_src_out.sync);  
+      proc_common_wait_until_high(dp_clk, ram_rd_word_valid);      
+      IF i=0 THEN -- Sync period 0: we expect RAM to contain zeros
+        ASSERT ram_rd_word_int=0                      REPORT "RAM contains wrong bin count (expected 0, actual " & INTEGER'IMAGE(ram_rd_word_int) & ")" SEVERITY ERROR;
+      ELSE -- Sync period 1 onwards
+        ASSERT ram_rd_word_int=c_expected_ram_content REPORT "RAM contains wrong bin count (expected " & INTEGER'IMAGE(c_expected_ram_content) & ", actual " & INTEGER'IMAGE(ram_rd_word_int) & ")" SEVERITY ERROR;
+      END IF;
+    END LOOP;
+    WAIT FOR 5 ns;
   END PROCESS;
   
 END tb;
diff --git a/libraries/dsp/st/tb/vhdl/tb_tb_st_histogram.vhd b/libraries/dsp/st/tb/vhdl/tb_tb_st_histogram.vhd
index 15c4f2fddae29e9d2f00dd172de76c904ecff142..12b4b26876a53513ce6aff00a12b0ab19d15f05f 100644
--- a/libraries/dsp/st/tb/vhdl/tb_tb_st_histogram.vhd
+++ b/libraries/dsp/st/tb/vhdl/tb_tb_st_histogram.vhd
@@ -18,12 +18,14 @@
 --
 -------------------------------------------------------------------------------
 
--------------------------------------------------------------------------------
--- 
--- Author: J.W.E. Oudman
+-- Author:
+-- . Daniel van der Schuur
 -- Purpose:
--- Description: 
--- .
+-- . Test tb_st_histogram in with several parameter sets
+-- Usage
+-- . as 8
+-- . run -all 
+-- . Testbenches are self-checking
 
 LIBRARY IEEE;
 USE IEEE.std_logic_1164.ALL;
@@ -34,30 +36,17 @@ END tb_tb_st_histogram;
 ARCHITECTURE tb OF tb_tb_st_histogram IS
   SIGNAL tb_end : STD_LOGIC := '0';  -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
 BEGIN
+  
+--  g_nof_sync             : NATURAL := 4;
+--  g_data_w               : NATURAL := 8;
+--  g_nof_bins             : NATURAL := 256;
+--  g_nof_data             : NATURAL := 1024;
+
+u_tb_st_histogram_0 : ENTITY work.tb_st_histogram GENERIC MAP ( 7,  8,  256, 1024); -- Incoming data wraps (repeats) 1024/ 256= 4 times: Bin count =  4
+u_tb_st_histogram_1 : ENTITY work.tb_st_histogram GENERIC MAP ( 6, 10,  256, 4096); -- Incoming data wraps (repeats) 4096/ 256=16 times: Bin count = 16
+u_tb_st_histogram_2 : ENTITY work.tb_st_histogram GENERIC MAP ( 5, 12,  512, 4096); -- Incoming data wraps (repeats) 4096/ 512= 8 times: Bin count =  8
+u_tb_st_histogram_3 : ENTITY work.tb_st_histogram GENERIC MAP ( 4, 13, 1024, 8192); -- Incoming data wraps (repeats) 8192/1024= 8 times: Bin count =  8
+u_tb_st_histogram_4 : ENTITY work.tb_st_histogram GENERIC MAP (40,  6,   64,  128); -- Incoming data wraps (repeats)  128/  64= 2 times: Bin count =  2
 
--- Usage
---   > as 8
---   > run -all 
---   > Testbenches are self-checking
-
---    
---  g_sync_length          : NATURAL := 200;
---  g_nof_sync             : NATURAL := 3;
---  g_data_w               : NATURAL := 4;
---  g_nof_bins             : NATURAL := 8;
---  g_nof_data             : NATURAL := 200;
---  --g_str                  : STRING  := "freq.density";
---  g_valid_gap            : STRING  := "custom";  -- "false" or "true" or "custom"
---  g_snk_in_data_sim_type : STRING  := "same rw"  -- "counter" or "toggle" or "same rw" or "mix"
---
-
--- do test for different number of bins 
-u_tb_st_histogram_counter_nof_2 : ENTITY work.tb_st_histogram GENERIC MAP (200, 3, 1, 2, 200, "true"  , "counter" );
-u_tb_st_histogram_counter_nof_4 : ENTITY work.tb_st_histogram GENERIC MAP (200, 3, 2, 4, 200, "true"  , "counter" );
-u_tb_st_histogram_counter       : ENTITY work.tb_st_histogram GENERIC MAP (200, 3, 4, 8, 200, "true"  , "counter" );
-
--- do tests for RAM delay issues
-u_tb_st_histogram_toggle        : ENTITY work.tb_st_histogram GENERIC MAP (200, 3, 4, 8, 200, "true"  , "toggle"  );
-u_tb_st_histogram_same_rw       : ENTITY work.tb_st_histogram GENERIC MAP (200, 3, 4, 8, 200, "custom", "same rw" );
 
 END tb;