Skip to content
Snippets Groups Projects
Commit d2b19329 authored by Daniel van der Schuur's avatar Daniel van der Schuur
Browse files

-Added g_nof_data_per_sync_diff generic;

-Added non-constant data block generation (+-g_nof_data_per_sync_diff
samples per sync) to tb_mmp_st_histogram.vhd;
-Fixed DP RAM -> MM RAM copy address error in mmp_st_histogram;
-Changed RAM block to allow MM write by user in mmp_st_histogram;
-Changed generic map in node_sdp_adc_input_and_timing.
-All test benches pass OK.
parent 19c4e383
No related branches found
No related tags found
1 merge request!154Updated st_histogram (instance) to support 200M+-512 samples per sync in LOFAR2.
...@@ -457,7 +457,8 @@ BEGIN ...@@ -457,7 +457,8 @@ BEGIN
g_nof_instances => c_sdp_S_pn, g_nof_instances => c_sdp_S_pn,
g_data_w => c_sdp_W_adc, g_data_w => c_sdp_W_adc,
g_nof_bins => c_sdp_V_si_histogram, g_nof_bins => c_sdp_V_si_histogram,
g_nof_data_per_sync => sel_a_b(g_sim, g_bsn_nof_clk_per_sync, c_sdp_f_adc_MHz*10**6 - c_sdp_N_fft/2) g_nof_data_per_sync => g_bsn_nof_clk_per_sync,
g_nof_data_per_sync_diff => c_sdp_N_fft/2
) )
PORT MAP ( PORT MAP (
mm_rst => mm_rst_internal, mm_rst => mm_rst_internal,
......
...@@ -46,7 +46,8 @@ ENTITY mmp_st_histogram IS ...@@ -46,7 +46,8 @@ ENTITY mmp_st_histogram IS
g_nof_instances : NATURAL; g_nof_instances : NATURAL;
g_data_w : NATURAL; g_data_w : NATURAL;
g_nof_bins : NATURAL; g_nof_bins : NATURAL;
g_nof_data_per_sync : NATURAL g_nof_data_per_sync : NATURAL;
g_nof_data_per_sync_diff : NATURAL
); );
PORT ( PORT (
dp_clk : IN STD_LOGIC; dp_clk : IN STD_LOGIC;
...@@ -90,14 +91,12 @@ ARCHITECTURE str OF mmp_st_histogram IS ...@@ -90,14 +91,12 @@ ARCHITECTURE str OF mmp_st_histogram IS
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Logic to move st_histogram RAM contents into the dual clock RAM -- Logic to move st_histogram RAM contents into the dual clock RAM
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
SIGNAL ram_fill_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_fill : STD_LOGIC;
SIGNAL ram_filling : STD_LOGIC; SIGNAL ram_filling : STD_LOGIC;
SIGNAL nxt_ram_filling : STD_LOGIC; SIGNAL nxt_ram_filling : STD_LOGIC;
SIGNAL ram_address : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0); SIGNAL ram_address : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0);
SIGNAL nxt_ram_address : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0); SIGNAL nxt_ram_address : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0);
SIGNAL prv_ram_address : STD_LOGIC_VECTOR(c_ram_adr_w-1 DOWNTO 0);
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- MM multiplexing -- MM multiplexing
...@@ -116,7 +115,8 @@ BEGIN ...@@ -116,7 +115,8 @@ BEGIN
GENERIC MAP( GENERIC MAP(
g_data_w => g_data_w, g_data_w => g_data_w,
g_nof_bins => g_nof_bins, g_nof_bins => g_nof_bins,
g_nof_data_per_sync => g_nof_data_per_sync g_nof_data_per_sync => g_nof_data_per_sync,
g_nof_data_per_sync_diff => g_nof_data_per_sync_diff
) )
PORT MAP ( PORT MAP (
dp_clk => dp_clk, dp_clk => dp_clk,
...@@ -159,14 +159,13 @@ BEGIN ...@@ -159,14 +159,13 @@ BEGIN
); );
END GENERATE; END GENERATE;
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Use snk_in Sync pulse to trigger RAM copy -- Use snk_in Sync pulse to trigger RAM copy
-- . use pipeline>=st_histogram I/O latency - don't copy too soon (clash with clear) -- . use pipeline>=st_histogram I/O latency - don't copy too soon (clash with clear)
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
u_common_pipeline_sl : ENTITY common_lib.common_pipeline_sl u_common_pipeline_sl : ENTITY common_lib.common_pipeline_sl
GENERIC MAP ( GENERIC MAP (
g_pipeline => 4 g_pipeline => 10
) )
PORT MAP ( PORT MAP (
clk => dp_clk, clk => dp_clk,
...@@ -175,7 +174,6 @@ BEGIN ...@@ -175,7 +174,6 @@ BEGIN
out_dat => ram_fill out_dat => ram_fill
); );
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Logic to move st_histogram RAM contents into the dual clock RAM above -- Logic to move st_histogram RAM contents into the dual clock RAM above
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
...@@ -195,7 +193,7 @@ BEGIN ...@@ -195,7 +193,7 @@ BEGIN
gen_rd_cipo_to_wr_copi: FOR i IN 0 TO g_nof_instances-1 GENERATE gen_rd_cipo_to_wr_copi: FOR i IN 0 TO g_nof_instances-1 GENERATE
wr_copi_arr(i).wr <= st_histogram_ram_cipo_arr(i).rdval; wr_copi_arr(i).wr <= st_histogram_ram_cipo_arr(i).rdval;
wr_copi_arr(i).wrdata(c_ram_dat_w-1 DOWNTO 0) <= st_histogram_ram_cipo_arr(i).rddata(c_ram_dat_w-1 DOWNTO 0); wr_copi_arr(i).wrdata(c_ram_dat_w-1 DOWNTO 0) <= st_histogram_ram_cipo_arr(i).rddata(c_ram_dat_w-1 DOWNTO 0);
wr_copi_arr(i).address(c_ram_adr_w-1 DOWNTO 0) <= ram_address; wr_copi_arr(i).address(c_ram_adr_w-1 DOWNTO 0) <= prv_ram_address;
END GENERATE; END GENERATE;
-- Registers -- Registers
...@@ -203,9 +201,11 @@ BEGIN ...@@ -203,9 +201,11 @@ BEGIN
BEGIN BEGIN
IF dp_rst = '1' THEN IF dp_rst = '1' THEN
ram_address <= (OTHERS=>'0'); ram_address <= (OTHERS=>'0');
prv_ram_address <= (OTHERS => '0');
ram_filling <= '0'; ram_filling <= '0';
ELSIF RISING_EDGE(dp_clk) THEN ELSIF RISING_EDGE(dp_clk) THEN
ram_address <= nxt_ram_address; ram_address <= nxt_ram_address;
prv_ram_address <= ram_address;
ram_filling <= nxt_ram_filling; ram_filling <= nxt_ram_filling;
END IF; END IF;
END PROCESS; END PROCESS;
......
...@@ -104,6 +104,7 @@ ENTITY st_histogram IS ...@@ -104,6 +104,7 @@ ENTITY st_histogram IS
g_data_w : NATURAL := 8; g_data_w : NATURAL := 8;
g_nof_bins : NATURAL := 256; -- <= 2^g_data_w (having more bins than possible values is not useful) g_nof_bins : NATURAL := 256; -- <= 2^g_data_w (having more bins than possible values is not useful)
g_nof_data_per_sync : NATURAL := 1024; g_nof_data_per_sync : NATURAL := 1024;
g_nof_data_per_sync_diff : NATURAL := 0; -- Allow +- g_nof_data_per_sync_diff samples per sync interval
g_data_type : STRING := "unsigned" -- unsigned or signed g_data_type : STRING := "unsigned" -- unsigned or signed
); );
PORT ( PORT (
...@@ -125,7 +126,7 @@ ARCHITECTURE rtl OF st_histogram IS ...@@ -125,7 +126,7 @@ ARCHITECTURE rtl OF st_histogram IS
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
CONSTANT c_ram_adr_w : NATURAL := ceil_log2(g_nof_bins); 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_adr_low : NATURAL := g_data_w-c_ram_adr_w;
CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync+1); CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync+g_nof_data_per_sync_diff+1);
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- snk_in.data help signal -- snk_in.data help signal
...@@ -190,7 +191,8 @@ ARCHITECTURE rtl OF st_histogram IS ...@@ -190,7 +191,8 @@ ARCHITECTURE rtl OF st_histogram IS
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- ram_clear -- ram_clear
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
CONSTANT c_data_cnt_w : NATURAL := ceil_log2(g_nof_data_per_sync); CONSTANT c_data_cnt_w : NATURAL := ceil_log2(g_nof_data_per_sync+g_nof_data_per_sync_diff);
CONSTANT c_clear_sample_cnt : NATURAL := g_nof_data_per_sync-g_nof_data_per_sync_diff; -- Clear sooner (-g_nof_data_per_sync_diff) rather than later
SIGNAL data_cnt : STD_LOGIC_VECTOR(c_data_cnt_w-1 DOWNTO 0); 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 nxt_data_cnt : STD_LOGIC_VECTOR(c_data_cnt_w-1 DOWNTO 0);
...@@ -458,7 +460,7 @@ BEGIN ...@@ -458,7 +460,7 @@ BEGIN
nxt_data_cnt <= (OTHERS=>'0') WHEN snk_in.sync='1' ELSE INCR_UVEC(data_cnt, 1) WHEN snk_in.valid='1' ELSE data_cnt; nxt_data_cnt <= (OTHERS=>'0') WHEN snk_in.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 -- 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'; ram_clear <= '1' WHEN TO_UINT(data_cnt)=c_clear_sample_cnt-g_nof_bins-1 ELSE '0';
-- Signal to indicate when RAM is being cleared -- 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 ram_clearing; nxt_ram_clearing <= '1' WHEN ram_clear='1' ELSE '0' WHEN TO_UINT(ram_clear_address)=g_nof_bins-1 ELSE ram_clearing;
......
...@@ -53,8 +53,7 @@ ENTITY tb_mmp_st_histogram IS ...@@ -53,8 +53,7 @@ ENTITY tb_mmp_st_histogram IS
g_data_w : NATURAL := 14; g_data_w : NATURAL := 14;
g_nof_bins : NATURAL := 512; g_nof_bins : NATURAL := 512;
g_nof_data_per_sync : NATURAL := 16384; -- g_nof_data_per_sync/g_nof_bins should be integer so counter data yields the same histogram in each bin g_nof_data_per_sync : NATURAL := 16384; -- g_nof_data_per_sync/g_nof_bins should be integer so counter data yields the same histogram in each bin
g_stimuli_mode : STRING := "counter"; -- "counter", "dc", "sine" or "random" g_nof_data_per_sync_diff : NATURAL := 32 -- Use non-constant g_nof_data_per_sync: longer (+g_nof_data_per_sync_diff), shorter (-g_nof_data_per_sync_diff),
g_sync_interval_diff : NATURAL := 64 -- Use non-constant g_nof_data_per_sync: longer (+g_sync_interval_diff), shorter (-g_sync_interval_diff),
); -- longer, shorter, etc. E.g. LOFAR2 uses 200M+-512 samples per sync. ); -- longer, shorter, etc. E.g. LOFAR2 uses 200M+-512 samples per sync.
END tb_mmp_st_histogram; END tb_mmp_st_histogram;
...@@ -65,7 +64,6 @@ ARCHITECTURE tb OF tb_mmp_st_histogram IS ...@@ -65,7 +64,6 @@ ARCHITECTURE tb OF tb_mmp_st_histogram IS
-- Constants derived from generics -- Constants derived from generics
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
CONSTANT c_expected_ram_content_counter : NATURAL := g_nof_data_per_sync/g_nof_bins; CONSTANT c_expected_ram_content_counter : NATURAL := g_nof_data_per_sync/g_nof_bins;
CONSTANT c_nof_levels_per_bin : NATURAL := (2**g_data_w)/g_nof_bins; --e.g. 2 values per bin if g_data_w=9 (512 levels) and g_nof_bins=256
CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync+1); CONSTANT c_ram_dat_w : NATURAL := ceil_log2(g_nof_data_per_sync+1);
CONSTANT c_ram_adr_w : NATURAL := ceil_log2(g_nof_bins); CONSTANT c_ram_adr_w : NATURAL := ceil_log2(g_nof_bins);
...@@ -88,7 +86,6 @@ ARCHITECTURE tb OF tb_mmp_st_histogram IS ...@@ -88,7 +86,6 @@ ARCHITECTURE tb OF tb_mmp_st_histogram IS
SIGNAL stimuli_src_out : t_dp_sosi; SIGNAL stimuli_src_out : t_dp_sosi;
SIGNAL stimuli_src_in : t_dp_siso; SIGNAL stimuli_src_in : t_dp_siso;
SIGNAL stimuli_done : STD_LOGIC; SIGNAL stimuli_done : STD_LOGIC;
SIGNAL long_sync_interval : BOOLEAN := TRUE;
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
-- st_histogram -- st_histogram
...@@ -110,6 +107,7 @@ ARCHITECTURE tb OF tb_mmp_st_histogram IS ...@@ -110,6 +107,7 @@ ARCHITECTURE tb OF tb_mmp_st_histogram IS
SIGNAL sum_of_bins : NATURAL; SIGNAL sum_of_bins : NATURAL;
SIGNAL verification_done : STD_LOGIC; SIGNAL verification_done : STD_LOGIC;
SIGNAL ver_long_sync_interval : BOOLEAN;
BEGIN BEGIN
...@@ -132,26 +130,28 @@ BEGIN ...@@ -132,26 +130,28 @@ BEGIN
p_generate_packets : PROCESS p_generate_packets : PROCESS
VARIABLE v_sosi : t_dp_sosi := c_dp_sosi_rst; VARIABLE v_sosi : t_dp_sosi := c_dp_sosi_rst;
VARIABLE v_nof_data_per_sync : NATURAL; VARIABLE v_nof_data_per_sync : NATURAL;
VARIABLE v_long_sync_interval : BOOLEAN;
BEGIN BEGIN
stimuli_done <= '0'; stimuli_done <= '0';
stimuli_src_out <= c_dp_sosi_rst; stimuli_src_out <= c_dp_sosi_rst;
proc_common_wait_until_low(dp_clk, dp_rst); proc_common_wait_until_low(dp_clk, dp_rst);
proc_common_wait_some_cycles(dp_clk, 5); proc_common_wait_some_cycles(dp_clk, 5);
v_long_sync_interval := FALSE;
FOR I IN 0 TO g_nof_sync-1 LOOP FOR I IN 0 TO g_nof_sync-1 LOOP
-- Optionally replace equal period lengths with: shorter, longer, shorter, longer, ... -- Optionally replace equal period lengths with: shorter, longer, shorter, longer, ...
long_sync_interval <= NOT long_sync_interval;
v_nof_data_per_sync := g_nof_data_per_sync; v_nof_data_per_sync := g_nof_data_per_sync;
IF long_sync_interval THEN IF v_long_sync_interval THEN
v_nof_data_per_sync := g_nof_data_per_sync+g_sync_interval_diff; v_nof_data_per_sync := g_nof_data_per_sync+g_nof_data_per_sync_diff;
ELSE --Short interval ELSE --Short interval
v_nof_data_per_sync := g_nof_data_per_sync-g_sync_interval_diff; v_nof_data_per_sync := g_nof_data_per_sync-g_nof_data_per_sync_diff;
END IF; END IF;
v_sosi.sync := '1'; 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 v_sosi.data := RESIZE_DP_DATA(v_sosi.data(g_data_w-1 DOWNTO 0)); -- wrap when >= 2**g_data_w
-- Generate a block of counter data -- Generate a block of counter data
proc_dp_gen_block_data(g_data_w, TO_UINT(v_sosi.data), v_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); proc_dp_gen_block_data(g_data_w, TO_UINT(v_sosi.data), v_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);
v_long_sync_interval := NOT v_long_sync_interval;
END LOOP; END LOOP;
stimuli_done <= '1'; stimuli_done <= '1';
...@@ -173,7 +173,8 @@ BEGIN ...@@ -173,7 +173,8 @@ BEGIN
g_nof_instances => g_nof_instances, g_nof_instances => g_nof_instances,
g_data_w => g_data_w, g_data_w => g_data_w,
g_nof_bins => g_nof_bins, g_nof_bins => g_nof_bins,
g_nof_data_per_sync => g_nof_data_per_sync g_nof_data_per_sync => g_nof_data_per_sync,
g_nof_data_per_sync_diff => g_nof_data_per_sync_diff
) )
PORT MAP ( PORT MAP (
dp_clk => dp_clk, dp_clk => dp_clk,
...@@ -203,28 +204,18 @@ BEGIN ...@@ -203,28 +204,18 @@ BEGIN
-- | 2 | 0 | 1 | 256 addresses * 12 | -- | 2 | 0 | 1 | 256 addresses * 12 |
-- | 3 | 1 | 0 | 256 addresses * 12 | -- | 3 | 1 | 0 | 256 addresses * 12 |
-- +-------------+-------------+----------+-----------------------+ -- +-------------+-------------+----------+-----------------------+
--
-- DC data (increments level every sync: 0, 1, 2, 3, ..):
---+-------------+-------------+----------+-----------------------+
-- | Sync period | RAM written | RAM read | RAM contents |
-- +-------------+-------------+----------+-----------------------+
-- | 0 | 0 | 1 | 256 addresses * 0 |
-- | 1 | 1 | 0 | Addr 1: 1024, others 0|
-- | 2 | 0 | 1 | Addr 2: 1024, others 0|
-- | 3 | 1 | 0 | Addr 3: 1024, others 0|
-- +-------------+-------------+----------+-----------------------+
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
-- Perform MM read and put result in ram_rd_word -- Perform MM read and put result in ram_rd_word
p_verify_mm_read : PROCESS p_verify_mm_read : PROCESS
BEGIN BEGIN
st_histogram_ram_copi.wr <= '0'; st_histogram_ram_copi.wr <= '0';
FOR i IN 0 TO g_nof_sync-1 LOOP FOR i IN 0 TO g_nof_sync-1 LOOP
-- mmp_st_histogram will start copying DP RAM contents to MM RAM 4 cyles after sync -- mmp_st_histogram will start copying DP RAM contents to MM RAM 10 cyles after sync
proc_common_wait_until_high(dp_clk, stimuli_src_out.sync); proc_common_wait_until_high(dp_clk, stimuli_src_out.sync);
proc_common_wait_some_cycles(dp_clk, 4); proc_common_wait_some_cycles(dp_clk, 10);
-- Wait until copying the bins completes -- Wait until copying the bins completes
proc_common_wait_some_cycles(dp_clk, 512); proc_common_wait_some_cycles(dp_clk, g_nof_bins);
-- Start MM reading the bins after some safety cycles -- Start MM reading the bins after some safety cycles
proc_common_wait_some_cycles(mm_clk, 20); proc_common_wait_some_cycles(mm_clk, 20);
...@@ -243,8 +234,11 @@ BEGIN ...@@ -243,8 +234,11 @@ BEGIN
-- Perform verification of ram_rd_word when ram_rd_word_valid -- Perform verification of ram_rd_word when ram_rd_word_valid
p_verify_assert : PROCESS p_verify_assert : PROCESS
VARIABLE v_expected_ram_content_counter : NATURAL;
VARIABLE v_sum_of_bins : NATURAL;
BEGIN BEGIN
verification_done <= '0'; verification_done <= '0';
ver_long_sync_interval <= TRUE;
FOR i IN 0 TO g_nof_sync-1 LOOP FOR i IN 0 TO g_nof_sync-1 LOOP
sum_of_bins <= 0; sum_of_bins <= 0;
proc_common_wait_until_high(dp_clk, stimuli_src_out.sync); proc_common_wait_until_high(dp_clk, stimuli_src_out.sync);
...@@ -253,19 +247,16 @@ BEGIN ...@@ -253,19 +247,16 @@ BEGIN
IF i=0 THEN -- Sync period 0: we expect RAM to contain zeros IF i=0 THEN -- Sync period 0: we expect RAM to contain zeros
ASSERT histogram_data=0 REPORT "RAM contains wrong bin count (expected 0, actual " & INTEGER'IMAGE(histogram_data) & ")" SEVERITY ERROR; ASSERT histogram_data=0 REPORT "RAM contains wrong bin count (expected 0, actual " & INTEGER'IMAGE(histogram_data) & ")" SEVERITY ERROR;
ELSE -- Sync period 1 onwards ELSE -- Sync period 1 onwards
IF g_stimuli_mode="counter" THEN v_expected_ram_content_counter:=c_expected_ram_content_counter;
-- Counter data: bin values remain the same every sync IF ver_long_sync_interval AND j=0 THEN
ASSERT histogram_data=c_expected_ram_content_counter REPORT "RAM contains wrong bin count (expected " & INTEGER'IMAGE(c_expected_ram_content_counter) & ", actual " & INTEGER'IMAGE(histogram_data) & ")" SEVERITY ERROR; -- Long sync interval: more counter values (counter wraps) so lowest bin has double the amount
ELSIF g_stimuli_mode="dc" THEN v_expected_ram_content_counter := 2*c_expected_ram_content_counter;
-- DC data: DC level increments every sync ELSIF ver_long_sync_interval=FALSE AND j=g_nof_bins-1 THEN
IF j=(i/c_nof_levels_per_bin) THEN -- Check bin address and account for multiple levels per bin -- Short sync interval: less counter values (counter does not reach max) so highest bin remains zero
-- this address (j) should contain the DC level total count of this sync period (i) v_expected_ram_content_counter := 0;
ASSERT histogram_data=g_nof_data_per_sync REPORT "RAM contains wrong bin count (expected " & INTEGER'IMAGE(g_nof_data_per_sync) & ", actual " & INTEGER'IMAGE(histogram_data) & ")" SEVERITY ERROR;
ELSE
-- this address should contain zero
ASSERT histogram_data=0 REPORT "RAM contains wrong bin count (expected 0, actual " & INTEGER'IMAGE(histogram_data) & ")" SEVERITY ERROR;
END IF;
END IF; END IF;
-- Check counter data: bin values remain the same every sync
ASSERT histogram_data=v_expected_ram_content_counter REPORT "RAM contains wrong bin count (expected " & INTEGER'IMAGE(v_expected_ram_content_counter) & ", actual " & INTEGER'IMAGE(histogram_data) & ")" SEVERITY ERROR;
END IF; END IF;
sum_of_bins<=sum_of_bins+histogram_data; -- Keep the sum of all bins sum_of_bins<=sum_of_bins+histogram_data; -- Keep the sum of all bins
proc_common_wait_some_cycles(mm_clk, 1); proc_common_wait_some_cycles(mm_clk, 1);
...@@ -273,9 +264,14 @@ BEGIN ...@@ -273,9 +264,14 @@ BEGIN
-- Check the sum of all bins -- Check the sum of all bins
IF i>0 THEN -- Skip sync 0 (histogram still all zeros) IF i>0 THEN -- Skip sync 0 (histogram still all zeros)
ASSERT sum_of_bins=g_nof_data_per_sync REPORT "Sum of bins not equal to g_nof_data_per_sync (expected " & INTEGER'IMAGE(g_nof_data_per_sync) & ", actual " & INTEGER'IMAGE(sum_of_bins) & ")" SEVERITY ERROR; -- Account for g_nof_data_per_sync_diff
v_sum_of_bins := g_nof_data_per_sync-g_nof_data_per_sync_diff;
IF ver_long_sync_interval THEN
v_sum_of_bins := g_nof_data_per_sync+g_nof_data_per_sync_diff;
END IF; END IF;
ASSERT sum_of_bins=v_sum_of_bins REPORT "Sum of bins not equal to g_nof_data_per_sync (expected " & INTEGER'IMAGE(v_sum_of_bins) & ", actual " & INTEGER'IMAGE(sum_of_bins) & ")" SEVERITY ERROR;
END IF;
ver_long_sync_interval <= NOT ver_long_sync_interval;
END LOOP; END LOOP;
verification_done <= '1'; --We have blocking proc_common_wait_until_high procedures above so we need to know if we make it here. verification_done <= '1'; --We have blocking proc_common_wait_until_high procedures above so we need to know if we make it here.
WAIT; WAIT;
...@@ -291,11 +287,11 @@ BEGIN ...@@ -291,11 +287,11 @@ BEGIN
END PROCESS; END PROCESS;
-- Register MOSI to store the read address -- Register MOSI to store the read address
p_clk: PROCESS(dp_rst, dp_clk) IS p_clk: PROCESS(mm_rst, mm_clk) IS
BEGIN BEGIN
IF dp_rst = '1' THEN IF mm_rst = '1' THEN
prv_st_histogram_ram_copi <= c_mem_copi_rst; prv_st_histogram_ram_copi <= c_mem_copi_rst;
ELSIF RISING_EDGE(dp_clk) THEN ELSIF RISING_EDGE(mm_clk) THEN
prv_st_histogram_ram_copi <= st_histogram_ram_copi; prv_st_histogram_ram_copi <= st_histogram_ram_copi;
END IF; END IF;
END PROCESS; END PROCESS;
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment