Skip to content
Snippets Groups Projects
Commit bb673e6c authored by Pepping's avatar Pepping
Browse files

Svn copy from $UNB

parent 8e9aa9af
No related branches found
No related tags found
No related merge requests found
-------------------------------------------------------------------------------
--
-- Copyright (C) 2011
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_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;
-- Purpose: Subband select
-- 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. In LOFAR a subband sample was defined as a dual pol subband, so a
-- pair of complex samples, but here instead the subband is defined as a
-- single signal path sample, so 1 complex sample via sosi.im and sosi.re.
-- . In LOFAR the channel select buffer was dual page, to ensure that the page
-- switch happens aligned with the sync. However typically the select buffer
-- only needs to be set once and remains fixed during a measurement.
-- Therefore the channel select buffer can be a single page memory.
-- . In LOFAR the selected channels were also output time multiplexed. This
-- was possible because g_nof_ch_sel <= g_nof_ch_in/2. Here the output is not
-- time multiplexed. If time multiplexing is needed then a separate component
-- needs to be used for this. For this purpose the ss_retrieve streaming
-- source supports the ready signal. Typically output_siso.ready='1', but
-- when g_nof_ch_sel < g_nof_ch_in/2, then a toggling output_siso.ready can
-- be used to multiplex this SS output with another SS output stream.
-- . The SS streaming sink does not support the input_siso signal, because it
-- is assumed that the SS source is always fast enough. The SS sink could
-- support the input_siso signal, e.g. based on store_done and retrieve_done.
ENTITY ss IS
GENERIC (
g_use_output_rl_adapter : BOOLEAN := FALSE; -- when true adapt output RL to 1 else the output RL is equal to c_retrieve_lat=2 which is fine if no flow control is needed.
g_dsp_data_w : NATURAL := 18;
g_nof_ch_in : NATURAL := 512;
g_nof_ch_sel : NATURAL := 252; -- g_nof_ch_sel < g_nof_ch_in
g_select_file_name : STRING := "UNUSED";
g_use_complex : BOOLEAN := TRUE
);
PORT (
mm_rst : IN STD_LOGIC;
mm_clk : IN STD_LOGIC;
dp_rst : IN STD_LOGIC;
dp_clk : IN STD_LOGIC;
-- Memory Mapped
ram_ss_ss_mosi : IN t_mem_mosi; -- channel select control
ram_ss_ss_miso : OUT t_mem_miso;
-- Streaming
input_sosi : IN t_dp_sosi; -- complex input
input_siso : OUT t_dp_siso; -- complex input
output_sosi : OUT t_dp_sosi; -- selected complex output with flow control
output_siso : IN t_dp_siso := c_dp_siso_rdy
);
END ss;
ARCHITECTURE str OF ss 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_select_buf : t_c_mem := (latency => 1,
adr_w => ceil_log2(g_nof_ch_sel),
dat_w => ceil_log2(g_nof_ch_in),
nof_dat => g_nof_ch_sel,
init_sl => '0');
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_select_buf.latency + c_store_buf.latency; -- = 2
CONSTANT c_output_rl : NATURAL := sel_a_b(g_use_output_rl_adapter, 1, c_retrieve_lat); -- force SS RL from 2 -> 1 or leave it at 2
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 retrieve_mosi : t_mem_mosi := c_mem_mosi_rst;
SIGNAL retrieve_miso : t_mem_miso := c_mem_miso_rst;
SIGNAL retrieve_done : STD_LOGIC;
SIGNAL select_mosi : t_mem_mosi := c_mem_mosi_rst;
SIGNAL select_miso : t_mem_miso := c_mem_miso_rst;
SIGNAL retrieve_sosi : t_dp_sosi;
SIGNAL retrieve_siso : t_dp_siso;
SIGNAL ss_sosi : t_dp_sosi;
SIGNAL ss_siso : t_dp_siso;
BEGIN
-----------------------------------------------------------------------------
-- Throttle the incoming streams so they provide a consistent packet flow
-- (no bursting) by enforcing a minimum period of g_nof_ch_sel
-----------------------------------------------------------------------------
u_dp_throttle_sop : ENTITY dp_lib.dp_throttle_sop
GENERIC MAP (
g_period => g_nof_ch_sel
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
snk_out => input_siso,
snk_in => input_sosi
);
u_store : ENTITY work.ss_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_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 => 0,
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 => retrieve_done,
rd_adr => retrieve_mosi.address(c_store_buf.adr_w-1 DOWNTO 0),
rd_en => retrieve_mosi.rd,
rd_dat => retrieve_miso.rddata(c_store_buf.dat_w-1 DOWNTO 0),
rd_val => retrieve_miso.rdval
);
u_select_buf : ENTITY common_lib.common_ram_crw_crw
GENERIC MAP (
g_ram => c_select_buf,
g_init_file => g_select_file_name
)
PORT MAP (
-- MM side
rst_a => mm_rst,
clk_a => mm_clk,
wr_en_a => ram_ss_ss_mosi.wr,
wr_dat_a => ram_ss_ss_mosi.wrdata(c_select_buf.dat_w-1 DOWNTO 0),
adr_a => ram_ss_ss_mosi.address(c_select_buf.adr_w-1 DOWNTO 0),
rd_en_a => ram_ss_ss_mosi.rd,
rd_dat_a => ram_ss_ss_miso.rddata(c_select_buf.dat_w-1 DOWNTO 0),
rd_val_a => ram_ss_ss_miso.rdval,
-- ST side
rst_b => dp_rst,
clk_b => dp_clk,
wr_en_b => select_mosi.wr,
wr_dat_b => select_mosi.wrdata(c_select_buf.dat_w-1 DOWNTO 0),
adr_b => select_mosi.address(c_select_buf.adr_w-1 DOWNTO 0),
rd_en_b => select_mosi.rd,
rd_dat_b => select_miso.rddata(c_select_buf.dat_w-1 DOWNTO 0),
rd_val_b => select_miso.rdval
);
u_retrieve : ENTITY work.ss_retrieve
GENERIC MAP (
g_dsp_data_w => g_dsp_data_w,
g_nof_ch_in => g_nof_ch_in,
g_nof_ch_sel => g_nof_ch_sel
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
-- Timing
store_done => store_done,
-- Read store_buf control
retrieve_mosi => retrieve_mosi,
retrieve_miso => retrieve_miso,
retrieve_done => retrieve_done,
-- Read select_buf control
select_mosi => select_mosi,
select_miso => select_miso,
-- Streaming
output_sosi => retrieve_sosi,
output_siso => retrieve_siso
);
u_rl : ENTITY dp_lib.dp_latency_adapter -- defaults to wires when c_output_rl = c_retrieve_lat
GENERIC MAP (
g_in_latency => c_retrieve_lat,
g_out_latency => c_output_rl
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
-- ST sink
snk_out => retrieve_siso,
snk_in => retrieve_sosi,
-- ST source
src_in => ss_siso,
src_out => ss_sosi
);
-- 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, ss_sosi);
ss_siso <= output_siso;
END str;
-------------------------------------------------------------------------------
--
-- Copyright (C) 2011
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_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;
-- Purpose: Select and/or reorder data on multiple streams.
--
-- Description:
-- Subband select unit that handles a stream that consists of
-- multiple (g_wb_factor) input streams.
-- It assumes that the g_nof_ch_in input channels are equally
-- distributed over the g_wb_factor input streams.
--
--
-- Remarks:
--
ENTITY ss_wide IS
GENERIC (
g_wb_factor : NATURAL := 4;
g_dsp_data_w : NATURAL := 18;
g_nof_ch_in : NATURAL := 256;
g_nof_ch_sel : NATURAL := 192; -- g_nof_ch_sel < g_nof_ch_in
g_select_file_prefix : STRING := "UNUSED";
g_use_complex : BOOLEAN := TRUE
);
PORT (
mm_rst : IN STD_LOGIC;
mm_clk : IN STD_LOGIC;
dp_rst : IN STD_LOGIC;
dp_clk : IN STD_LOGIC;
-- Memory Mapped
ram_ss_ss_wide_mosi : IN t_mem_mosi; -- channel select control
ram_ss_ss_wide_miso : OUT t_mem_miso;
-- Streaming
input_sosi_arr : IN t_dp_sosi_arr(g_wb_factor-1 DOWNTO 0); -- complex input
input_siso_arr : OUT t_dp_siso_arr(g_wb_factor-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy); -- complex input
output_sosi_arr : OUT t_dp_sosi_arr(g_wb_factor-1 DOWNTO 0); -- selected complex output with flow control
output_siso_arr : IN t_dp_siso_arr(g_wb_factor-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy)
);
END ss_wide;
ARCHITECTURE str OF ss_wide IS
CONSTANT c_mem_addr_w : NATURAL := ceil_log2(g_nof_ch_sel);
CONSTANT c_nof_ch_in : NATURAL := g_nof_ch_in;
CONSTANT c_nof_ch_sel : NATURAL := g_nof_ch_sel;
SIGNAL ram_ss_ss_wide_mosi_arr : t_mem_mosi_arr(g_wb_factor-1 DOWNTO 0);
SIGNAL ram_ss_ss_wide_miso_arr : t_mem_miso_arr(g_wb_factor-1 DOWNTO 0) := (OTHERS => c_mem_miso_rst);
BEGIN
---------------------------------------------------------------
-- COMBINE MEMORY MAPPED INTERFACES
---------------------------------------------------------------
-- Combine the internal array of mm interfaces for the selection
-- memory to one array that is connected to the port of the ss_wide wunit
u_mem_mux_select : entity common_lib.common_mem_mux
generic map (
g_nof_mosi => g_wb_factor,
g_mult_addr_w => c_mem_addr_w
)
port map (
mosi => ram_ss_ss_wide_mosi,
miso => ram_ss_ss_wide_miso,
mosi_arr => ram_ss_ss_wide_mosi_arr,
miso_arr => ram_ss_ss_wide_miso_arr
);
---------------------------------------------------------------
-- INSTANTIATE MULTIPLE SINGLE CHANNEL SUBBAND SELECT UNITS
---------------------------------------------------------------
gen_ss_singles : FOR I IN 0 TO g_wb_factor-1 GENERATE
u_single_ss : ENTITY work.ss
GENERIC MAP (
g_dsp_data_w => g_dsp_data_w,
g_nof_ch_in => c_nof_ch_in,
g_nof_ch_sel => c_nof_ch_sel,
g_select_file_name => sel_a_b(g_select_file_prefix="UNUSED", "UNUSED", g_select_file_prefix & "_" & NATURAL'IMAGE(I) & ".hex"),
g_use_complex => g_use_complex
)
PORT MAP (
mm_rst => mm_rst,
mm_clk => mm_clk,
dp_rst => dp_rst,
dp_clk => dp_clk,
-- Memory Mapped
ram_ss_ss_mosi => ram_ss_ss_wide_mosi_arr(I),
ram_ss_ss_miso => ram_ss_ss_wide_miso_arr(I),
-- Streaming
input_sosi => input_sosi_arr(I),
input_siso => input_siso_arr(I),
output_sosi => output_sosi_arr(I),
output_siso => output_siso_arr(I)
);
END GENERATE;
END str;
-------------------------------------------------------------------------------
--
-- Copyright (C) 2011
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_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;
-- Purpose: Select a subset of the input data. Reorder the input data. Redistribute data over multiple outputs.
--
-- Description: This unit creates a parallel set of output streams where each
-- stream can contain data from any input stream.
--
-- The selection mechanism is based on three stages:
--
-- 1. Input Reorder Stage
-- 2. Selection Stage
-- 3. Output Reorder Stage
--
-- 1. The input reorder stage redirects the data (within a frame) of
-- the g_nof_inputs input streams to a set of g_nof_internals
-- streams, based on the settings of the selection buffer. The
-- selection buffer contains a selection setting for every clock
-- cycle of a frame.
--
-- 2. The selection stage creates output streams that can contain any
-- data in any order from the accordingly input streams.
--
-- 3. The output reorder stage performs another reordering stage on
-- the output of the selection stage.
--
-- Remarks:
--
ENTITY ss_parallel IS
GENERIC (
g_nof_inputs : NATURAL := 24;
g_nof_internals : NATURAL := 64;
g_nof_outputs : NATURAL := 64;
g_dsp_data_w : NATURAL := 8;
g_frame_size_in : NATURAL := 64;
g_frame_size_out : NATURAL := 128;
g_reorder_in_file_name : STRING := "UNUSED"; -- path_to_file.hex
g_ss_wide_file_prefix : STRING := "UNUSED"; -- path_to_file
g_reorder_out_file_name : STRING := "UNUSED" -- path_to_file.hex
);
PORT (
mm_rst : IN STD_LOGIC;
mm_clk : IN STD_LOGIC;
dp_rst : IN STD_LOGIC;
dp_clk : IN STD_LOGIC;
-- Memory Mapped
ram_ss_reorder_in_mosi : IN t_mem_mosi;
ram_ss_reorder_in_miso : OUT t_mem_miso;
ram_ss_reorder_out_mosi : IN t_mem_mosi;
ram_ss_reorder_out_miso : OUT t_mem_miso;
ram_ss_ss_wide_mosi : IN t_mem_mosi;
ram_ss_ss_wide_miso : OUT t_mem_miso;
-- Streaming
input_sosi_arr : IN t_dp_sosi_arr(g_nof_inputs -1 DOWNTO 0);
input_siso_arr : OUT t_dp_siso_arr(g_nof_inputs -1 DOWNTO 0);
output_sosi_arr : OUT t_dp_sosi_arr(g_nof_outputs-1 DOWNTO 0);
output_siso_arr : IN t_dp_siso_arr(g_nof_outputs-1 DOWNTO 0) := (OTHERS => c_dp_siso_rdy)
);
END ss_parallel;
ARCHITECTURE str OF ss_parallel IS
SIGNAL ss_wide_in_sosi_arr : t_dp_sosi_arr(g_nof_internals-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
SIGNAL ss_wide_out_sosi_arr : t_dp_sosi_arr(g_nof_internals-1 DOWNTO 0) := (OTHERS => c_dp_sosi_rst);
BEGIN
-----------------------------------------------------------------------------
-- Throttle the incoming streams so they provide a consistent packet flow
-- (no bursting) by enforcing a minimum period of g_frame_size_out
-----------------------------------------------------------------------------
gen_dp_throttle_sop : FOR i IN 0 TO g_nof_inputs-1 GENERATE
u_dp_throttle_sop : ENTITY dp_lib.dp_throttle_sop
GENERIC MAP (
g_period => g_frame_size_out
)
PORT MAP (
rst => dp_rst,
clk => dp_clk,
snk_out => input_siso_arr(i),
snk_in => input_sosi_arr(i)
);
END GENERATE;
-----------------------------------------------------------------------------
-- Reorder input streams
-----------------------------------------------------------------------------
u_input_reorder : ENTITY work.ss_reorder
GENERIC MAP(
g_nof_inputs => g_nof_inputs,
g_nof_outputs => g_nof_internals,
g_dsp_data_w => g_dsp_data_w,
g_frame_size => g_frame_size_in,
g_ram_init_file => g_reorder_in_file_name,
g_pipeline_in => 1,
g_pipeline_in_m => 1,
g_pipeline_out => 1
)
PORT MAP(
mm_rst => mm_rst,
mm_clk => mm_clk,
dp_rst => dp_rst,
dp_clk => dp_clk,
-- Memory Mapped
ram_ss_reorder_mosi => ram_ss_reorder_in_mosi,
ram_ss_reorder_miso => ram_ss_reorder_in_miso,
-- Streaming
input_sosi_arr => input_sosi_arr,
output_sosi_arr => ss_wide_in_sosi_arr
);
-----------------------------------------------------------------------------
-- Serial word selection per stream
-----------------------------------------------------------------------------
u_ss_wide : ENTITY work.ss_wide
GENERIC MAP (
g_wb_factor => g_nof_internals,
g_dsp_data_w => g_dsp_data_w,
g_nof_ch_in => g_frame_size_in,
g_nof_ch_sel => g_frame_size_out,
g_select_file_prefix => g_ss_wide_file_prefix
)
PORT MAP (
mm_rst => mm_rst,
mm_clk => mm_clk,
dp_rst => dp_rst,
dp_clk => dp_clk,
-- Memory Mapped
ram_ss_ss_wide_mosi => ram_ss_ss_wide_mosi,
ram_ss_ss_wide_miso => ram_ss_ss_wide_miso,
-- Streaming
input_sosi_arr => ss_wide_in_sosi_arr,
input_siso_arr => OPEN,
output_sosi_arr => ss_wide_out_sosi_arr
);
-----------------------------------------------------------------------------
-- Reorder output streams
-----------------------------------------------------------------------------
u_output_reorder : ENTITY work.ss_reorder
GENERIC MAP(
g_nof_inputs => g_nof_internals,
g_nof_outputs => g_nof_outputs,
g_dsp_data_w => g_dsp_data_w,
g_frame_size => g_frame_size_out,
g_ram_init_file => g_reorder_out_file_name,
g_pipeline_in => 1,
g_pipeline_in_m => 1,
g_pipeline_out => 1
)
PORT MAP(
mm_rst => mm_rst,
mm_clk => mm_clk,
dp_rst => dp_rst,
dp_clk => dp_clk,
-- Memory Mapped
ram_ss_reorder_mosi => ram_ss_reorder_out_mosi,
ram_ss_reorder_miso => ram_ss_reorder_out_miso,
-- Streaming
input_sosi_arr => ss_wide_out_sosi_arr,
output_sosi_arr => output_sosi_arr
);
END str;
-------------------------------------------------------------------------------
--
-- Copyright (C) 2011
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_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;
-- Purpose: Retrieve blocks of g_nof_ch_sel complex data words from a dual
-- page data buffer
-- Description:
-- The retrieve control uses a channel select buffer to know the order
-- in which the g_nof_ch_sel complex data words have to be retrieved from the
-- dual page input data buffer. The order is arbitrary and the same channel
-- may be selected multiple times.
-- Remarks:
-- . Typcially output_siso.ready='1'. When g_nof_ch_sel < g_nof_ch_in/2, then a
-- toggling output_siso.ready can be used to multiplex this SS retrieve output
-- with another SS retrieve output stream.
-- . The retrieve_done signal occurs when the last data of the block is read
-- requested, so 1 cycle before the output_sosi.eop.
-- . The timing of the ch_cnt for the retrieve_mosi.address is such that the
-- SS can store a frame and retrieve it immediately in any order, so worst
-- case the last stored data can be retrieved first.
ENTITY ss_retrieve IS
GENERIC (
g_dsp_data_w : NATURAL;
g_nof_ch_in : NATURAL;
g_nof_ch_sel : NATURAL
);
PORT (
rst : IN STD_LOGIC;
clk : IN STD_LOGIC;
-- Timing
store_done : IN STD_LOGIC;
-- Read databuf control
retrieve_mosi : OUT t_mem_mosi;
retrieve_miso : IN t_mem_miso;
retrieve_done : OUT STD_LOGIC;
-- Read selectbuf control
select_mosi : OUT t_mem_mosi;
select_miso : IN t_mem_miso;
-- Streaming
output_sosi : OUT t_dp_sosi;
output_siso : IN t_dp_siso := c_dp_siso_rdy
);
END ss_retrieve;
ARCHITECTURE rtl OF ss_retrieve IS
CONSTANT c_retrieve_lat : NATURAL := 2; -- fixed 1 for select buf read + 1 for store buf read
SIGNAL ch_cnt : INTEGER RANGE 0 TO g_nof_ch_sel-1;
SIGNAL nxt_ch_cnt : INTEGER;
SIGNAL retrieve_en : STD_LOGIC;
SIGNAL prev_retrieve_ready : STD_LOGIC;
SIGNAL retrieve_ready : STD_LOGIC;
SIGNAL nxt_retrieve_done : 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
p_reg : PROCESS (clk, rst)
BEGIN
IF rst = '1' THEN
-- Internal registers.
ch_cnt <= 0;
prev_retrieve_ready <= '0';
retrieve_sop_dly(1 TO c_retrieve_lat) <= (OTHERS=>'0');
retrieve_eop_dly(1 TO c_retrieve_lat) <= (OTHERS=>'0');
-- Output registers.
retrieve_done <= '0';
ELSIF rising_edge(clk) THEN
-- Internal registers.
ch_cnt <= nxt_ch_cnt;
prev_retrieve_ready <= retrieve_ready;
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);
-- Output registers.
retrieve_done <= nxt_retrieve_done;
END IF;
END PROCESS;
-- 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 => rst,
clk => clk,
switch_high => store_done,
switch_low => nxt_retrieve_done, -- can not use retrieve_done with g_and_low = TRUE, because if retrieve_done occurs after next store_done then that page gets missed
out_level => retrieve_en
);
retrieve_ready <= retrieve_en AND output_siso.ready;
p_ch_cnt : PROCESS (retrieve_ready, ch_cnt)
BEGIN
nxt_retrieve_done <= '0';
nxt_ch_cnt <= ch_cnt;
IF retrieve_ready='1' THEN
IF ch_cnt=g_nof_ch_sel-1 THEN
nxt_retrieve_done <= '1';
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_ready='1' AND ch_cnt=0 ELSE '0';
retrieve_eop_dly(0) <= '1' WHEN retrieve_ready='1' AND ch_cnt=g_nof_ch_sel-1 ELSE '0';
-- First read store buf address from select buf when the output is ready
select_mosi.rd <= '1'; -- no need to use retrieve_ready here, keep rd active to ease timing closure
select_mosi.address <= TO_MEM_ADDRESS(ch_cnt);
-- Then use the read select address to read the data from the store buf
retrieve_mosi.rd <= prev_retrieve_ready;
retrieve_mosi.address <= RESIZE_MEM_ADDRESS(select_miso.rddata(ceil_log2(g_nof_ch_in)-1 DOWNTO 0));
-- The output_sosi has RL=2, because of the read accesses to the select buf followed by the read access to the store buf, both with read latency is 1, so c_retrieve_lat=2
output_sosi.re <= RESIZE_DP_DSP_DATA(retrieve_miso.rddata( g_dsp_data_w-1 DOWNTO 0));
output_sosi.im <= RESIZE_DP_DSP_DATA(retrieve_miso.rddata(c_nof_complex*g_dsp_data_w-1 DOWNTO g_dsp_data_w));
output_sosi.data <= RESIZE_DP_DATA(retrieve_miso.rddata( c_nof_complex*g_dsp_data_w-1 DOWNTO 0));
output_sosi.valid <= retrieve_miso.rdval;
output_sosi.sop <= retrieve_sop_dly(c_retrieve_lat);
output_sosi.eop <= retrieve_eop_dly(c_retrieve_lat);
END rtl;
-------------------------------------------------------------------------------
--
-- Copyright (C) 2011
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
LIBRARY IEEE, common_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;
-- Purpose: Controller that store blocks of g_nof_ch_in complex input data
-- words in a dual page data buffer
-- Description:
-- Write databuf control for g_nof_ch_in complex input data words and pulse
-- store_done for each g_nof_ch_in data words that have been written.
-- Remarks:
-- . The SS stores the complex input data as concatenated data = im & re with
-- data width 2 * g_dsp_data_w.
-- . The SS does not use input sop and eop, because it uses a ch_cnt. Hence
-- the input_sosi only needs to carry im, re and valid, the sop and eop are
-- ignored. The ch_cnt is needed anyway to set the store_mosi.address. The
-- g_nof_ch_in defines the number of valid per input block, so from sop to
-- eop. The ss_store assumes that the first valid corresponds to a sop. The
-- ch_cnt restarts at the and of a block, so when ch_cnt = g_nof_ch_in-1.
-- . The store_done signal occurs when the last data of the block is being
-- written, so 1 cycle after the input_sosi.eop.
ENTITY ss_store IS
GENERIC (
g_dsp_data_w : NATURAL; -- = width of sosi.im = width of sosi.re
g_nof_ch_in : NATURAL; -- = nof valid per input block (sop to eop)
g_use_complex : BOOLEAN := TRUE -- = TRUE --> use RE and IM field. FALSE = use DATA field
);
PORT (
rst : IN STD_LOGIC;
clk : IN STD_LOGIC;
-- Streaming
input_sosi : IN t_dp_sosi;
-- Timing
store_done : OUT STD_LOGIC;
-- Write databuf control
store_mosi : OUT t_mem_mosi
);
END ss_store;
ARCHITECTURE rtl OF ss_store IS
SIGNAL ch_cnt : INTEGER RANGE 0 TO g_nof_ch_in-1;
SIGNAL nxt_ch_cnt : INTEGER;
SIGNAL i_store_mosi : t_mem_mosi;
SIGNAL nxt_store_mosi : t_mem_mosi := c_mem_mosi_rst;
SIGNAL nxt_store_done : STD_LOGIC;
BEGIN
store_mosi <= i_store_mosi;
p_reg : PROCESS (clk, rst)
BEGIN
IF rst = '1' THEN
-- Internal registers.
ch_cnt <= 0;
-- Output registers.
i_store_mosi <= c_mem_mosi_rst;
store_done <= '0';
ELSIF rising_edge(clk) THEN
-- Internal registers.
ch_cnt <= nxt_ch_cnt;
-- Output registers.
i_store_mosi <= nxt_store_mosi;
store_done <= nxt_store_done;
END IF;
END PROCESS;
p_ch_cnt : PROCESS (ch_cnt, input_sosi)
BEGIN
nxt_store_done <= '0';
nxt_ch_cnt <= ch_cnt;
IF input_sosi.valid='1' THEN
IF ch_cnt=g_nof_ch_in-1 THEN
nxt_store_done <= '1';
nxt_ch_cnt <= 0;
ELSE
nxt_ch_cnt <= ch_cnt + 1;
END IF;
END IF;
END PROCESS;
-- store
nxt_store_mosi.wr <= input_sosi.valid;
nxt_store_mosi.address <= TO_MEM_ADDRESS(ch_cnt) WHEN input_sosi.valid='1' ELSE i_store_mosi.address;
-- Use complex data fields
gen_complex : IF g_use_complex GENERATE
nxt_store_mosi.wrdata <= RESIZE_MEM_DATA(input_sosi.im(g_dsp_data_w-1 DOWNTO 0) & input_sosi.re(g_dsp_data_w-1 DOWNTO 0)) WHEN input_sosi.valid='1' ELSE i_store_mosi.wrdata;
END GENERATE;
-- Use regular data field
gen_non_complex : IF NOT(g_use_complex) GENERATE
nxt_store_mosi.wrdata <= RESIZE_MEM_DATA(input_sosi.data(c_nof_complex * g_dsp_data_w-1 DOWNTO 0)) WHEN input_sosi.valid='1' ELSE i_store_mosi.wrdata;
END GENERATE;
END rtl;
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment