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

Merge branch 'L2SDP-791' into 'master'

Resolve L2SDP-791

Closes L2SDP-791

See merge request desp/hdl!270
parents 580f666b 6ea8c60f
No related branches found
No related tags found
1 merge request!270Resolve L2SDP-791
Pipeline #34252 passed
Showing
with 225 additions and 135 deletions
......@@ -44,7 +44,11 @@
-- > add wave -position insertpoint \
-- sim:/tb_lofar2_unb2c_sdp_station_xsub_one_xst_offload/c_exp_subband_xst
-- > run -a
-- Takes about 10 m
-- Takes about 50 m
-- View e.g.:
-- * rx_sdp_stat_re/im in radix decimal and in format literal or analogue
-- * rx_sdp_stat_header.app
-- * new_interval in node_sdp_correlator.vhd
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_lib, unb2c_board_lib, i2c_lib, mm_lib, dp_lib, diag_lib, lofar2_sdp_lib, wpfb_lib, lofar2_unb2c_sdp_station_lib, eth_lib;
......
......@@ -22,11 +22,13 @@
--
-- Author: R. van der Walle
-- Purpose:
-- . Implements the functionality of the Subband Correlator in the
-- . Implements the functionality of the Subband Correlator (F_sub) in the
-- LOFAR2 SDPFW design.
-- Description:
-- Remark:
-- .
-- . Use new_interval to avoid offloading undefined XST data for the first
-- sync interval after an F_sub restart, because then there is no previous
-- sync interval with valid XST data yet.
-------------------------------------------------------------------------------
LIBRARY IEEE, common_lib, dp_lib, reorder_lib, st_lib, mm_lib, ring_lib;
......@@ -118,6 +120,8 @@ ARCHITECTURE str OF node_sdp_correlator IS
SIGNAL xsel_data_sosi : t_dp_sosi := c_dp_sosi_rst;
SIGNAL local_sosi : t_dp_sosi := c_dp_sosi_rst;
SIGNAL new_interval : STD_LOGIC;
SIGNAL ring_mux_sosi : t_dp_sosi := c_dp_sosi_rst;
SIGNAL ring_mux_siso : t_dp_siso := c_dp_siso_rdy;
SIGNAL dp_fifo_fill_sosi : t_dp_sosi := c_dp_sosi_rst;
......@@ -175,6 +179,8 @@ BEGIN
in_sosi_arr => quant_sosi_arr,
out_sosi => xsel_sosi,
new_interval => new_interval,
mm_rst => mm_rst,
mm_clk => mm_clk,
......@@ -465,6 +471,8 @@ BEGIN
reg_bsn_monitor_v2_offload_cipo => reg_bsn_monitor_v2_xst_offload_cipo,
in_sosi => crosslets_sosi,
new_interval => new_interval,
out_sosi => mon_xst_udp_sosi_arr(0),
out_siso => xst_udp_siso,
......
......@@ -24,15 +24,18 @@
-- Purpose:
-- Select subbands from incoming blocks
-- Description:
-- The Crosslet subband select selects N_crosslets from each incoming block.
-- * The Crosslet subband select selects N_crosslets from each incoming block.
-- Per crosslet there are S_pn = 12 subbands, one from each signal input of
-- the PN.
-- The cur_crosslets_info is valid at the out_sosi.sync and for the entire
-- * The cur_crosslets_info is valid at the out_sosi.sync and for the entire
-- sync interval. The cur_crosslets_info identifies the crosslets that are
-- being calculated during this out_sosi.sync interval.
-- The prev_crosslets_info identifies the crosslets that were calculated
-- during the previous out_sosi.sync interval, so the XST for those crosslets
-- are then pending to be offloaded.
-- * The new_interval is active before the first out_sosi.sync and inactive
-- before the next out_sosi.sync, so it can be used to know when a new
-- sequence of out_sosi.sync intervals starts.
-- Remark:
-- . See L5 SDPFW Design Document: Subband Correlator
-- Link: https://support.astron.nl/confluence/pages/viewpage.action?spaceKey=L2M&title=L5+SDPFW+Design+Document%3A+Subband+Correlator
......@@ -58,6 +61,8 @@ ENTITY sdp_crosslets_subband_select IS
in_sosi_arr : IN t_dp_sosi_arr(c_sdp_P_pfb-1 DOWNTO 0);
out_sosi : OUT t_dp_sosi;
new_interval : OUT STD_LOGIC;
mm_rst : IN STD_LOGIC;
mm_clk : IN STD_LOGIC;
......@@ -142,7 +147,8 @@ BEGIN
in_sosi_arr => in_sosi_arr,
out_sosi_arr => dp_bsn_sync_scheduler_src_out_arr,
out_start => start_trigger
out_start => start_trigger,
out_start_interval => new_interval
);
---------------------------------------------------------------
......
......@@ -142,6 +142,7 @@ ENTITY sdp_statistics_offload IS
-- Input timing regarding the integration interval of the statistics
in_sosi : IN t_dp_sosi;
new_interval : IN STD_LOGIC := '0';
-- Streaming output of offloaded statistics packets
out_sosi : OUT t_dp_sosi;
......@@ -225,6 +226,7 @@ ARCHITECTURE str OF sdp_statistics_offload IS
SIGNAL data_id_rec : t_sdp_stat_data_id;
SIGNAL data_id_slv : STD_LOGIC_VECTOR(31 DOWNTO 0) := (OTHERS => '0');
SIGNAL in_trigger : STD_LOGIC;
SIGNAL trigger_en : STD_LOGIC := '0';
SIGNAL trigger_offload : STD_LOGIC := '0';
SIGNAL mm_done : STD_LOGIC := '0';
......@@ -477,6 +479,14 @@ BEGIN
nxt_r <= v;
END PROCESS;
-- The in_trigger can skip the first in_sosi.sync. This is necessary if the
-- in_sosi input can be restarted, because then at every restart there is
-- no valid previous in_sosi.sync interval yet. This is used for XST offload,
-- because then the in_sync interval is MM programmable. For SST and BST the
-- new_interval = '0' is not used, because then the in_sosi typically
-- remains on after it was started.
in_trigger <= in_sosi.sync AND NOT new_interval;
u_mms_common_variable_delay : ENTITY common_lib.mms_common_variable_delay
PORT MAP (
mm_rst => mm_rst,
......@@ -489,7 +499,7 @@ BEGIN
reg_enable_miso => reg_enable_miso,
delay => nof_cycles_dly,
trigger => in_sosi.sync,
trigger => in_trigger,
trigger_en => trigger_en,
trigger_dly => trigger_offload
);
......
......@@ -84,12 +84,11 @@ ARCHITECTURE tb OF tb_sdp_crosslets_subband_select IS
SIGNAL mm_trigger_miso : t_mem_miso;
SIGNAL st_en : STD_LOGIC := '1';
SIGNAL st_bsn : NATURAL := c_scheduled_bsn - c_nof_block_dly;
SIGNAL st_siso_arr : t_dp_siso_arr(c_sdp_P_pfb-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy);
SIGNAL st_sosi_arr : t_dp_sosi_arr(c_sdp_P_pfb-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
SIGNAL exp_sosi : t_dp_sosi := c_dp_sosi_rst;
SIGNAL bsn : NATURAL := c_scheduled_bsn - c_nof_block_dly;
SIGNAL in_sosi_arr : t_dp_sosi_arr(c_sdp_P_pfb-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
SIGNAL out_sosi : t_dp_sosi;
......@@ -198,14 +197,14 @@ BEGIN
END GENERATE;
-- Time stimuli
bsn <= bsn + 1 WHEN rising_edge(clk) AND (st_sosi_arr(0).eop='1');
st_bsn <= st_bsn + 1 WHEN rising_edge(clk) AND (st_sosi_arr(0).eop='1');
-- Add BSN to the ST data
p_in_sosi : PROCESS(st_sosi_arr, bsn)
p_in_sosi : PROCESS(st_sosi_arr, st_bsn)
BEGIN
in_sosi_arr <= st_sosi_arr;
FOR I IN 0 TO c_sdp_P_pfb-1 LOOP
in_sosi_arr(I) <= st_sosi_arr(I);
in_sosi_arr(I).bsn <= TO_DP_BSN(bsn);
in_sosi_arr(I).bsn <= TO_DP_BSN(st_bsn);
END LOOP;
END PROCESS;
......
......@@ -172,6 +172,7 @@ ARCHITECTURE tb OF tb_sdp_statistics_offload IS
SIGNAL offload_rx_hdr_dat_mosi : t_mem_mosi := c_mem_mosi_rst;
SIGNAL offload_rx_hdr_dat_miso : t_mem_miso;
SIGNAL new_interval : STD_LOGIC := '0';
SIGNAL in_sosi : t_dp_sosi := c_dp_sosi_rst;
SIGNAL in_crosslets_info_rec : t_sdp_crosslets_info;
......@@ -241,6 +242,9 @@ ARCHITECTURE tb OF tb_sdp_statistics_offload IS
SIGNAL dbg_c_ram_size : NATURAL := c_ram_size;
SIGNAL dbg_c_crosslets_info_rec : t_sdp_crosslets_info := c_crosslets_info_rec;
SIGNAL dbg_c_crosslets_info_slv : STD_LOGIC_VECTOR(c_sdp_crosslets_info_reg_w-1 DOWNTO 0) := c_crosslets_info_slv;
SIGNAL dbg_c_nof_block_per_sync : NATURAL := c_nof_block_per_sync;
SIGNAL dbg_c_nof_clk_per_block : NATURAL := c_nof_clk_per_block;
SIGNAL dbg_c_nof_clk_per_sync : NATURAL := c_nof_clk_per_sync ;
BEGIN
......@@ -281,7 +285,9 @@ BEGIN
in_sosi.bsn <= TO_DP_BSN(c_bsn_init);
in_sosi.valid <= '1';
in_crosslets_info_rec <= c_crosslets_info_rec;
new_interval <= '1'; -- mark first in_sosi.sync interval
WHILE TRUE LOOP
-- One in_sosi.sync interval
FOR i IN 0 TO c_nof_block_per_sync-1 LOOP
FOR j IN 0 TO c_nof_clk_per_block-1 LOOP
in_sosi.sync <= '0';
......@@ -304,6 +310,7 @@ BEGIN
proc_common_wait_some_cycles(dp_clk, 1);
END LOOP;
END LOOP;
new_interval <= '0';
END LOOP;
WAIT;
END PROCESS;
......@@ -311,8 +318,7 @@ BEGIN
-- Enable the statistics offload when input is running
p_enable_trigger : PROCESS
BEGIN
-- Wait at least one sync interval, so that DUT can have measured the integration_interval
proc_common_wait_until_hi_lo(dp_clk, in_sosi.sync);
proc_common_wait_until_low(dp_clk, mm_rst);
proc_common_wait_some_cycles(mm_clk, 10);
-- Enable common variable delay.
proc_mem_mm_bus_wr(c_reg_enable_mm_addr_enable, 1, mm_clk, enable_miso, enable_mosi);
......@@ -645,6 +651,8 @@ BEGIN
-- ST
in_sosi => in_sosi,
new_interval => new_interval,
out_sosi => sdp_offload_sosi,
out_siso => sdp_offload_siso,
......
......@@ -63,6 +63,9 @@
-- * out_start:
-- Pulse at out_sosi.sync with out_sosi.bsn = ctrl_start_bsn. The first
-- out_sosi.sync interval will have nof_blk_max blocks.
-- * out_start_interval:
-- Active from out_start until next out_sosi.sync, so active during the
-- first out_sosi.sync interval of a new out_sosi sequence.
-- * out_enable:
-- Goes high at first out_sosi.sync. In case of a restart when ctrl_enable
-- was already '1', then the out_enable will go low and high to ensure that
......@@ -135,6 +138,7 @@ ENTITY dp_bsn_sync_scheduler IS
in_sosi : IN t_dp_sosi;
out_sosi : OUT t_dp_sosi;
out_start : OUT STD_LOGIC; -- pulse at out_sosi.sync at ctrl_start_bsn
out_start_interval : OUT STD_LOGIC; -- active during first out_sosi.sync interval
out_enable : OUT STD_LOGIC -- for tb verification purposes
);
END dp_bsn_sync_scheduler;
......@@ -166,7 +170,11 @@ ARCHITECTURE rtl OF dp_bsn_sync_scheduler IS
SIGNAL r : t_reg;
SIGNAL nxt_r : t_reg;
SIGNAL output_start : STD_LOGIC;
SIGNAL output_enable : STD_LOGIC;
SIGNAL output_next : STD_LOGIC; -- active at next output_sync's
SIGNAL output_start : STD_LOGIC; -- active at first output_sync
SIGNAL output_start_interval : STD_LOGIC; -- active during first output_sync interval
SIGNAL output_start_interval_reg : STD_LOGIC := '0';
SIGNAL output_sync : STD_LOGIC;
SIGNAL output_sosi : t_dp_sosi;
......@@ -371,14 +379,16 @@ BEGIN
nxt_r <= v;
END PROCESS;
output_enable <= nxt_r.output_enable;
-----------------------------------------------------------------------------
-- Output in_sosi with programmed sync interval or disable the output
-----------------------------------------------------------------------------
-- . note this is part of p_comb, but using a separate process is fine too.
p_output_sosi : PROCESS(in_sosi, nxt_r, output_sync)
p_output_sosi : PROCESS(in_sosi, output_enable, output_sync)
BEGIN
output_sosi <= in_sosi;
IF nxt_r.output_enable = '1' THEN
IF output_enable = '1' THEN
output_sosi.sync <= output_sync;
ELSE
output_sosi.sync <= '0';
......@@ -389,7 +399,30 @@ BEGIN
END PROCESS;
-----------------------------------------------------------------------------
-- Pipeline output to avoid timing closure problems due to use of nxt_r.output_enable
-- Determine output_start_interval
-----------------------------------------------------------------------------
output_next <= output_sync AND NOT output_start;
p_output_start_interval : PROCESS(output_start_interval_reg, output_start, output_next, output_enable)
BEGIN
-- Hold output_start until next sync interval
output_start_interval <= output_start_interval_reg;
IF output_start = '1' THEN
output_start_interval <= '1';
ELSIF output_next = '1' THEN
output_start_interval <= '0';
END IF;
-- provided that output_enable is still active
IF output_enable = '0' THEN
output_start_interval <= '0';
END IF;
END PROCESS;
output_start_interval_reg <= output_start_interval WHEN rising_edge(clk);
-----------------------------------------------------------------------------
-- Pipeline output to avoid timing closure problems due to use of output_enable
-----------------------------------------------------------------------------
u_out_sosi : ENTITY work.dp_pipeline
GENERIC MAP (
......@@ -406,11 +439,13 @@ BEGIN
gen_pipe_out_start : IF g_pipeline = 1 GENERATE
out_start <= output_start WHEN rising_edge(clk);
out_start_interval <= output_start_interval_reg;
out_enable <= r.output_enable;
END GENERATE;
no_pipe_out_start : IF g_pipeline = 0 GENERATE
out_start <= output_start;
out_enable <= nxt_r.output_enable;
out_start_interval <= output_start_interval;
out_enable <= output_enable;
END GENERATE;
END rtl;
......
......@@ -82,6 +82,7 @@ ENTITY mmp_dp_bsn_sync_scheduler IS
in_sosi : IN t_dp_sosi;
out_sosi : OUT t_dp_sosi;
out_start : OUT STD_LOGIC;
out_start_interval : OUT STD_LOGIC;
out_enable : OUT STD_LOGIC
);
END mmp_dp_bsn_sync_scheduler;
......@@ -215,6 +216,7 @@ BEGIN
in_sosi => in_sosi,
out_sosi => out_sosi,
out_start => out_start,
out_start_interval => out_start_interval,
out_enable => out_enable
);
......
......@@ -53,6 +53,7 @@ ENTITY mmp_dp_bsn_sync_scheduler_arr IS
in_sosi_arr : IN t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
out_sosi_arr : OUT t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0);
out_start : OUT STD_LOGIC;
out_start_interval : OUT STD_LOGIC;
out_enable : OUT STD_LOGIC
);
END mmp_dp_bsn_sync_scheduler_arr;
......@@ -85,6 +86,7 @@ BEGIN
out_sosi => single_src_out,
out_start => out_start,
out_start_interval => out_start_interval,
out_enable => out_enable
);
......
......@@ -34,7 +34,7 @@
-- > as 4
-- > run -all
-- View in Wave window u_dut: r, nxt_r, and tb: in_sosi, out_sosi,
-- out_sync, out_start
-- out_sync, out_start, out_start_interval
--
-- Development steps:
-- . Step 1 ~1 day work (idea started earlier, so requirements were clear),
......@@ -76,13 +76,14 @@ USE dp_lib.tb_dp_pkg.ALL;
ENTITY tb_dp_bsn_sync_scheduler IS
GENERIC (
-- Input sync period and sosi ctrl
g_nof_input_sync : NATURAL := 10;
g_nof_input_sync : NATURAL := 10; -- Use c_nof_input_sync > g_block_size, see tb_tb_dp_bsn_sync_scheduler
g_nof_block_per_input_sync : NATURAL := 17;
g_block_size : NATURAL := 2;
g_input_gap_size : NATURAL := 0;
-- Output sync period
g_nof_samples_per_output_sync : NATURAL := 45 -- 45 / g_block_size = 4.5
g_nof_samples_per_output_sync : NATURAL := 45; -- 45 / g_block_size = 4.5
g_pipeline : NATURAL := 0 -- 0 or 1
);
END tb_dp_bsn_sync_scheduler;
......@@ -108,6 +109,8 @@ ARCHITECTURE tb OF tb_dp_bsn_sync_scheduler IS
CONSTANT c_output_nof_blocks_min : NATURAL := g_nof_samples_per_output_sync / g_block_size;
CONSTANT c_enable_init_nof_bsn : NATURAL := ceil_value(c_output_nof_blocks_min / g_block_size + 10, g_nof_block_per_input_sync);
CONSTANT c_out_enable_margin : NATURAL := g_block_size;
SIGNAL clk : STD_LOGIC := '1';
SIGNAL rst : STD_LOGIC := '1';
SIGNAL cnt : INTEGER := 0;
......@@ -145,26 +148,34 @@ ARCHITECTURE tb OF tb_dp_bsn_sync_scheduler IS
-- Output
SIGNAL out_sync : STD_LOGIC; -- declared next to in_sync, out_start and out_sosi for easier comparison in Wave window
SIGNAL out_start : STD_LOGIC;
SIGNAL out_start_interval : STD_LOGIC;
SIGNAL exp_start_interval : STD_LOGIC := '0';
SIGNAL first_interval : STD_LOGIC := '0';
SIGNAL out_enable : STD_LOGIC;
SIGNAL expected_out_enable : STD_LOGIC := '0';
SIGNAL out_sosi : t_dp_sosi := c_dp_sosi_init;
-- Verify
SIGNAL in_sosi_integer_comb : t_dp_sosi_integer;
SIGNAL in_sosi_integer_pipe : t_dp_sosi_integer;
SIGNAL in_sosi_integer : t_dp_sosi_integer;
SIGNAL out_sosi_integer : t_dp_sosi_integer;
SIGNAL verify_sosi_equal : STD_LOGIC := '0';
SIGNAL verify_sosi_equal_at_sop : STD_LOGIC := '0';
SIGNAL verify_sosi_equal_at_valid : STD_LOGIC := '0';
SIGNAL verify_sync : STD_LOGIC := '1';
SIGNAL recover_from_in_lost : STD_LOGIC := '0';
SIGNAL verifying_sync_equal : STD_LOGIC := '0';
SIGNAL prev_ctrl_enable : STD_LOGIC := '0';
SIGNAL prev_out_enable : STD_LOGIC := '0';
SIGNAL pending_out_disable : STD_LOGIC := '0';
SIGNAL expected_out_enable : STD_LOGIC := '0';
SIGNAL expected_out_enable1 : STD_LOGIC := '0';
SIGNAL expected_out_enable2 : STD_LOGIC := '0';
SIGNAL out_enable_cnt : NATURAL := 0;
SIGNAL nxt_out_enable_cnt : NATURAL := 0;
SIGNAL expected_out_enable_comb : STD_LOGIC := '0';
SIGNAL expected_out_enable_pipe : STD_LOGIC := '0';
SIGNAL expecting_out_start : STD_LOGIC := '0';
SIGNAL hold_out_eop : STD_LOGIC := '0';
SIGNAL hold_out_sop : STD_LOGIC := '0';
SIGNAL out_sop_cnt : NATURAL := 0;
......@@ -346,75 +357,53 @@ BEGIN
-----------------------------------------------------------------------------
-- . Verify out_enable
-----------------------------------------------------------------------------
p_hold_out_eop : PROCESS(clk)
BEGIN
IF rising_edge(clk) THEN
IF out_sosi.eop = '1' THEN
hold_out_eop <= '1';
ELSIF out_sosi.sop = '1' THEN
hold_out_eop <= '0';
END IF;
END IF;
END PROCESS;
-- Determine expected out_enable
p_expected_out_enable : PROCESS(ctrl_enable, ctrl_enable_evt, in_sosi, ctrl_start_bsn, out_enable, pending_out_disable, hold_out_eop)
-- The expected out_enable is difficult to determine cycle exact, because
-- it depends on g_block_size = 2 or > 2 and on g_pipeline. Therfore use
-- expected_out_enable_comb = '-' to define dont care.
-- * For g_block_size = 2 the use of r.enable (instead of v.enable) in
-- dp_bsn_sync_scheduler.vhd causes that the output can stay enabled 2
-- cycles longer, which is ok. Using v.enable does avoid these extra
-- cycles, but for timing closure it is preferred to use r.enable.
-- Verify out_enable
p_expected_out_enable : PROCESS(ctrl_enable, in_sosi, ctrl_start_bsn, ctrl_enable_evt, out_enable_cnt, ctrl_enable, in_sosi, ctrl_start_bsn)
BEGIN
-- Expect output disable after ctrl_enable_evt
IF ctrl_enable_evt = '1' THEN
IF out_enable = '0' THEN
-- Output is already disabled
expected_out_enable <= '0';
ELSE
-- Output is enabled, so this is a re-enable event.
IF hold_out_eop = '1' THEN
expected_out_enable <= '0'; -- end of block, so output can disable immediately
ELSE
pending_out_disable <= '1'; -- plan output disable before re-enable
END IF;
END IF;
END IF;
-- Default
expected_out_enable_comb <= '0';
IF pending_out_disable <= '1' THEN
IF hold_out_eop = '1' THEN
expected_out_enable <= '0'; -- end of block, so output can disable
pending_out_disable <= '0';
END IF;
END IF;
-- Expect output enable at start BSN
-- Expect output enable '1' when ctrl_enable is active, but after ctrl_start_bsn
IF ctrl_enable = '1' THEN
IF UNSIGNED(in_sosi.bsn) >= UNSIGNED(ctrl_start_bsn) THEN
expected_out_enable <= '1';
expected_out_enable_comb <= '1';
END IF;
END IF;
-- Introduce some dont care margin in case of ctrl_enable_evt when ctrl_enable was active and may change.
-- The ctrl_enable may go inactive (= stop) or remain active (= restart).
IF ctrl_enable_evt = '1' AND prev_ctrl_enable = '1' THEN
nxt_out_enable_cnt <= 0;
expected_out_enable_comb <= '-';
ELSIF out_enable_cnt < c_out_enable_margin THEN
nxt_out_enable_cnt <= out_enable_cnt + 1;
expected_out_enable_comb <= '-';
END IF;
END PROCESS;
expected_out_enable1 <= expected_out_enable WHEN rising_edge(clk);
expected_out_enable2 <= expected_out_enable1 WHEN rising_edge(clk);
prev_ctrl_enable <= ctrl_enable WHEN rising_edge(clk);
out_enable_cnt <= nxt_out_enable_cnt WHEN rising_edge(clk);
expected_out_enable_pipe <= expected_out_enable_comb WHEN rising_edge(clk);
expected_out_enable <= expected_out_enable_comb WHEN g_pipeline = 0 ELSE expected_out_enable_pipe;
p_verify_out_enable : PROCESS(clk)
BEGIN
-- Use registered values to compare, to avoid combinatorial differences
-- that can occur during a simulation delta cycle. These combinatorial
-- differences are not relevant, because they get resolved after a few
-- delta cycles.
IF rising_edge(clk) THEN
IF out_enable /= expected_out_enable THEN
IF out_enable = '1' THEN
IF g_block_size > 2 THEN
REPORT "Unexpected enabled out_enable" SEVERITY ERROR;
ELSIF out_enable /= expected_out_enable2 THEN
-- For g_block_size = 2 the use of r.enable (instead of v.enable)
-- in dp_bsn_sync_scheduler.vhd causes that the output can stay
-- enabled 2 cycles longer, which is ok. Using v.enable does
-- avoid this need to use expected_out_enable2, but for timing
-- closure it is preferred to use r.enable.
REPORT "Unexpected enabled out_enable2" SEVERITY ERROR;
END IF;
ELSE
REPORT "Unexpected disabled out_enable" SEVERITY ERROR;
END IF;
IF expected_out_enable = '1' THEN
ASSERT out_enable = '1' REPORT "Wrong out_enable, should be active" SEVERITY ERROR;
ELSIF expected_out_enable = '0' THEN
ASSERT out_enable = '0' REPORT "Wrong out_enable, should be inactive" SEVERITY ERROR;
END IF;
END IF;
END PROCESS;
......@@ -471,6 +460,23 @@ BEGIN
END IF;
END PROCESS;
exp_start_interval <= out_start OR (first_interval AND NOT out_sync) WHEN rst = '0' ELSE '0';
p_verify_out_start_interval : PROCESS(clk)
BEGIN
IF rising_edge(clk) THEN
-- Create first_interval for exp_start_interval
IF out_start = '1' THEN
first_interval <= '1';
ELSIF out_sync = '1' THEN
first_interval <= '0';
END IF;
-- Verify exp_start_interval
ASSERT exp_start_interval = out_start_interval REPORT "Wrong out_start_interval" SEVERITY ERROR;
END IF;
END PROCESS;
-----------------------------------------------------------------------------
-- . Verify out_sosi = in_sosi, for all fields except out_sosi.sync
-----------------------------------------------------------------------------
......@@ -480,14 +486,19 @@ BEGIN
-- declaration is not sufficient.
verify_sosi_equal <= out_enable WHEN rising_edge(clk);
in_sosi_integer <= func_dp_stream_slv_to_integer(in_sosi, c_natural_w) WHEN rising_edge(clk);
verify_sosi_equal_at_sop <= verify_sosi_equal AND in_sosi_integer.sop;
verify_sosi_equal_at_valid <= verify_sosi_equal AND in_sosi_integer.valid;
in_sosi_integer_comb <= func_dp_stream_slv_to_integer(in_sosi, c_natural_w) WHEN rising_edge(clk);
in_sosi_integer_pipe <= in_sosi_integer_comb WHEN rising_edge(clk);
in_sosi_integer <= in_sosi_integer_comb WHEN g_pipeline = 0 ELSE in_sosi_integer_pipe;
out_sosi_integer <= func_dp_stream_slv_to_integer(out_sosi, c_natural_w) WHEN rising_edge(clk);
proc_dp_verify_sosi_equal( "bsn", clk, verify_sosi_equal, out_sosi_integer, in_sosi_integer);
proc_dp_verify_sosi_equal( "bsn", clk, verify_sosi_equal_at_sop, out_sosi_integer, in_sosi_integer);
proc_dp_verify_sosi_equal( "sop", clk, verify_sosi_equal, out_sosi_integer, in_sosi_integer);
proc_dp_verify_sosi_equal( "eop", clk, verify_sosi_equal, out_sosi_integer, in_sosi_integer);
proc_dp_verify_sosi_equal("valid", clk, verify_sosi_equal, out_sosi_integer, in_sosi_integer);
proc_dp_verify_sosi_equal( "data", clk, verify_sosi_equal, out_sosi_integer, in_sosi_integer);
proc_dp_verify_sosi_equal( "data", clk, verify_sosi_equal_at_valid, out_sosi_integer, in_sosi_integer);
-- Verify that out_sosi blocks have sop and eop
proc_dp_verify_sop_and_eop(clk, out_sosi.valid, out_sosi.sop, out_sosi.eop, hold_out_sop);
......@@ -558,7 +569,7 @@ BEGIN
GENERIC MAP (
g_bsn_w => c_bsn_w,
g_block_size => g_block_size,
g_pipeline => 0
g_pipeline => g_pipeline
)
PORT MAP (
rst => rst,
......@@ -578,6 +589,7 @@ BEGIN
in_sosi => in_sosi,
out_sosi => out_sosi,
out_start => out_start,
out_start_interval => out_start_interval,
out_enable => out_enable
);
......
......@@ -42,6 +42,7 @@ ARCHITECTURE tb OF tb_tb_dp_bsn_sync_scheduler IS
-- repeat period of the sync pattern is visible by nxt_r.accumulate in
-- dp_bsn_scheduler.vhd.
CONSTANT c_nof_input_sync : NATURAL := 25;
CONSTANT c_pipeline : NATURAL := 1;
BEGIN
-- from tb_dp_bsn_scheduler.vhd
......@@ -54,27 +55,30 @@ BEGIN
--
-- -- Output sync period
-- g_nof_samples_per_output_sync : NATURAL := 45; -- = g_block_size * 9 / 2
-- g_pipeline : NATURAL := 0
u_output_is_input : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 170); -- 170/10 = 17 block/out_sync, = in_sosi
u_output_is_input_no_gaps : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 5, 0, 85); -- 85/5 = 17 block/out_sync, = in_sosi
gen_tb : FOR P IN 0 TO c_pipeline GENERATE
u_output_is_input : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 170, P); -- 170/10 = 17 block/out_sync, = in_sosi
u_output_is_input_no_gaps : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 5, 0, 85, P); -- 85/5 = 17 block/out_sync, = in_sosi
u_sync_interval_0_5x : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 85); -- 85/10 = 8.5 block/out_sync, factor 85/170 = 0.5,
u_sync_interval_1_5x : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 255); -- 255/10 = 25.5 block/out_sync, factor 255/170 = 1.5,
u_sync_interval_prime_251 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 251); -- 251/10 = 25.1 block/out_sync, 251 is a prime
u_sync_interval_0_5x : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 85, P); -- 85/10 = 8.5 block/out_sync, factor 85/170 = 0.5,
u_sync_interval_1_5x : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 255, P); -- 255/10 = 25.5 block/out_sync, factor 255/170 = 1.5,
u_sync_interval_prime_251 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 251, P); -- 251/10 = 25.1 block/out_sync, 251 is a prime
u_short_block_4_3_15 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 4, 3, 3, 15); -- 15/3 = 5 block/out_sync,
u_short_block_5_3_16 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 5, 3, 3, 16); -- 16/3 = 5.33 block/out_sync,
u_short_block_6_3_17 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 6, 3, 3, 17); -- 17/3 = 5.66 block/out_sync,
u_short_block_4_3_15 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 4, 3, 3, 15, P); -- 15/3 = 5 block/out_sync,
u_short_block_5_3_16 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 5, 3, 3, 16, P); -- 16/3 = 5.33 block/out_sync,
u_short_block_6_3_17 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 6, 3, 3, 17, P); -- 17/3 = 5.66 block/out_sync,
u_short_block_no_gaps_4_3_15 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 4, 3, 0, 15); -- 15/3 = 5 block/out_sync,
u_short_block_no_gaps_5_3_16 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 5, 3, 0, 16); -- 16/3 = 5.33 block/out_sync,
u_short_block_no_gaps_6_3_17 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 6, 3, 0, 17); -- 17/3 = 5.66 block/out_sync,
u_short_block_no_gaps_4_3_15 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 4, 3, 0, 15, P); -- 15/3 = 5 block/out_sync,
u_short_block_no_gaps_5_3_16 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 5, 3, 0, 16, P); -- 16/3 = 5.33 block/out_sync,
u_short_block_no_gaps_6_3_17 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 6, 3, 0, 17, P); -- 17/3 = 5.66 block/out_sync,
u_short_block_size_2 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 7, 2, 3, 16); -- 16/2 = 8 block/out_sync,
u_short_block_size_2_no_gaps : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 7, 2, 0, 16); -- 16/2 = 8 block/out_sync,
u_short_block_size_2 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 7, 2, 3, 16, P); -- 16/2 = 8 block/out_sync,
u_short_block_size_2_no_gaps : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 7, 2, 0, 16, P); -- 16/2 = 8 block/out_sync,
u_fraction_half : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 45); -- 45/10 = 4.5 block/out_sync
u_fraction_0 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 50); -- 50/10 = 5 block/out_sync
u_fraction_half : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 45, P); -- 45/10 = 4.5 block/out_sync
u_fraction_0 : ENTITY work.tb_dp_bsn_sync_scheduler GENERIC MAP (c_nof_input_sync, 17, 10, 3, 50, P); -- 50/10 = 5 block/out_sync
END GENERATE;
END tb;
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment