Skip to content
Snippets Groups Projects
Code owners
Assign users and groups as approvers for specific file changes. Learn more.
st_histogram_8_april.vhd 17.22 KiB

-- 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         
  );                
  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 common_ram_r_w_0_miso    : t_mem_miso := c_mem_miso_rst;
  
  SIGNAL init_phase           : STD_LOGIC := '1';
  SIGNAL rd_cnt_allowed       : STD_LOGIC := '0';
  SIGNAL rd_cnt_allowed_pp    : STD_LOGIC := '0';
  SIGNAL nxt_rd_adr_cnt       : NATURAL := 0;
  SIGNAL rd_adr_cnt           : NATURAL;-- := 0;
  SIGNAL toggle_detect        : STD_LOGIC := '0';
  SIGNAL toggle_detect_pp     : STD_LOGIC;
  SIGNAL toggle_detect_false  : STD_LOGIC := '1';
--  SIGNAL nxt_toggle_adr_cnt : NATURAL := 0;
--  SIGNAL toggle_adr_cnt     : NATURAL;-- := 0;
  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 adr_w             : STD_LOGIC_VECTOR(g_in_data_w -1 DOWNTO c_adr_low);
  SIGNAL same_r_w_address     : STD_LOGIC;
  SIGNAL same_r_w_address_pp  : STD_LOGIC;
  
  --pipelined signals
  SIGNAL dp_pipeline_src_out_p    : t_dp_sosi;
  SIGNAL dp_pipeline_src_out_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
  -- . in  : snk_in          (latency: 0)
  -- . out : bin_reader_mosi (latency: 0)
  -- . out : bin_reader_mosi_pp (latency: 2)
  -- - out : rd_cnt_allowed_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); 
  
  --snk_in pipeline
  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      => dp_pipeline_src_out_p
  );
  
  init_phase <= '0' WHEN dp_pipeline_src_out_p.sync = '1';
  
  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      => dp_pipeline_src_out_pp
  );
  
  dbg_snk_data <= dp_pipeline_src_out_pp.data(g_in_data_w-1 DOWNTO 0);
  
  toggle_detect_false <= '0' WHEN dp_pipeline_src_out_pp.sync = '1';
  sync_detect <= snk_in.valid WHEN (snk_in.sync='1' OR dp_pipeline_src_out_p.sync='1' OR dp_pipeline_src_out_pp.sync='1') ELSE '0';
  
--  u_dp_sync_detect_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       => sync_detect,
--    src_out      => sync_detect_ppp
--  );
  
  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
  );
  
  --prev_bin_reader_mosi pipeline
--  u_dp_pipeline_bin_reader_mosi_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       => bin_reader_mosi,
--    src_out      => prev_bin_reader_mosi
--  );

 
  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)
  );
  
  u_common_pipeline_bin_reader_mosi_2_cycle : ENTITY common_lib.common_pipeline  -- better to pipeline prev_bin_reader_mosi??
  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)
  );
  
  u_common_pipeline_bin_reader_mosi_3_cycle : ENTITY common_lib.common_pipeline  -- better to pipeline prev_bin_reader_mosi??
  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)
  );
  
  
  --bin_reader_mosi_pp pipeline
--  u_dp_pipeline_bin_reader_mosi_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       => bin_reader_mosi,
--    src_out      => bin_reader_mosi_pp
--  );
  
--  rd_cnt_allowed <= snk_in.valid WHEN (bin_reader_mosi.address = prev_bin_reader_mosi.address AND init_phase = '0') ELSE '0'; -- AND snk_in.sync='0'
  rd_cnt_allowed <= snk_in.valid WHEN ( bin_reader_mosi.address = prev_bin_reader_mosi.address AND ( (dp_pipeline_src_out_p.sync='1' AND dp_pipeline_src_out_p.valid='1') OR (dp_pipeline_src_out_pp.sync='1' AND dp_pipeline_src_out_p.valid='1') ) )
                                 ELSE snk_in.valid WHEN (bin_reader_mosi.address = prev_bin_reader_mosi.address AND init_phase='0' AND snk_in.sync='0')
                                 ELSE '0';
  
  --rd_cnt_allowed_pp pipeline
  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
  );
  
  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') ELSE '0'; --AND (snk_in.sync='0' OR dp_pipeline_src_out_p.sync='0')
  
  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
  );
  
  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';
  
  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  : dp_pipeline_src_out_pp (latency: 2)
  -- . in  : toggle_detect_pp      (latency: 2)
  -- . in  : same_r_w_address_pp   (latency: 2)
  -- . in  : bin_reader_mosi_pp    (latency: 2)
  -- . in  : common_ram_r_w_0_miso (latency: 2)
  -- . in  : rd_cnt_allowed_pp     (latency: 2)
  -- . out : bin_writer_mosi  (latency: 3)
  -----------------------------------------------------------------------------
  p_nxt_bin_writer_mosi : PROCESS(common_ram_r_w_0_miso, common_ram_r_w_0_miso.rdval, common_ram_r_w_0_miso.rddata, 
                                  bin_reader_mosi_pp.address, toggle_detect, rd_cnt_allowed_pp, rd_adr_cnt, init_phase, prev_wrdata, prev_prev_wrdata, sync_detect_pp, same_r_w_address_pp, dp_pipeline_src_out_pp.valid) IS
  BEGIN
    nxt_bin_writer_mosi <= c_mem_mosi_rst;
    dbg_state_string <= "unv";
    IF common_ram_r_w_0_miso.rdval='1' THEN -- OR rd_cnt_allowed_pp = '1'  -- when not same as last 2 adresses
      nxt_bin_writer_mosi.wr      <= '1';
      nxt_bin_writer_mosi.wrdata  <= INCR_UVEC(common_ram_r_w_0_miso.rddata, 1); -- c_word_w); -- depends on count case -- rd_adr_cnt
      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address; --TODO: what other input do we need for this? -- becomes bin_reader_mosi.address
