Skip to content
Snippets Groups Projects
Commit 50895123 authored by Reinier van der Walle's avatar Reinier van der Walle
Browse files

finished implementing dp_block_validate_err and its tbs

parent 8a8ac77e
Branches
Tags
2 merge requests!124Resolve L2SDP-271,!123Resolve L2SDP-270
...@@ -61,6 +61,7 @@ synth_files = ...@@ -61,6 +61,7 @@ synth_files =
src/vhdl/dp_fifo_from_mm_reg.vhd src/vhdl/dp_fifo_from_mm_reg.vhd
src/vhdl/dp_fifo_monitor.vhd src/vhdl/dp_fifo_monitor.vhd
src/vhdl/dp_fifo_monitor_arr.vhd src/vhdl/dp_fifo_monitor_arr.vhd
src/vhdl/dp_block_validate_err.vhd
src/vhdl/mms_dp_fifo_to_mm.vhd src/vhdl/mms_dp_fifo_to_mm.vhd
src/vhdl/mms_dp_fifo_from_mm.vhd src/vhdl/mms_dp_fifo_from_mm.vhd
src/vhdl/mms_dp_fifo_fill.vhd src/vhdl/mms_dp_fifo_fill.vhd
...@@ -195,6 +196,7 @@ test_bench_files = ...@@ -195,6 +196,7 @@ test_bench_files =
tb/vhdl/tb_dp_block_select.vhd tb/vhdl/tb_dp_block_select.vhd
tb/vhdl/tb_dp_block_validate_length.vhd tb/vhdl/tb_dp_block_validate_length.vhd
tb/vhdl/tb_dp_block_validate_err.vhd
tb/vhdl/tb_dp_block_reshape.vhd tb/vhdl/tb_dp_block_reshape.vhd
tb/vhdl/tb_dp_block_reshape_sync.vhd tb/vhdl/tb_dp_block_reshape_sync.vhd
tb/vhdl/tb_dp_block_gen.vhd tb/vhdl/tb_dp_block_gen.vhd
...@@ -275,6 +277,7 @@ test_bench_files = ...@@ -275,6 +277,7 @@ test_bench_files =
tb/vhdl/tb_tb_dp_block_select.vhd tb/vhdl/tb_tb_dp_block_select.vhd
tb/vhdl/tb_tb_dp_block_validate_length.vhd tb/vhdl/tb_tb_dp_block_validate_length.vhd
tb/vhdl/tb_tb_dp_block_validate_err.vhd
tb/vhdl/tb_tb_dp_block_reshape.vhd tb/vhdl/tb_tb_dp_block_reshape.vhd
tb/vhdl/tb_tb_dp_block_reshape_sync.vhd tb/vhdl/tb_tb_dp_block_reshape_sync.vhd
tb/vhdl/tb_tb_dp_block_gen.vhd tb/vhdl/tb_tb_dp_block_gen.vhd
...@@ -341,6 +344,7 @@ regression_test_vhdl = ...@@ -341,6 +344,7 @@ regression_test_vhdl =
tb/vhdl/tb_tb_dp_block_select.vhd tb/vhdl/tb_tb_dp_block_select.vhd
tb/vhdl/tb_tb_dp_block_validate_length.vhd tb/vhdl/tb_tb_dp_block_validate_length.vhd
tb/vhdl/tb_tb_dp_block_validate_err.vhd
tb/vhdl/tb_tb_dp_block_reshape.vhd tb/vhdl/tb_tb_dp_block_reshape.vhd
tb/vhdl/tb_tb_dp_block_reshape_sync.vhd tb/vhdl/tb_tb_dp_block_reshape_sync.vhd
tb/vhdl/tb_tb_dp_block_gen.vhd tb/vhdl/tb_tb_dp_block_gen.vhd
......
...@@ -21,116 +21,272 @@ ...@@ -21,116 +21,272 @@
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Author: R vd Walle -- Author: R vd Walle
-- Purpose: -- Purpose:
-- Validate the length of a DP block. -- Validate the error field of a DP block.
-- Description: -- Description:
-- The dp_block_validate_length.vhd checks whether the in_sosi block has the -- . The dp_block_validate_err.vhd checks the in_sosi.err field at the end of a
-- expected length given by g_expected_length. The block length is defined by -- block. Therefore the block needs to be stored, before it can be validated.
-- the number of valid from sop to eop. The tasks of the -- The stored block is then either forwarded when the in_sosi.err = 0, or else
-- dp_block_validate_length.vhd are: -- it is discarded.
-- . Default all in_sosi fields are passed on to the out_sosi. -- . The dp_block_validate_err.vhd has to maintain the a total number of in_sosi
-- . If the input block length differs from g_expected_length, then the bit at -- blocks counter and a number of discarded blocks counter per bit in the
-- bit index g_err_bi in the out_sosi.err field is forced to 1, else the -- in_sosi.err field. The counters can be read via the MM interface.
-- out_sosi.err field passes on the in_sosi.err field.
-- . If the input block length > g_expected_length, then the out_sosi block
-- length is restricted to g_expected_length, by inserting an eop and
-- discarding the remaining data and eop information from the in_sosi.
-- Remarks: -- Remarks:
-- - This component supports flow control and was designed by keeping the functional -- . Note that a block can have more than one bit set in the err field. This can
-- state registers and the pipeline registers seperate. Therefore the function is -- result in multiple counters increasing per block. Therefore, it should not be
-- implemented using combinatorial logic and local state registers to keep its -- assumed that the sum of the err counters is the total amount of discarded
-- state. The combinatorial function output preserves the snk_in ready latency and -- blocks.
-- is pipelined using dp_pipeline to ease timing closure on the output. -- . Note that dp_fifo_fill_eop cannot handle continues stream of blocks without
-- a gap between blocks the dp_fifo_fill_eop needs 1 cycle to process a block.
-- Streaming without gaps may cause the fifo to overflow. Bursts of blocks
-- can be handled by increasing g_fifo_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_block_count 0x0
-- ====================================================================================
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
LIBRARY IEEE, common_lib; LIBRARY IEEE, common_lib;
USE IEEE.std_logic_1164.all; USE IEEE.std_logic_1164.all;
USE IEEE.numeric_std.all;
USE work.dp_stream_pkg.ALL; USE work.dp_stream_pkg.ALL;
USE common_lib.common_pkg.ALL;
USE common_lib.common_mem_pkg.ALL;
ENTITY dp_block_validate_length IS ENTITY dp_block_validate_err IS
GENERIC ( GENERIC (
g_err_bi : NATURAL := 0; -- bit index in error field g_cnt_w : NATURAL := c_word_w; -- max is c_word_w due to mm word width
g_expected_length : NATURAL := 255 g_max_block_size : POSITIVE := 250;
g_min_block_size : POSITIVE := 1;
g_nof_err_counts : NATURAL := 8;
-- fifo generics
g_fifo_size : POSITIVE := 256;
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 ( PORT (
rst : IN STD_LOGIC; dp_rst : IN STD_LOGIC;
clk : IN STD_LOGIC; dp_clk : IN STD_LOGIC;
-- ST sink -- ST sink
snk_out : OUT t_dp_siso; snk_out : OUT t_dp_siso := c_dp_siso_rdy;
snk_in : IN t_dp_sosi; snk_in : IN t_dp_sosi;
-- ST source -- ST source
src_in : IN t_dp_siso := c_dp_siso_rdy; src_in : IN t_dp_siso := c_dp_siso_rdy;
src_out : OUT t_dp_sosi 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_length; END dp_block_validate_err;
ARCHITECTURE rtl OF dp_block_validate_err IS
LIBRARY IEEE, common_lib; CONSTANT c_max_cnt : STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0) := (OTHERS => '1');
USE IEEE.std_logic_1164.all; CONSTANT c_nof_err_ok : NATURAL := ceil_div(g_max_block_size, g_min_block_size);
USE work.dp_stream_pkg.ALL;
TYPE t_cnt_err_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0);
ARCHITECTURE rtl OF dp_block_validate_length IS -- Define the actual size of the MM slave register
CONSTANT c_mm_reg : t_c_mem := (latency => 1,
adr_w => ceil_log2(g_nof_err_counts+1),
dat_w => c_word_w, -- Use MM bus data width = c_word_w = 32 for all MM registers
nof_dat => g_nof_err_counts+1,
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 cnt_clr : STD_LOGIC;
SIGNAL cnt_blk : STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0);
SIGNAL cnt_blk_en : STD_LOGIC;
SIGNAL cnt_err : t_cnt_err_arr(g_nof_err_counts-1 DOWNTO 0);
SIGNAL cnt_err_en : STD_LOGIC_VECTOR(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 cnt_reg : NATURAL;
SIGNAL cnt : NATURAL;
SIGNAL block_sosi : t_dp_sosi; SIGNAL block_sosi : t_dp_sosi;
SIGNAL block_siso : t_dp_siso;
SIGNAL block_sosi_piped : t_dp_sosi;
BEGIN BEGIN
p_clk : PROCESS(rst, clk) u_common_spulse_cnt_clr : ENTITY common_lib.common_spulse
BEGIN PORT MAP (
IF rst='1' THEN in_rst => mm_rst,
cnt_reg <= 0; in_clk => mm_clk,
ELSIF rising_edge(clk) THEN in_pulse => reg_mosi.rd,
cnt_reg <= cnt; in_busy => OPEN,
END IF; out_rst => dp_rst,
END PROCESS; out_clk => dp_clk,
out_pulse => cnt_clr
);
-- Count valid per block -- block counter
p_cnt : PROCESS(snk_in, cnt_reg) cnt_blk_en <= snk_in.eop WHEN UNSIGNED(cnt_blk) < UNSIGNED(c_max_cnt) ELSE '0';
BEGIN u_blk_counter : ENTITY common_lib.common_counter
cnt <= cnt_reg; GENERIC MAP (
IF snk_in.sop='1' THEN g_width => g_cnt_w
cnt <= 0; )
ELSIF snk_in.valid='1' THEN PORT MAP (
cnt <= cnt_reg + 1; rst => dp_rst,
END IF; clk => dp_clk,
END PROCESS;
-- Resize snk_in combinatorially into block_sosi, so no impact on RL cnt_clr => cnt_clr,
p_block_sosi : PROCESS(snk_in, cnt) cnt_en => cnt_blk_en,
BEGIN count => cnt_blk
-- Default keep snk_in info and data fields );
block_sosi <= snk_in;
IF snk_in.valid='1' THEN
-- Set output eop, info @ eop gets lost if g_expected_length < actual block size
IF snk_in.eop = '1' XOR cnt = g_expected_length-1 THEN
block_sosi.err(g_err_bi) <= '1';
END IF;
IF cnt = g_expected_length-1 THEN -- error counters
block_sosi.eop <= '1'; gen_err_counters : FOR I IN 0 TO g_nof_err_counts-1 GENERATE
END IF; cnt_err_en(I) <= snk_in.eop AND snk_in.err(I) WHEN UNSIGNED(cnt_err(I)) < UNSIGNED(c_max_cnt) ELSE '0';
u_blk_counter : ENTITY common_lib.common_counter
GENERIC MAP (
g_width => g_cnt_w
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
IF cnt > g_expected_length-1 THEN cnt_clr => cnt_clr,
block_sosi <= c_dp_sosi_rst; cnt_en => cnt_err_en(I),
END IF; count => cnt_err(I)
END IF; );
END PROCESS; END GENERATE;
-- Register mapping
-- first registers are the error counters
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(cnt_err(I), c_word_w);
END GENERATE;
-- The last register is the block counter.
count_reg((g_nof_err_counts+1) * c_word_w - 1 DOWNTO g_nof_err_counts * c_word_w ) <= RESIZE_UVEC(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
);
-- Register block_sosi to easy timing closure
u_pipeline : ENTITY work.dp_pipeline u_pipeline : ENTITY work.dp_pipeline
GENERIC MAP ( GENERIC MAP (
g_pipeline => 1 -- 0 for wires, > 0 for registers, g_pipeline => 1 -- 0 for wires, > 0 for registers,
) )
PORT MAP ( PORT MAP (
rst => rst, rst => dp_rst,
clk => clk, clk => dp_clk,
-- ST sink -- ST sink
snk_out => snk_out, snk_out => block_siso,
snk_in => block_sosi, snk_in => block_sosi,
-- ST source -- ST source
src_in => src_in, src_in => src_in,
src_out => src_out 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; END rtl;
-------------------------------------------------------------------------------
--
-- 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:
-- Test bench for dp_block_validate_err.
-- Description:
-- Verifies the output sosi of the DUT with the expected sosi.
-- The TB also reads the register values via MM and verifies them against the
-- expected values.
-- Usage:
-- . as 5
-- . run -all
LIBRARY IEEE, common_lib;
USE IEEE.std_logic_1164.ALL;
USE IEEE.numeric_std.ALL;
USE common_lib.common_pkg.ALL;
USE common_lib.common_mem_pkg.ALL;
USE common_lib.tb_common_mem_pkg.ALL;
USE common_lib.common_str_pkg.ALL;
USE common_lib.common_lfsr_sequences_pkg.ALL;
USE common_lib.tb_common_pkg.ALL;
USE work.dp_stream_pkg.ALL;
USE work.tb_dp_pkg.ALL;
ENTITY tb_dp_block_validate_err IS
GENERIC (
g_nof_blocks_per_sync : NATURAL := 5;
g_nof_data_per_blk : NATURAL := 9;
g_max_block_size : NATURAL := 9;
g_nof_err_counts : NATURAL := 8;
g_gap_size : NATURAL := 4;
g_cnt_w : NATURAL := 3
);
END tb_dp_block_validate_err;
ARCHITECTURE tb OF tb_dp_block_validate_err IS
------------------------------------------------------------------------------
-- Clock & reset
------------------------------------------------------------------------------
CONSTANT c_dp_clk_period : TIME := 5 ns;
CONSTANT c_mm_clk_period : TIME := 10 ns;
CONSTANT c_dut_pipeline : NATURAL := g_nof_data_per_blk + 3;
CONSTANT c_nof_sync : NATURAL := 5;
CONSTANT c_nof_blk : NATURAL := g_nof_blocks_per_sync * c_nof_sync;
CONSTANT c_max_cnt : NATURAL := 2**g_cnt_w -1;
CONSTANT c_mm_addr_dp_blk_cnt : NATURAL := g_nof_err_counts;
CONSTANT c_exp_blk_cnt : NATURAL := sel_a_b(c_nof_blk < c_max_cnt, c_nof_blk, c_max_cnt);
SIGNAL dp_clk : STD_LOGIC := '1';
SIGNAL mm_clk : STD_LOGIC := '1';
SIGNAL rst : STD_LOGIC := '1';
SIGNAL tb_end : STD_LOGIC := '0';
SIGNAL stimuli_end : STD_LOGIC;
SIGNAL stimuli_sosi : t_dp_sosi;
SIGNAL stimuli_siso : t_dp_siso;
SIGNAL stimuli_cnt_reg : NATURAL;
SIGNAL stimuli_cnt : NATURAL;
SIGNAL verify_sosi : t_dp_sosi;
SIGNAL verify_siso : t_dp_siso := c_dp_siso_rdy;
SIGNAL reference_cnt : NATURAL;
SIGNAL reference_cnt_reg : NATURAL;
SIGNAL reference_sosi : t_dp_sosi;
SIGNAL reference_siso : t_dp_siso := c_dp_siso_rdy;
SIGNAL reg_mosi : t_mem_mosi := c_mem_mosi_rst;
SIGNAL reg_miso : t_mem_miso := c_mem_miso_rst;
BEGIN
------------------------------------------------------------------------------
-- Clock & reset
------------------------------------------------------------------------------
dp_clk <= (NOT dp_clk) OR tb_end AFTER c_dp_clk_period/2;
mm_clk <= (NOT mm_clk) OR tb_end AFTER c_mm_clk_period/2;
rst <= '1', '0' AFTER c_dp_clk_period*7;
------------------------------------------------------------------------------
-- Stimuli:
------------------------------------------------------------------------------
-- Generate snk_in with data frames
u_stimuli : ENTITY work.dp_stream_stimuli
GENERIC MAP (
g_sync_period => g_nof_blocks_per_sync,
g_nof_repeat => g_nof_blocks_per_sync * c_nof_sync,
g_pkt_len => g_nof_data_per_blk,
g_pkt_gap => g_gap_size,
g_err_init => 0,
g_err_incr => 1
)
PORT MAP (
rst => rst,
clk => dp_clk,
-- Generate stimuli
src_in => stimuli_siso,
src_out => stimuli_sosi,
-- End of stimuli
tb_end => stimuli_end
);
------------------------------------------------------------------------------
-- DUT
------------------------------------------------------------------------------
u_dut : ENTITY work.dp_block_validate_err
GENERIC MAP (
g_cnt_w => g_cnt_w,
g_max_block_size => g_max_block_size,
g_nof_err_counts => g_nof_err_counts,
g_data_w => c_word_w,
g_bsn_w => c_dp_stream_bsn_w,
g_empty_w => c_dp_stream_empty_w,
g_channel_w => c_dp_stream_channel_w,
g_use_bsn => TRUE,
g_use_empty => TRUE,
g_use_channel => TRUE,
g_use_sync => TRUE
)
PORT MAP (
dp_rst => rst,
dp_clk => dp_clk,
mm_rst => rst,
mm_clk => mm_clk,
-- ST sink
snk_out => stimuli_siso,
snk_in => stimuli_sosi,
-- ST source
src_in => verify_siso,
src_out => verify_sosi,
reg_mosi => reg_mosi,
reg_miso => reg_miso
);
------------------------------------------------------------------------------
-- Verification
------------------------------------------------------------------------------
u_pipeline : ENTITY work.dp_pipeline
GENERIC MAP (
g_pipeline => c_dut_pipeline
)
PORT MAP (
rst => rst,
clk => dp_clk,
-- ST sink
snk_out => OPEN,
snk_in => stimuli_sosi,
-- ST source
src_in => reference_siso,
src_out => reference_sosi
);
reference_cnt_reg <= reference_cnt WHEN rising_edge(dp_clk);
reference_cnt <= 0 WHEN reference_sosi.eop='1' AND ((reference_cnt_reg+1) MOD 2**g_nof_err_counts) = 0 ELSE
reference_cnt_reg + 1 WHEN reference_sosi.eop='1' ELSE
reference_cnt_reg;
p_verify : PROCESS(dp_clk)
BEGIN
IF rising_edge(dp_clk) THEN
IF reference_cnt_reg = 0 THEN -- no errors so we expect a block
ASSERT verify_sosi.valid = reference_sosi.valid REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ASSERT verify_sosi.sop = reference_sosi.sop REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ASSERT verify_sosi.eop = reference_sosi.eop REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ASSERT verify_sosi.data = reference_sosi.data REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ASSERT verify_sosi.channel = reference_sosi.channel REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ASSERT verify_sosi.bsn = reference_sosi.bsn REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ASSERT verify_sosi.empty = reference_sosi.empty REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ASSERT verify_sosi.sync = reference_sosi.sync REPORT "Unexpected difference between in / out sosi" SEVERITY ERROR;
ELSE -- we expect no block as there are errors
ASSERT verify_sosi.valid = '0' REPORT "Wrong, valid is not '0' which is unexpected." SEVERITY ERROR;
ASSERT verify_sosi.sop = '0' REPORT "Wrong, sop is not '0' which is unexpected." SEVERITY ERROR;
ASSERT verify_sosi.eop = '0' REPORT "Wrong, eop is not '0' which is unexpected." SEVERITY ERROR;
END IF;
END IF;
END PROCESS;
p_verify_mm : PROCESS
VARIABLE v_X : INTEGER := 0; -- variable to hold 2**I * ((c_nof_blk-1) / 2**(I+1))
VARIABLE v_Y : INTEGER := 0; -- variable to hold (c_nof_blk-1) + 1 - (2 * v_X) - 2**I
-- v_N is a variable to hold the expectet cnt number for the error counter registers = v_X + v_Y for v_Y > 0, else = v_x.
-- this can be calculated as the dp error field is a counter up to c_nof_blk - 1.
VARIABLE v_N : INTEGER := 0;
BEGIN
proc_common_wait_until_lo_hi(dp_clk, stimuli_end);
proc_common_wait_some_cycles(dp_clk, c_dut_pipeline + 1);
proc_common_wait_until_lo_hi(mm_clk, mm_clk);
proc_mem_mm_bus_rd(c_mm_addr_dp_blk_cnt, mm_clk, reg_miso, reg_mosi);
proc_mem_mm_bus_rd_latency(1, mm_clk);
ASSERT c_exp_blk_cnt = TO_UINT(reg_miso.rddata(c_word_w-1 DOWNTO 0)) REPORT "Wrong total block count" SEVERITY ERROR;
FOR I IN 0 TO g_nof_err_counts-1 LOOP
v_X := 2**I * ((c_nof_blk-1) / 2**(I+1));
v_Y := c_nof_blk - 2*v_X - 2**I;
IF v_Y < 0 THEN -- v_N = v_X + v_Y only holds for v_Y > 0.
v_N := v_X;
ELSE
v_N := v_X + v_Y;
END IF;
IF v_N > c_max_cnt THEN
v_N := c_max_cnt; -- the DUT clips the counters
END IF;
proc_mem_mm_bus_rd(I, mm_clk, reg_miso, reg_mosi);
proc_mem_mm_bus_rd_latency(1, mm_clk);
ASSERT v_N = TO_UINT(reg_miso.rddata(c_word_w-1 DOWNTO 0)) REPORT "Wrong error count" SEVERITY ERROR;
END LOOP;
proc_common_wait_some_cycles(dp_clk, 10);
tb_end <= '1';
WAIT;
END PROCESS;
tb_end <= '0', stimuli_end AFTER (1 + 10*c_dut_pipeline)*c_dp_clk_period;
END tb;
-------------------------------------------------------------------------------
--
-- 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:
-- Verify multiple variations of tb_dp_block_validate_err
-- Usage:
-- > as 3
-- > run -all
LIBRARY IEEE;
USE IEEE.std_logic_1164.ALL;
ENTITY tb_tb_dp_block_validate_err IS
END tb_tb_dp_block_validate_err;
ARCHITECTURE tb OF tb_tb_dp_block_validate_err IS
SIGNAL tb_end : STD_LOGIC := '0'; -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end'
CONSTANT c_blk_per_sync : NATURAL := 5;
CONSTANT c_data_per_blk : NATURAL := 9;
CONSTANT c_max_block_size : NATURAL := 9;
CONSTANT c_nof_err_counts : NATURAL := 5;
BEGIN
-- g_nof_blocks_per_sync : NATURAL := 5;
-- g_nof_data_per_blk : NATURAL := 9;
-- g_max_block_size : NATURAL := 9;
-- g_nof_err_counts : NATURAL := 8;
-- g_gap_size : NATURAL := 4;
-- g_cnt_w : NATURAL := 3
u_normal : ENTITY work.tb_dp_block_validate_err GENERIC MAP(c_blk_per_sync, c_data_per_blk, c_max_block_size, c_nof_err_counts, 4, 3);
u_clip : ENTITY work.tb_dp_block_validate_err GENERIC MAP(c_blk_per_sync, c_data_per_blk, c_max_block_size, c_nof_err_counts, 4, 3);
u_small_cnt_w : ENTITY work.tb_dp_block_validate_err GENERIC MAP(c_blk_per_sync, c_data_per_blk, c_max_block_size, c_nof_err_counts, 4, 1);
u_large_cnt_w : ENTITY work.tb_dp_block_validate_err GENERIC MAP(c_blk_per_sync, c_data_per_blk, c_max_block_size, c_nof_err_counts, 4, 30);
u_small_gap : ENTITY work.tb_dp_block_validate_err GENERIC MAP(c_blk_per_sync, c_data_per_blk, c_max_block_size, c_nof_err_counts, 1, 16);
u_large_gap : ENTITY work.tb_dp_block_validate_err GENERIC MAP(c_blk_per_sync, c_data_per_blk, c_max_block_size, c_nof_err_counts, 100, 16);
u_low_nof_cnt : ENTITY work.tb_dp_block_validate_err GENERIC MAP(c_blk_per_sync, c_data_per_blk, c_max_block_size, 1, 1, 16);
END tb;
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment