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

Merge branch 'L2SDP-182' into L2SDP-285

parents e22a54e4 a62a656d
No related branches found
No related tags found
2 merge requests!100Removed text for XSub that is now written in Confluence Subband correlator...,!86Resolve L2SDP-285
......@@ -9,8 +9,11 @@ synth_files =
src/vhdl/reorder_retreive.vhd
src/vhdl/reorder_store.vhd
src/vhdl/reorder_col.vhd
src/vhdl/reorder_col_select.vhd
src/vhdl/reorder_col_wide.vhd
src/vhdl/reorder_col_wide_select.vhd
src/vhdl/reorder_row.vhd
src/vhdl/reorder_row_select.vhd
src/vhdl/reorder_matrix.vhd
src/vhdl/reorder_sequencer.vhd
src/vhdl/reorder_transpose.vhd
......@@ -31,11 +34,13 @@ test_bench_files =
tb/vhdl/tb_reorder_col.vhd
tb/vhdl/tb_tb_reorder_col.vhd
tb/vhdl/tb_reorder_col_wide.vhd
tb/vhdl/tb_reorder_col_wide_row_select.vhd
tb/vhdl/tb_mmf_reorder_matrix.vhd
tb/vhdl/tb_mmf_reorder_row.vhd
tb/vhdl/tb_mms_reorder_rewire.vhd
regression_test_vhdl =
tb/vhdl/tb_reorder_col_wide_row_select.vhd
# tb/vhdl/tb_tb_reorder_col.vhd -- fails in unb2c
......
-------------------------------------------------------------------------------
--
-- 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: Reorder packet
-- Description:
-- Select g_nof_ch_sel complex samples from an input block of g_nof_ch_in
-- complex samples. The subband select map is arbitrary (any order and also
-- duplicates) and can be set via the MM interface.
-- The timing of sync and BSN is passed on in parallel.
-- Remarks:
-- . The g_nof_ch_sel can be <= g_nof_ch_in <= period size, where g_nof_ch_in
-- is the number of valid samples from sop to eop. If g_nof_ch_in is equal to
-- the period size then there are no data invalid cycles during a period.
-- Note that if g_nof_ch_in is less than the period size, then g_nof_ch_sel
-- can be larger than g_nof_ch_in to select channels multiple times.
-- . The g_nof_ch_in defines the number of complex input data words in a data
-- period, so 1 complex sample via sosi.im and sosi.re.
LIBRARY IEEE, common_lib, technology_lib, dp_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 dp_lib.dp_stream_pkg.ALL;
USE technology_lib.technology_select_pkg.ALL;
ENTITY reorder_col_select IS
GENERIC (
g_technology : NATURAL := c_tech_select_default;
g_dsp_data_w : NATURAL := 18;
g_nof_ch_in : NATURAL := 1024;
g_nof_ch_sel : NATURAL := 12; -- g_nof_ch_sel < g_nof_ch_in
g_use_complex : BOOLEAN := TRUE
);
PORT (
dp_rst : IN STD_LOGIC;
dp_clk : IN STD_LOGIC;
-- Memory Mapped
col_select_mosi : IN t_mem_mosi; -- channel select control on DP clk
col_select_miso : OUT t_mem_miso := c_mem_miso_rst; -- only waitrequest is used
-- Streaming
input_sosi : IN t_dp_sosi; -- complex input
output_sosi : OUT t_dp_sosi -- selected complex output with flow control
);
END reorder_col_select;
ARCHITECTURE str OF reorder_col_select IS
CONSTANT c_store_buf : t_c_mem := (latency => 1,
adr_w => ceil_log2(g_nof_ch_in),
dat_w => c_nof_complex*g_dsp_data_w,
nof_dat => g_nof_ch_in,
init_sl => '0'); -- ST side : stat_mosi
CONSTANT c_data_nof_pages : NATURAL := 2; -- fixed dual page SS
CONSTANT c_info_nof_pages : NATURAL := 2; -- fixed, fits the dual page block latency and logic latency of the SS
CONSTANT c_retrieve_lat : NATURAL := c_store_buf.latency + 1; -- = 2 rd_latency from waitrequest + store_buf latency
SIGNAL info_sop_wr_en : STD_LOGIC_VECTOR(c_info_nof_pages-1 DOWNTO 0);
SIGNAL info_eop_wr_en : STD_LOGIC_VECTOR(c_info_nof_pages-1 DOWNTO 0);
SIGNAL info_sosi : t_dp_sosi;
SIGNAL store_mosi : t_mem_mosi;
SIGNAL store_done : STD_LOGIC;
SIGNAL i_col_select_miso : t_mem_miso := c_mem_miso_rst;
SIGNAL ch_cnt : INTEGER RANGE 0 TO g_nof_ch_sel-1;
SIGNAL nxt_ch_cnt : INTEGER;
SIGNAL retrieve_sosi : t_dp_sosi;
SIGNAL retrieve_en : STD_LOGIC;
SIGNAL retrieve_sop_dly : STD_LOGIC_VECTOR(0 TO c_retrieve_lat);
SIGNAL retrieve_eop_dly : STD_LOGIC_VECTOR(0 TO c_retrieve_lat);
BEGIN
u_store : ENTITY work.reorder_store
GENERIC MAP (
g_dsp_data_w => g_dsp_data_w,
g_nof_ch_in => g_nof_ch_in,
g_use_complex => g_use_complex
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
-- Streaming
input_sosi => input_sosi,
-- Timing
store_done => store_done,
-- Write store buffer control
store_mosi => store_mosi
);
u_store_buf : ENTITY common_lib.common_paged_ram_r_w
GENERIC MAP (
g_technology => g_technology,
g_str => "use_adr",
g_data_w => c_store_buf.dat_w,
g_nof_pages => c_data_nof_pages,
g_page_sz => c_store_buf.nof_dat,
g_wr_start_page => 0,
g_rd_start_page => 1,
g_rd_latency => 1
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
wr_next_page => store_done,
wr_adr => store_mosi.address(c_store_buf.adr_w-1 DOWNTO 0),
wr_en => store_mosi.wr,
wr_dat => store_mosi.wrdata(c_store_buf.dat_w-1 DOWNTO 0),
rd_next_page => store_done,
rd_adr => col_select_mosi.address(c_store_buf.adr_w-1 DOWNTO 0),
rd_en => col_select_mosi.rd,
rd_dat => i_col_select_miso.rddata(c_store_buf.dat_w-1 DOWNTO 0),
rd_val => i_col_select_miso.rdval
);
-- Enable retrieve when a block has been stored, disable retrieve when the block has been output
u_retrieve_en : ENTITY common_lib.common_switch
GENERIC MAP (
g_rst_level => '0',
g_priority_lo => FALSE, -- store_done has priority over nxt_retrieve_done when they occur simultaneously
g_or_high => TRUE,
g_and_low => FALSE
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
switch_high => store_done,
switch_low => retrieve_eop_dly(0),
out_level => retrieve_en
);
p_reg : PROCESS (dp_clk, dp_rst)
BEGIN
IF dp_rst = '1' THEN
-- Internal registers.
ch_cnt <= 0;
retrieve_sop_dly(1 TO c_retrieve_lat) <= (OTHERS=>'0');
retrieve_eop_dly(1 TO c_retrieve_lat) <= (OTHERS=>'0');
ELSIF rising_edge(dp_clk) THEN
-- Internal registers.
ch_cnt <= nxt_ch_cnt;
retrieve_sop_dly(1 TO c_retrieve_lat) <= retrieve_sop_dly(0 TO c_retrieve_lat-1);
retrieve_eop_dly(1 TO c_retrieve_lat) <= retrieve_eop_dly(0 TO c_retrieve_lat-1);
END IF;
END PROCESS;
p_ch_cnt : PROCESS (retrieve_en, ch_cnt)
BEGIN
nxt_ch_cnt <= ch_cnt;
col_select_miso.waitrequest <= '1';
IF retrieve_en='1' THEN
col_select_miso.waitrequest <= '0';
IF ch_cnt=g_nof_ch_sel-1 THEN
nxt_ch_cnt <= 0;
ELSE
nxt_ch_cnt <= ch_cnt + 1;
END IF;
END IF;
END PROCESS;
-- Optional SS output frame control
retrieve_sop_dly(0) <= '1' WHEN retrieve_en='1' AND ch_cnt=0 ELSE '0';
retrieve_eop_dly(0) <= '1' WHEN retrieve_en='1' AND ch_cnt=g_nof_ch_sel-1 ELSE '0';
retrieve_sosi.re <= RESIZE_DP_DSP_DATA(i_col_select_miso.rddata( g_dsp_data_w-1 DOWNTO 0));
retrieve_sosi.im <= RESIZE_DP_DSP_DATA(i_col_select_miso.rddata(c_nof_complex*g_dsp_data_w-1 DOWNTO g_dsp_data_w));
retrieve_sosi.data <= RESIZE_DP_DATA(i_col_select_miso.rddata( c_nof_complex*g_dsp_data_w-1 DOWNTO 0));
retrieve_sosi.valid <= i_col_select_miso.rdval;
retrieve_sosi.sop <= retrieve_sop_dly(c_retrieve_lat);
retrieve_sosi.eop <= retrieve_eop_dly(c_retrieve_lat);
-- Page delay the input_sosi info (sync, BSN, channel at sop and err, empty at eop) and combine it with the retrieved SS data to get the output_sosi
info_sop_wr_en <= input_sosi.sop & store_done;
info_eop_wr_en <= input_sosi.eop & store_done;
u_info_sosi : ENTITY dp_lib.dp_paged_sop_eop_reg
GENERIC MAP (
g_nof_pages => c_info_nof_pages
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
-- page write enable ctrl
sop_wr_en => info_sop_wr_en,
eop_wr_en => info_eop_wr_en,
-- ST sink
snk_in => input_sosi,
-- ST source
src_out => info_sosi
);
output_sosi <= func_dp_stream_combine_info_and_data(info_sosi, retrieve_sosi);
END str;
-------------------------------------------------------------------------------
--
-- 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: Select and/or reorder data on multiple streams.
--
-- Description:
-- Reorder-col unit that handles a stream that consists of
-- multiple (g_nof_inputs) input streams.
--
--
-- Remarks:
--
LIBRARY IEEE, common_lib, technology_lib, dp_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 dp_lib.dp_stream_pkg.ALL;
USE technology_lib.technology_select_pkg.ALL;
ENTITY reorder_col_wide_select IS
GENERIC (
g_technology : NATURAL := c_tech_select_default;
g_nof_inputs : NATURAL := 6;
g_dsp_data_w : NATURAL := 18;
g_nof_ch_in : NATURAL := 1024;
g_nof_ch_sel : NATURAL := 12; -- g_nof_ch_sel < g_nof_ch_in
g_use_complex : BOOLEAN := TRUE
);
PORT (
dp_rst : IN STD_LOGIC;
dp_clk : IN STD_LOGIC;
-- Memory Mapped
col_select_mosi : IN t_mem_mosi; -- channel select control
col_select_miso : OUT t_mem_miso; -- only used for waitrequest
-- Streaming
input_sosi_arr : IN t_dp_sosi_arr(g_nof_inputs-1 DOWNTO 0); -- complex input
input_siso_arr : OUT t_dp_siso_arr(g_nof_inputs-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy); -- complex input
output_sosi_arr : OUT t_dp_sosi_arr(g_nof_inputs-1 DOWNTO 0) -- selected complex output with flow control
);
END reorder_col_wide_select;
ARCHITECTURE str OF reorder_col_wide_select IS
SIGNAL col_select_miso_arr : t_mem_miso_arr(g_nof_inputs-1 DOWNTO 0);
BEGIN
col_select_miso <= col_select_miso_arr(0); -- All inputs have the same mosi/miso
---------------------------------------------------------------
-- INSTANTIATE MULTIPLE SINGLE CHANNEL SUBBAND SELECT UNITS
---------------------------------------------------------------
gen_ss_singles : FOR I IN 0 TO g_nof_inputs-1 GENERATE
u_single_ss : ENTITY work.reorder_col_select
GENERIC MAP (
g_technology => g_technology,
g_dsp_data_w => g_dsp_data_w,
g_nof_ch_in => g_nof_ch_in,
g_nof_ch_sel => g_nof_ch_sel,
g_use_complex => g_use_complex
)
PORT MAP (
dp_rst => dp_rst,
dp_clk => dp_clk,
-- Memory Mapped
col_select_mosi => col_select_mosi,
col_select_miso => col_select_miso_arr(I),
-- Streaming
input_sosi => input_sosi_arr(I),
output_sosi => output_sosi_arr(I)
);
END GENERATE;
END str;
-------------------------------------------------------------------------------
--
-- 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: Subband Select Reordering.
--
-- Description: For every clock cycle within a frame a different output
-- configuration can be created, based on the available inputs.
--
-- The in_select input defines the mapping of the inputs to the outputs
-- for a single clock cylce.
--
-- Remarks:
-- in_select has to be defined 1 clock cycle after the in_sosi data.
LIBRARY IEEE, common_lib, technology_lib, dp_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 dp_lib.dp_stream_pkg.ALL;
USE technology_lib.technology_select_pkg.ALL;
ENTITY reorder_row_select IS
GENERIC (
g_technology : NATURAL := c_tech_select_default;
g_dsp_data_w : NATURAL := 16;
g_nof_inputs : NATURAL := 8;
g_nof_outputs : NATURAL := 16;
g_pipeline_in : NATURAL := 1; -- pipeline in_data
g_pipeline_in_m : NATURAL := 1; -- pipeline in_data for M-fold fan out
g_pipeline_out : NATURAL := 1 -- pipeline out_data
);
PORT (
dp_rst : IN STD_LOGIC;
dp_clk : IN STD_LOGIC;
-- Streaming
input_sosi_arr : IN t_dp_sosi_arr(g_nof_inputs-1 DOWNTO 0);
output_sosi_arr : OUT t_dp_sosi_arr(g_nof_outputs-1 DOWNTO 0);
in_select : IN STD_LOGIC_VECTOR(g_nof_outputs*ceil_log2(g_nof_inputs)-1 DOWNTO 0)
);
END reorder_row_select;
ARCHITECTURE str OF reorder_row_select IS
CONSTANT c_tot_pipeline : NATURAL := g_pipeline_in + g_pipeline_in_m + g_pipeline_out + 1; --+1 for regs process
CONSTANT c_data_w : NATURAL := g_dsp_data_w*c_nof_complex;
TYPE t_dp_sosi_2arr IS ARRAY (INTEGER RANGE <>) OF t_dp_sosi_arr(g_nof_inputs-1 DOWNTO 0);
TYPE reg_type IS RECORD
pipe_sosi_2arr : t_dp_sosi_2arr(c_tot_pipeline-1 DOWNTO 0);
output_sosi_arr : t_dp_sosi_arr(g_nof_outputs-1 DOWNTO 0);
END RECORD;
SIGNAL r, rin : reg_type;
SIGNAL reorder_in_dat : STD_LOGIC_VECTOR(g_nof_inputs*c_data_w-1 DOWNTO 0);
SIGNAL reorder_out_dat : STD_LOGIC_VECTOR(g_nof_outputs*c_data_w-1 DOWNTO 0);
BEGIN
---------------------------------------------------------------
-- PREPARE THE INPUT DATA.
--
-- Use a delayed version of the input data to correct for the
-- delay that is introduced by the read latency of the
-- selection buffer.
---------------------------------------------------------------
gen_input : FOR I IN g_nof_inputs-1 DOWNTO 0 GENERATE
reorder_in_dat((I+1)*c_data_w-1 DOWNTO I*c_data_w) <= r.pipe_sosi_2arr(0)(I).im(g_dsp_data_w-1 DOWNTO 0) &
r.pipe_sosi_2arr(0)(I).re(g_dsp_data_w-1 DOWNTO 0);
END GENERATE;
---------------------------------------------------------------
-- EXECUTE SELECTION
--
-- Selection is performed based on the setting of the
-- in_select signal.
---------------------------------------------------------------
u_reorder : ENTITY common_lib.common_select_m_symbols
GENERIC MAP (
g_nof_input => g_nof_inputs,
g_nof_output => g_nof_outputs,
g_symbol_w => c_data_w,
g_pipeline_in => g_pipeline_in,
g_pipeline_in_m => g_pipeline_in_m,
g_pipeline_out => g_pipeline_out
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
in_data => reorder_in_dat,
in_select => in_select,
out_data => reorder_out_dat
);
---------------------------------------------------------------
-- REGISTERING AND PIPELINING
--
-- This process takes care of registering the incoming SOSI
-- array and the pipelining for all SOSI control fields.
-- Also the data-output of the select_m_symbols block is merged
-- here with the rest of the pipelined SOSI signals.
---------------------------------------------------------------
comb : PROCESS(r, input_sosi_arr, reorder_out_dat)
VARIABLE v : reg_type;
BEGIN
v := r;
v.pipe_sosi_2arr(0) := input_sosi_arr;
v.pipe_sosi_2arr(c_tot_pipeline-1 DOWNTO 1) := r.pipe_sosi_2arr(c_tot_pipeline-2 DOWNTO 0);
-- Merge data output to the outgoing SOSI record.
FOR I IN g_nof_outputs-1 DOWNTO 0 LOOP
v.output_sosi_arr(I) := r.pipe_sosi_2arr(c_tot_pipeline-1)(0);
v.output_sosi_arr(I).im := RESIZE_DP_DSP_DATA(reorder_out_dat((I+1)*c_data_w-1 DOWNTO I*c_data_w + g_dsp_data_w));
v.output_sosi_arr(I).re := RESIZE_DP_DSP_DATA(reorder_out_dat((I+1)*c_data_w-g_dsp_data_w-1 DOWNTO I*c_data_w));
END LOOP;
rin <= v;
END PROCESS comb;
regs : PROCESS(dp_clk)
BEGIN
IF rising_edge(dp_clk) THEN
r <= rin;
END IF;
END PROCESS;
output_sosi_arr <= r.output_sosi_arr;
END str;
-------------------------------------------------------------------------------
--
-- 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
-- Usage:
-- > as 10
-- > run -all
-- . Observe in_sosi_arr and out_sosi_arr in the Wave window
--
-- Description:
LIBRARY IEEE, common_lib, dp_lib;
USE IEEE.std_logic_1164.ALL;
USE common_lib.common_pkg.ALL;
USE common_lib.common_mem_pkg.ALL;
USE common_lib.tb_common_pkg.ALL;
USE common_lib.tb_common_mem_pkg.ALL;
USE common_lib.common_lfsr_sequences_pkg.ALL;
USE dp_lib.dp_stream_pkg.ALL;
USE dp_lib.tb_dp_pkg.ALL;
ENTITY tb_reorder_col_wide_row_select IS
END tb_reorder_col_wide_row_select;
ARCHITECTURE tb OF tb_reorder_col_wide_row_select IS
CONSTANT c_clk_period : TIME := 10 ns;
CONSTANT c_rl : NATURAL := 1;
CONSTANT c_dsp_data_w : NATURAL := 16;
CONSTANT c_nof_sync : NATURAL := 5;
CONSTANT c_nof_inputs : NATURAL := 6;
CONSTANT c_nof_outputs : NATURAL := 2;
CONSTANT c_nof_ch_in : NATURAL := 1024;
CONSTANT c_nof_ch_sel_row : NATURAL := c_nof_inputs;
CONSTANT c_nof_ch_sel_col : NATURAL := 2;
CONSTANT c_nof_ch_sel_offset : NATURAL := 2;
CONSTANT c_ch_sel_offsets : t_natural_arr(0 TO c_nof_ch_sel_offset-1) := (0, 16);
CONSTANT c_ch_sel_step : NATURAL := 3;
CONSTANT c_nof_ch_sel : NATURAL := c_nof_ch_sel_offset*c_nof_ch_sel_col*c_nof_ch_sel_row;
CONSTANT c_nof_block_per_sync : NATURAL := 4;
CONSTANT c_nof_inputs_w : NATURAL := ceil_log2(c_nof_inputs);
CONSTANT c_in_select_w : NATURAL := c_nof_outputs*c_nof_inputs_w;
CONSTANT c_in_select_dly : NATURAL := 2;
SIGNAL rst : STD_LOGIC;
SIGNAL clk : STD_LOGIC := '1';
SIGNAL tb_end : STD_LOGIC;
SIGNAL mm_mosi : t_mem_mosi;
SIGNAL mm_miso : t_mem_miso;
SIGNAL st_en : STD_LOGIC := '1';
SIGNAL st_siso_arr : t_dp_siso_arr(c_nof_inputs-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy);
SIGNAL st_sosi_arr : t_dp_sosi_arr(c_nof_inputs-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
SIGNAL exp_sosi_arr : t_dp_sosi_arr(c_nof_outputs-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
SIGNAL exp_siso_arr : t_dp_siso_arr(c_nof_outputs-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy);
SIGNAL bsn : NATURAL := 10;
SIGNAL in_sosi_arr : t_dp_sosi_arr(c_nof_inputs-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
SIGNAL out_siso_arr : t_dp_siso_arr(c_nof_inputs-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy);
SIGNAL col_wide_select_sosi_arr : t_dp_sosi_arr(c_nof_inputs-1 DOWNTO 0);
SIGNAL out_sosi_arr : t_dp_sosi_arr(c_nof_outputs-1 DOWNTO 0);
SIGNAL dly_out_sosi_arr : t_dp_sosi_arr(c_nof_outputs-1 DOWNTO 0);
SIGNAL reorder_row_in_select : STD_LOGIC_VECTOR(c_in_select_w-1 DOWNTO 0);
SIGNAL in_select : STD_LOGIC_VECTOR(c_in_select_w-1 DOWNTO 0);
BEGIN
clk <= (NOT clk) OR tb_end AFTER c_clk_period/2;
rst <= '1', '0' AFTER c_clk_period*7;
-- MM domain
p_mm_stimuli : PROCESS
VARIABLE k : NATURAL;
BEGIN
FOR rep IN 0 TO c_nof_sync*c_nof_block_per_sync-1 LOOP
k := c_nof_ch_sel_col * (rep/c_nof_block_per_sync) * c_ch_sel_step;
mm_mosi <= c_mem_mosi_rst;
proc_common_wait_until_low(clk, mm_miso.waitrequest);
FOR I IN 0 TO c_nof_ch_sel_offset-1 LOOP
FOR row IN 0 TO c_nof_ch_sel_row-1 LOOP
FOR col IN 0 TO c_nof_ch_sel_col-1 LOOP
FOR i_out IN 0 TO c_nof_outputs-1 LOOP
reorder_row_in_select((i_out+1)* c_nof_inputs_w -1 DOWNTO i_out * c_nof_inputs_w) <= TO_UVEC(row, c_nof_inputs_w);
END LOOP;
proc_mem_mm_bus_rd(c_ch_sel_offsets(I)+col+k, clk, mm_mosi);
END LOOP;
END LOOP;
END LOOP;
END LOOP;
WAIT;
END PROCESS;
u_pipe_in_select : ENTITY common_lib.common_pipeline
GENERIC MAP(
g_pipeline => c_in_select_dly,
g_in_dat_w => c_in_select_w,
g_out_dat_w => c_in_select_w
)
PORT MAP(
rst => rst,
clk => clk,
in_dat => reorder_row_in_select,
out_dat => in_select
);
------------------------------------------------------------------------------
-- Data blocks
------------------------------------------------------------------------------
gen_stimuli : FOR K IN 0 TO c_nof_inputs-1 GENERATE
p_st_stimuli : PROCESS
VARIABLE v_re : NATURAL := 0+k*2**5;
VARIABLE v_im : NATURAL := 1+k*2**5;
BEGIN
tb_end <= '0';
st_sosi_arr(K) <= c_dp_sosi_rst;
proc_common_wait_until_low(clk, rst);
-- Run some sync intervals with DSP counter data for the real and imag fields
WAIT UNTIL rising_edge(clk);
FOR I IN 0 TO c_nof_sync-1 LOOP
proc_dp_gen_block_data(c_rl, FALSE, c_dsp_data_w, c_dsp_data_w, 0, v_re, v_im, c_nof_ch_in, 0, 0, '1', "0", clk, st_en, st_siso_arr(K), st_sosi_arr(K)); -- next sync
v_re := v_re + c_nof_ch_in;
v_im := v_im + c_nof_ch_in;
FOR J IN 0 TO c_nof_block_per_sync-2 LOOP -- provide sop and eop for block reference
proc_dp_gen_block_data(c_rl, FALSE, c_dsp_data_w, c_dsp_data_w, 0, v_re, v_im, c_nof_ch_in, 0, 0, '0', "0", clk, st_en, st_siso_arr(K), st_sosi_arr(K)); -- no sync
v_re := v_re + c_nof_ch_in;
v_im := v_im + c_nof_ch_in;
END LOOP;
END LOOP;
st_sosi_arr(K) <= c_dp_sosi_rst;
proc_common_wait_some_cycles(clk, 10);
tb_end <= '1';
WAIT;
END PROCESS;
END GENERATE;
-- Time stimuli
bsn <= bsn + 1 WHEN rising_edge(clk) AND (st_sosi_arr(0).eop='1'); -- OR st_sosi.sync='1');
-- Add BSN to the ST data
p_in_sosi : PROCESS(st_sosi_arr, bsn)
BEGIN
FOR I IN 0 TO c_nof_inputs-1 LOOP
in_sosi_arr(I) <= st_sosi_arr(I);
in_sosi_arr(I).bsn <= TO_DP_BSN(bsn);
END LOOP;
END PROCESS;
------------------------------------------------------------------------------
-- Verification
------------------------------------------------------------------------------
u_pipeline_arr : ENTITY dp_lib.dp_pipeline_arr
GENERIC MAP (
g_nof_streams => c_nof_outputs
)
PORT MAP (
rst => rst,
clk => clk,
snk_in_arr => out_sosi_arr,
src_out_arr => dly_out_sosi_arr
);
gen_verify : FOR O IN 0 TO c_nof_outputs-1 GENERATE
p_generate_exp_data : PROCESS
VARIABLE v_col : NATURAL := 0;
VARIABLE v_row : NATURAL := 0;
VARIABLE v_offset : NATURAL := 0;
VARIABLE v_sync_ix : NATURAL := 0;
VARIABLE v_k : NATURAL := 0;
BEGIN
FOR I IN 0 TO c_nof_sync*c_nof_block_per_sync-1 LOOP
exp_sosi_arr(O) <= c_dp_sosi_rst;
proc_common_wait_until_high(clk, out_sosi_arr(0).sop);
FOR J IN 0 TO c_nof_ch_sel-1 LOOP
v_sync_ix := I / c_nof_block_per_sync;
v_offset := J / (c_nof_ch_sel_col*c_nof_ch_sel_row);
v_col := J MOD c_nof_ch_sel_col;
v_row := (J/c_nof_ch_sel_col) MOD c_nof_ch_sel_row;
v_k := c_nof_ch_sel_col * v_sync_ix * c_ch_sel_step;
exp_sosi_arr(O) <= c_dp_sosi_rst;
exp_sosi_arr(O).valid <= '1';
IF J = 0 THEN
exp_sosi_arr(O).sop <= '1';
IF I MOD c_nof_block_per_sync = 0 THEN
exp_sosi_arr(O).sync <= '1';
END IF;
ELSIF j = c_nof_ch_sel-1 THEN
exp_sosi_arr(O).eop <= '1';
END IF;
exp_sosi_arr(O).re <= TO_DP_DSP_DATA( I * c_nof_ch_in + v_k + c_ch_sel_offsets(v_offset) + v_col + v_row*2**5);
exp_sosi_arr(O).im <= TO_DP_DSP_DATA(1+ I * c_nof_ch_in + v_k + c_ch_sel_offsets(v_offset) + v_col + v_row*2**5);
proc_common_wait_some_cycles(clk, 1);
END LOOP;
END LOOP;
WAIT;
END PROCESS;
p_verify_out_sosi : PROCESS(clk)
BEGIN
IF rising_edge(clk) THEN
ASSERT dly_out_sosi_arr(O).valid = exp_sosi_arr(O).valid REPORT "Wrong out_sosi.valid" SEVERITY ERROR;
ASSERT dly_out_sosi_arr(O).sop = exp_sosi_arr(O).sop REPORT "Wrong out_sosi.sop" SEVERITY ERROR;
ASSERT dly_out_sosi_arr(O).eop = exp_sosi_arr(O).eop REPORT "Wrong out_sosi.eop" SEVERITY ERROR;
ASSERT dly_out_sosi_arr(O).sync = exp_sosi_arr(O).sync REPORT "Wrong out_sosi.sync" SEVERITY ERROR;
IF exp_sosi_arr(O).valid = '1' THEN
ASSERT dly_out_sosi_arr(O).re = exp_sosi_arr(O).re REPORT "Wrong out_sosi.re" SEVERITY ERROR;
ASSERT dly_out_sosi_arr(O).im = exp_sosi_arr(O).im REPORT "Wrong out_sosi.im" SEVERITY ERROR;
END IF;
END IF;
END PROCESS;
END GENERATE;
u_dut_col : ENTITY work.reorder_col_wide_select
GENERIC MAP (
g_nof_inputs => c_nof_inputs,
g_dsp_data_w => c_dsp_data_w,
g_nof_ch_in => c_nof_ch_in,
g_nof_ch_sel => c_nof_ch_sel
)
PORT MAP (
dp_rst => rst,
dp_clk => clk,
-- Memory Mapped
col_select_mosi => mm_mosi,
col_select_miso => mm_miso,
-- Streaming
input_sosi_arr => in_sosi_arr,
output_sosi_arr => col_wide_select_sosi_arr
);
u_dut_row : ENTITY work.reorder_row_select
GENERIC MAP (
g_dsp_data_w => c_dsp_data_w,
g_nof_inputs => c_nof_inputs,
g_nof_outputs => c_nof_outputs
)
PORT MAP (
dp_rst => rst,
dp_clk => clk,
in_select => in_select,
-- Streaming
input_sosi_arr => col_wide_select_sosi_arr,
output_sosi_arr => out_sosi_arr
);
END tb;
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment