Skip to content
Snippets Groups Projects
Code owners
Assign users and groups as approvers for specific file changes. Learn more.
dp_block_validate_err.vhd 12.77 KiB
-------------------------------------------------------------------------------
--
-- Copyright 2021
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- Licensed under the Apache License, Version 2.0 (the "License");
-- you may not use this file except in compliance with the License.
-- You may obtain a copy of the License at
--
--     http://www.apache.org/licenses/LICENSE-2.0
--
-- Unless required by applicable law or agreed to in writing, software
-- distributed under the License is distributed on an "AS IS" BASIS,
-- WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-- See the License for the specific language governing permissions and
-- limitations under the License.
--
-------------------------------------------------------------------------------

-------------------------------------------------------------------------------
-- Author: R vd Walle
-- Purpose:
--   Validate the error field of a DP block.
-- Description:
--  . The dp_block_validate_err.vhd checks the in_sosi.err field at the end of a
--    block. Therefore the block needs to be stored, before it can be validated. 
--    The stored block is then either forwarded when the in_sosi.err = 0, or else 
--    it is discarded. 
--  . The dp_block_validate_err.vhd has to maintain the a total number of in_sosi 
--    blocks counter and a number of discarded blocks counter per bit in the 
--    in_sosi.err field. The counters can be read via the MM interface. 
-- Remarks:
--   . Note that a block can have more than one bit set in the err field. This can
--     result in multiple counters increasing per block. Therefore, it should not be 
--     assumed that the sum of the err counters is the total amount of discarded
--     blocks.
--   . g_max/min_block_size indicate the minimum / maximum length of incoming blocks.
--     The ratio of max / min is used to determine a fifo size for the outgoing
--     sosi.valid signals. To minimize logic the g_min_block_size can be set to
--     the expected minimum block size.
--   . g_fifo_size can be set to g_max_block_size if there is no backpressure.
--     If there is back pressure on the src_in, the fifo_fill_eop can be used to 
--     to account for this backpressure by using an g_fifo_size > g_max_block_size.
-------------------------------------------------------------------------------
-- REGMAP
-------------------------------------------------------------------------------
--  wi                  Bits    R/W Name                                 Default                                         
--  ====================================================================================
--  0                   [31..0] RO  err_count_index_0                     0x0    
--  1                   [31..0] RO  err_count_index_1                     0x0   
--  .                    .      .   .                                     . 
--  .                    .      .   .                                     . 
--  .                    .      .   .                                     . 
--  g_nof_err_counts-1  [31..0] RO  err_count_index_[g_nof_err_counts-1]  0x0           
--  g_nof_err_counts    [31..0] RO  total_discarded_blocks                0x0           
--  g_nof_err_counts+1  [31..0] RO  total_block_count                     0x0           
--  g_nof_err_counts+2  [31..0] RW  clear                                 0x0 read or write to clear counters
--  ====================================================================================
-------------------------------------------------------------------------------
LIBRARY IEEE, common_lib;
USE IEEE.std_logic_1164.all;
USE IEEE.numeric_std.all;
USE work.dp_stream_pkg.ALL;
USE common_lib.common_pkg.ALL;
USE common_lib.common_mem_pkg.ALL;