--      reset count? if toggle detected copy count to toggle counter
      nxt_prev_wrdata             <= TO_UINT(common_ram_r_w_0_miso.rddata) + 1;
--      nxt_rd_adr_cnt              <= 0;                                                   -- really necessary ??
      dbg_state_string <= "val";
--      IF bin_reader_mosi_pp.address = bin_reader_mosi.address THEN             -- Double implemented ?? toggle?
--        nxt_toggle_adr_cnt <= INCR_UVEC(common_ram_r_w_0_miso.rddata, 1);      -- Double implemented ??
    ELSIF toggle_detect_pp = '1' THEN -- dp_pipeline_src_out_pp: 2
      nxt_bin_writer_mosi.wr      <= '1';
      nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_prev_wrdata+1), c_mem_data_w); -- prev_wrdata + rd_adr_cnt + toggle_adr_cnt??? + 1  òf prev_prev_wrdata + 1 ??
      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
--      nxt_toggle_adr_cnt          <= 0;
      nxt_prev_wrdata             <= prev_prev_wrdata+1;
      dbg_state_string <= "td ";
      
    ELSIF rd_cnt_allowed_pp = '1' THEN
--      nxt_rd_adr_cnt              <= rd_adr_cnt + 1;                                                                                                   -- << !! is rd_adr_cnt really necessary? prev_wrdata might fulfill the need !!
      nxt_bin_writer_mosi.wr      <= '1';
--      IF sync_detect_ppp = '1' THEN
--        nxt_bin_writer_mosi.wrdata <= TO_UVEC( (rd_adr_cnt + 1), c_mem_data_w); -- snk_in.sync (impossible); dp_pipeline_src_out_p (thus 1st cnt): 2 (cnt+1?); dp_pipeline_src_out_pp (1st or maybe 2nd cnt): cnt+1
--        dbg_state_string <= "rs ";
--      ELSE 
        nxt_bin_writer_mosi.wrdata  <= TO_UVEC( (prev_wrdata + rd_adr_cnt + 1), c_mem_data_w); -- c_word_w); -- maybe RAM + cnt + 1 ??  -- only prev_wrdata + 1 necessary
        nxt_prev_wrdata             <= prev_wrdata + 1;
        dbg_state_string <= "r# ";
--      END IF;
      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
      
    ELSIF sync_detect_pp = '1' THEN -- snk_in.sync at least -- good as it is!
      nxt_bin_writer_mosi.wr      <= '1';
      nxt_bin_writer_mosi.wrdata  <= TO_UVEC(1, c_mem_data_w); -- snk_in.sync: 1; dp_pipeline_src_out_p.sync (thus new adress): 1; dp_pipeline_src_out_pp.sync (thus new adress): 1
      nxt_bin_writer_mosi.address <= bin_reader_mosi_pp.address;
--      nxt_rd_adr_cnt              <= 0;                             -- really necessary ??
      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_bin_writer_mosi : PROCESS(dp_clk, dp_rst, nxt_bin_writer_mosi, nxt_rd_adr_cnt, nxt_prev_wrdata, prev_wrdata, prev_prev_wrdata) IS
  BEGIN
    IF dp_rst = '1' THEN
       bin_writer_mosi <= c_mem_mosi_rst;
    ELSIF RISING_EDGE(dp_clk) THEN
       bin_writer_mosi <= nxt_bin_writer_mosi;
--       rd_adr_cnt      <= nxt_rd_adr_cnt;
--       toggle_adr_cnt  <= nxt_toggle_adr_cnt;
       prev_wrdata     <= nxt_prev_wrdata;
       prev_prev_wrdata<= prev_wrdata;
       prev_prev_prev_wrdata <= prev_prev_wrdata;
    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_writer_mosi      (latency: 3)
  -- . out : bin_arbiter_rd_mosi (latency: 1)
  -- .     : bin_arbiter_wr_mosi (latency: 4)
  -----------------------------------------------------------------------------
  nxt_bin_arbiter_wr_mosi <= bin_writer_mosi; --TODO - The rd and wr mosi should not have the same address.          v met 2 cycles rd mag, met 3 cycles niet, dus klopt dit wel?, moet hier niet bin_reader_mosi_pp staan? --AND !(A=B)
  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';                                                                                       -- bin_writer_mosi(adress 3cycles ago?) .address when .rd='1' ????
  nxt_bin_arbiter_rd_mosi.address <= bin_reader_mosi.address;

  p_bin_arbiter_mosi : PROCESS(dp_clk, dp_rst, nxt_bin_arbiter_wr_mosi, nxt_bin_arbiter_rd_mosi) IS
  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;


  -----------------------------------------------------------------------------
  -- 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;