ENTITY dp_block_validate_err IS
  GENERIC (
    g_cnt_w              : NATURAL  := c_word_w; -- max is c_word_w due to mm word width
    g_max_block_size     : POSITIVE := 250; -- largest possible incoming block size.
    g_min_block_size     : POSITIVE := 1;   -- smallest possible incoming block size.
    g_nof_err_counts     : NATURAL  := 8;
    -- fifo generics
    g_fifo_size          : POSITIVE := 256; -- fifo size to buffer incoming blocks, should be >= g_max_block_size 
    g_data_w             : NATURAL  := 16;
    g_bsn_w              : NATURAL  := 1;
    g_empty_w            : NATURAL  := 1;
    g_channel_w          : NATURAL  := 1;
    g_use_bsn            : BOOLEAN  := FALSE;
    g_use_empty          : BOOLEAN  := FALSE;
    g_use_channel        : BOOLEAN  := FALSE;
    g_use_sync           : BOOLEAN  := FALSE;
    g_use_complex        : BOOLEAN  := FALSE
  );
  PORT (
    dp_rst       : IN  STD_LOGIC;
    dp_clk       : IN  STD_LOGIC;
    -- ST sink
    snk_out      : OUT t_dp_siso := c_dp_siso_rdy;
    snk_in       : IN  t_dp_sosi;
    -- ST source
    src_in       : IN  t_dp_siso := c_dp_siso_rdy;
    src_out      : OUT t_dp_sosi;

    mm_rst       : IN  STD_LOGIC;
    mm_clk       : IN  STD_LOGIC;

    reg_mosi     : IN  t_mem_mosi := c_mem_mosi_rst;
    reg_miso     : OUT t_mem_miso := c_mem_miso_rst
  );
END dp_block_validate_err;

ARCHITECTURE rtl OF dp_block_validate_err IS

  CONSTANT c_max_cnt    : STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0) := (OTHERS => '1');
  CONSTANT c_nof_err_ok : NATURAL := ceil_div(g_max_block_size, g_min_block_size);
  CONSTANT c_nof_regs   : NATURAL := g_nof_err_counts + 3;
  CONSTANT c_clear_adr  : NATURAL := c_nof_regs-1;

  TYPE t_cnt_err_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0);

  -- Define the actual size of the MM slave register
  CONSTANT c_mm_reg : t_c_mem := (latency  => 1,
                                  adr_w    => ceil_log2(c_nof_regs),
                                  dat_w    => c_word_w,       -- Use MM bus data width = c_word_w = 32 for all MM registers
                                  nof_dat  => c_nof_regs,
                                  init_sl  => '0');

  -- Registers in st_clk domain
  SIGNAL count_reg     : STD_LOGIC_VECTOR(c_mm_reg.nof_dat*c_mm_reg.dat_w-1 DOWNTO 0) := (OTHERS=>'0');

  SIGNAL nxt_cnt_en       : STD_LOGIC;
  SIGNAL cnt_en           : STD_LOGIC := '0';
  SIGNAL cnt_this_eop     : STD_LOGIC;

  SIGNAL mm_cnt_clr       : STD_LOGIC;
  SIGNAL cnt_clr          : STD_LOGIC;
  SIGNAL cnt_blk          : STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0);
  SIGNAL cnt_blk_en       : STD_LOGIC;
  SIGNAL cnt_discarded    : STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0);
  SIGNAL cnt_discarded_en : STD_LOGIC;
  SIGNAL cnt_err_arr      : t_cnt_err_arr(g_nof_err_counts-1 DOWNTO 0);
  SIGNAL cnt_err_en_arr   : STD_LOGIC_VECTOR(g_nof_err_counts-1 DOWNTO 0);

  SIGNAL hold_cnt_blk        : STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0);
  SIGNAL hold_cnt_discarded  : STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0);
  SIGNAL hold_cnt_err_arr    : t_cnt_err_arr(g_nof_err_counts-1 DOWNTO 0);

  SIGNAL err_ok          : STD_LOGIC;
  SIGNAL err_ok_reg      : STD_LOGIC;
  SIGNAL fifo_err_ok     : STD_LOGIC;
  SIGNAL fifo_err_ok_val : STD_LOGIC;
  SIGNAL out_valid       : STD_LOGIC;
  SIGNAL out_valid_reg   : STD_LOGIC;

  SIGNAL block_sosi       : t_dp_sosi;
  SIGNAL block_siso       : t_dp_siso;
  SIGNAL block_sosi_piped : t_dp_sosi;
  
BEGIN
 
  mm_cnt_clr <= (reg_mosi.rd OR reg_mosi.wr) WHEN TO_UINT(reg_mosi.address(c_mm_reg.adr_w-1 DOWNTO 0)) = c_clear_adr ELSE '0' ;
  u_common_spulse : ENTITY common_lib.common_spulse
    PORT MAP (
      in_rst    => mm_rst,
      in_clk    => mm_clk,
      in_pulse  => mm_cnt_clr,
      out_rst   => dp_rst,
      out_clk   => dp_clk,
      out_pulse => cnt_clr
    );

  -- . clear block counters immediately at cnt_clr
  -- . start block counters after sync, e.g. to align block counters in different nodes in
  --   case the snk_in was (already) active during the cnt_clr
  nxt_cnt_en <= '0' WHEN cnt_clr = '1' ELSE '1' WHEN snk_in.sync = '1' ELSE cnt_en;
  cnt_en <= nxt_cnt_en WHEN rising_edge(dp_clk);
  cnt_this_eop <= cnt_en AND snk_in.eop;

  -- block counter
  cnt_blk_en <= cnt_this_eop;
  u_blk_counter : ENTITY common_lib.common_counter
  GENERIC MAP (
    g_width => g_cnt_w,
    g_clip  => TRUE
  )
  PORT MAP ( 
    rst => dp_rst,
    clk => dp_clk,

    cnt_clr => cnt_clr, 
    cnt_en  => cnt_blk_en,
    count   => cnt_blk
  );

  -- discarded block counter
  cnt_discarded_en <= cnt_this_eop WHEN TO_UINT(snk_in.err(g_nof_err_counts-1 DOWNTO 0)) > 0 ELSE '0';
  u_discarded_counter : ENTITY common_lib.common_counter
  GENERIC MAP (
    g_width => g_cnt_w,
    g_clip  => TRUE
  )
  PORT MAP ( 
    rst => dp_rst,
    clk => dp_clk,

    cnt_clr => cnt_clr, 
    cnt_en  => cnt_discarded_en,
    count   => cnt_discarded
  );

  -- error counters
  gen_err_counters : FOR I IN 0 TO g_nof_err_counts-1 GENERATE
    cnt_err_en_arr(I) <= cnt_this_eop AND snk_in.err(I);
    u_blk_counter : ENTITY common_lib.common_counter
    GENERIC MAP (
      g_width => g_cnt_w,
      g_clip  => TRUE
    )
    PORT MAP ( 
      rst => dp_rst,
      clk => dp_clk,
  
      cnt_clr => cnt_clr, 
      cnt_en  => cnt_err_en_arr(I),
      count   => cnt_err_arr(I)
    );
  END GENERATE;

  -- Hold counter values at snk_in.sync to have stable values for MM read for comparision between nodes
  p_hold_counters : PROCESS(dp_clk)
  BEGIN
    IF rising_edge(dp_clk) THEN
      IF cnt_clr = '1' THEN
        hold_cnt_blk <= (OTHERS=>'0');
        hold_cnt_discarded <= (OTHERS=>'0');
        hold_cnt_err_arr <= (OTHERS=>(OTHERS=>'0'));
      ELSIF snk_in.sync = '1' THEN
        hold_cnt_blk <= cnt_blk;
        hold_cnt_discarded <= cnt_discarded;
        hold_cnt_err_arr <= cnt_err_arr;
      END IF;
    END IF;
  END PROCESS;

  -- Register mapping
  gen_reg : FOR I IN 0 TO g_nof_err_counts-1 GENERATE
    count_reg((I + 1) * c_word_w - 1 DOWNTO I * c_word_w) <= RESIZE_UVEC(hold_cnt_err_arr(I), c_word_w);
  END GENERATE;
  count_reg((g_nof_err_counts+1) * c_word_w - 1 DOWNTO  g_nof_err_counts    * c_word_w ) <= RESIZE_UVEC(hold_cnt_discarded, c_word_w);
  count_reg((g_nof_err_counts+2) * c_word_w - 1 DOWNTO (g_nof_err_counts+1) * c_word_w ) <= RESIZE_UVEC(hold_cnt_blk,       c_word_w);

  u_reg : ENTITY common_lib.common_reg_r_w_dc
  GENERIC MAP (
    g_cross_clock_domain => TRUE,
    g_readback           => FALSE,
    g_reg                => c_mm_reg
  )
  PORT MAP (
    -- Clocks and reset
    mm_rst      => mm_rst,
    mm_clk      => mm_clk,
    st_rst      => dp_rst,
    st_clk      => dp_clk,
    
    -- Memory Mapped Slave in mm_clk domain
    sla_in      => reg_mosi,
    sla_out     => reg_miso,
    
    -- MM registers in st_clk domain
    reg_wr_arr  => OPEN,
    reg_rd_arr  => OPEN,
    in_reg      => count_reg,   -- read only
    out_reg     => OPEN       -- no write
  );

  u_fifo_fill_eop : ENTITY work.dp_fifo_fill_eop
  GENERIC MAP (
    g_data_w       => g_data_w,  
    g_bsn_w        => g_bsn_w,  
    g_empty_w      => g_empty_w,  
    g_channel_w    => g_channel_w,  
    g_use_bsn      => g_use_bsn,  
    g_use_empty    => g_use_empty,  
    g_use_channel  => g_use_channel,  
    g_use_sync     => g_use_sync,  
    g_use_complex  => g_use_complex,  
    g_fifo_fill    => g_max_block_size,  
    g_fifo_size    => g_fifo_size  
  )
  PORT MAP (
    wr_rst => dp_rst,        
    wr_clk => dp_clk,     
    rd_rst => dp_rst,     
    rd_clk => dp_clk,     
    
    -- ST sink
    snk_out => snk_out,    
    snk_in  => snk_in,    
    -- ST source
    src_in  => block_siso,    
    src_out => block_sosi  
  );

  u_pipeline : ENTITY work.dp_pipeline
  GENERIC MAP (
    g_pipeline   => 1  -- 0 for wires, > 0 for registers, 
  )
  PORT MAP (
    rst          => dp_rst,
    clk          => dp_clk,
    -- ST sink
    snk_out      => block_siso,
    snk_in       => block_sosi,
    -- ST source
    src_in       => src_in,
    src_out      => block_sosi_piped
  );

  p_dp_clk : PROCESS(dp_rst, dp_clk)
  BEGIN
    IF dp_rst='1' THEN
      err_ok_reg      <= '0';
      out_valid_reg   <= '0';
    ELSIF rising_edge(dp_clk) THEN
      err_ok_reg      <= err_ok;
      out_valid_reg   <= out_valid;
    END IF;
  END PROCESS;

  err_ok <= NOT vector_or(snk_in.err(g_nof_err_counts-1 DOWNTO 0)) WHEN snk_in.eop = '1' ELSE err_ok_reg;

  u_fifo_err_ok : ENTITY common_lib.common_fifo_sc
  GENERIC MAP (
    g_dat_w => 1,
    g_nof_words => c_nof_err_ok
  )
  PORT MAP (
    rst       => dp_rst,
    clk       => dp_clk,
    wr_dat(0) => err_ok,
    wr_req    => snk_in.eop,
    rd_req    => block_sosi.sop,
    rd_dat(0) => fifo_err_ok,
    rd_val    => fifo_err_ok_val
  );

  out_valid <= fifo_err_ok WHEN fifo_err_ok_val = '1' ELSE out_valid_reg;

  p_src_out : PROCESS(block_sosi_piped, out_valid)
  BEGIN
    src_out       <= block_sosi_piped;
    src_out.valid <= block_sosi_piped.valid AND out_valid;
    src_out.sop   <= block_sosi_piped.sop   AND out_valid;
    src_out.eop   <= block_sosi_piped.eop   AND out_valid;
    src_out.sync  <= block_sosi_piped.sync  AND out_valid;
  END PROCESS;
  
END rtl;