OpenCores
URL https://opencores.org/ocsvn/astron_multiplexer/astron_multiplexer/trunk

Subversion Repositories astron_multiplexer

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /
    from Rev 1 to Rev 2
    Reverse comparison

Rev 1 → Rev 2

/astron_multiplexer/trunk/common_demultiplexer.vhd
0,0 → 1,95
-------------------------------------------------------------------------------
--
-- Copyright (C) 2012
-- 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_pkg_lib, common_components_lib;
USE IEEE.STD_LOGIC_1164.ALL;
USE common_pkg_lib.common_pkg.ALL;
USE common_components_lib.common_components_pkg.ALL;
 
-- Purpose: Assign input to one of g_nof_out output streams based on out_sel input
-- Description: The output streams are concatenated into one SLV.
-- Remarks:
-- . Same scheme for pipeline handling and g_nof_out=1 handling as in common_select_symbol
 
ENTITY common_demultiplexer IS
GENERIC (
g_pipeline_in : NATURAL := 0;
g_pipeline_out : NATURAL := 0;
g_nof_out : NATURAL;
g_dat_w : NATURAL
);
PORT (
rst : IN STD_LOGIC := '0';
clk : IN STD_LOGIC := '0'; -- for g_pipeline_* = 0 no rst and clk are needed, because then the demultiplexer works combinatorialy
in_dat : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0);
in_val : IN STD_LOGIC;
 
out_sel : IN STD_LOGIC_VECTOR(ceil_log2(g_nof_out)-1 DOWNTO 0);
out_dat : OUT STD_LOGIC_VECTOR(g_nof_out*g_dat_w-1 DOWNTO 0);
out_val : OUT STD_LOGIC_VECTOR(g_nof_out -1 DOWNTO 0)
);
END;
 
ARCHITECTURE rtl OF common_demultiplexer IS
CONSTANT c_sel_w : NATURAL := out_sel'LENGTH;
SIGNAL in_dat_reg : STD_LOGIC_VECTOR(in_dat'RANGE);
SIGNAL in_val_reg : STD_LOGIC;
SIGNAL out_sel_reg : STD_LOGIC_VECTOR(out_sel'RANGE);
SIGNAL sel_dat : STD_LOGIC_VECTOR(g_nof_out*g_dat_w-1 DOWNTO 0);
SIGNAL sel_val : STD_LOGIC_VECTOR(g_nof_out -1 DOWNTO 0);
BEGIN
 
-- pipeline input
u_pipe_in_dat : common_pipeline GENERIC MAP ("SIGNED", g_pipeline_in, 0, g_dat_w, g_dat_w) PORT MAP (rst, clk, '1', '0', '1', in_dat, in_dat_reg);
u_pipe_in_val : common_pipeline_sl GENERIC MAP ( g_pipeline_in, 0, FALSE) PORT MAP (rst, clk, '1', '0', '1', in_val, in_val_reg);
u_pipe_out_sel : common_pipeline GENERIC MAP ("SIGNED", g_pipeline_in, 0, c_sel_w, c_sel_w) PORT MAP (rst, clk, '1', '0', '1', out_sel, out_sel_reg);
 
-- select combinatorialy
no_sel : IF g_nof_out=1 GENERATE
sel_dat <= in_dat_reg;
sel_val(0) <= in_val_reg;
END GENERATE;
gen_sel : IF g_nof_out>1 GENERATE
p_sel : PROCESS(out_sel_reg, in_dat_reg, in_val_reg)
BEGIN
sel_val <= (OTHERS=>'0');
FOR I IN g_nof_out-1 DOWNTO 0 LOOP
sel_dat((I+1)*g_dat_w-1 DOWNTO I*g_dat_w) <= in_dat_reg; -- replicate in_dat to all outputs, this requires less logic than default forcing invalid outputs to 0
IF TO_UINT(out_sel_reg)=I THEN
sel_val(I) <= in_val_reg; -- let out_sel determine which output is valid
END IF;
END LOOP;
END PROCESS;
END GENERATE;
 
-- pipeline output
u_pipe_out_dat : common_pipeline GENERIC MAP ("SIGNED", g_pipeline_out, 0, g_nof_out*g_dat_w, g_nof_out*g_dat_w) PORT MAP (rst, clk, '1', '0', '1', sel_dat, out_dat);
u_pipe_out_val : common_pipeline GENERIC MAP ("SIGNED", g_pipeline_out, 0, g_nof_out , g_nof_out ) PORT MAP (rst, clk, '1', '0', '1', sel_val, out_val);
END rtl;
astron_multiplexer/trunk/common_demultiplexer.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/common_multiplexer.vhd =================================================================== --- astron_multiplexer/trunk/common_multiplexer.vhd (nonexistent) +++ astron_multiplexer/trunk/common_multiplexer.vhd (revision 2) @@ -0,0 +1,75 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2012 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, common_components_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; + +-- Purpose: Assign one of g_nof_in input streams to the output based on in_sel input +-- Description: The input streams are concatenated into one SLV. +-- Remarks: + +ENTITY common_multiplexer IS + GENERIC ( + g_pipeline_in : NATURAL := 0; + g_pipeline_out : NATURAL := 0; + g_nof_in : NATURAL; + g_dat_w : NATURAL + ); + PORT ( + clk : IN STD_LOGIC; + rst : IN STD_LOGIC; + + in_sel : IN STD_LOGIC_VECTOR(ceil_log2(g_nof_in)-1 DOWNTO 0); + in_dat : IN STD_LOGIC_VECTOR(g_nof_in*g_dat_w-1 DOWNTO 0); + in_val : IN STD_LOGIC; + + out_dat : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + out_val : OUT STD_LOGIC + ); +END; + +ARCHITECTURE str OF common_multiplexer IS + +BEGIN + + u_select_symbol : ENTITY common_components_lib.common_select_symbol + GENERIC MAP ( + g_pipeline_in => g_pipeline_in, + g_pipeline_out => g_pipeline_out, + g_nof_symbols => g_nof_in, + g_symbol_w => g_dat_w, + g_sel_w => ceil_log2(g_nof_in) + ) + PORT MAP ( + rst => rst, + clk => clk, + + in_data => in_dat, + in_val => in_val, + + in_sel => in_sel, + + out_symbol => out_dat, + out_val => out_val + ); + +END str;
astron_multiplexer/trunk/common_multiplexer.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/common_zip.vhd =================================================================== --- astron_multiplexer/trunk/common_zip.vhd (nonexistent) +++ astron_multiplexer/trunk/common_zip.vhd (revision 2) @@ -0,0 +1,104 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2009 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- +-- Purpose: Merges the data of multiple input streams into one output stream. +-- +-- Description: An output stream is composed out of the input streams. The duty cycle +-- of the in_val signal must be 1/g_nof_streams in order +-- to avoid the loss of data. + +library IEEE, common_pkg_lib; +use IEEE.std_logic_1164.ALL; +use common_pkg_lib.common_pkg.ALL; + +entity common_zip is + generic ( + g_nof_streams : natural := 2; -- Number of input streams to be zipped + g_dat_w : natural := 8 + ); + port ( + rst : in std_logic := '0'; + clk : in std_logic; + in_val : in std_logic := '0'; + in_dat_arr : in t_slv_64_arr(g_nof_streams-1 downto 0); + out_val : out std_logic; + out_dat : out std_logic_vector(g_dat_w-1 downto 0) + ); +end common_zip; + +architecture rtl of common_zip is + + type t_dat_arr is array (natural range <>) of std_logic_vector(out_dat'range); + + type reg_type is record + in_dat_arr : t_dat_arr(g_nof_streams-1 downto 1); -- Input register + index : integer range 1 to g_nof_streams; -- Index + out_dat : std_logic_vector(g_dat_w-1 downto 0); -- Registered output value + out_val : std_logic; -- Registered data valid signal + end record; + + signal r, rin : reg_type; + +begin + + comb : process(r, rst, in_val, in_dat_arr) + variable v : reg_type; + begin + + v := r; + v.out_val := '0'; -- Default the output valid signal is low. + + if(in_val = '1') then -- Wait for incoming data + v.index := 1; + v.out_val := '1'; + v.out_dat := in_dat_arr(0)(g_dat_w-1 downto 0); -- Output the first stream already + for I in 1 to g_nof_streams-1 loop + v.in_dat_arr(I) := in_dat_arr(I)(g_dat_w-1 downto 0); -- Store input data in register + end loop; + end if; + + if(r.index < g_nof_streams) then + v.out_val := '1'; + v.out_dat := r.in_dat_arr(r.index); -- Output the next input stream + v.index := r.index+1; + end if; + + if(rst = '1') then + v.in_dat_arr := (others => (others => '0')); + v.index := g_nof_streams; + v.out_dat := (others => '0'); + v.out_val := '0'; + end if; + + rin <= v; + + end process comb; + + regs : process(clk) + begin + if rising_edge(clk) then + r <= rin; + end if; + end process; + + out_dat <= r.out_dat; + out_val <= r.out_val; + +end rtl;
astron_multiplexer/trunk/common_zip.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/dp_frame_busy.vhd =================================================================== --- astron_multiplexer/trunk/dp_frame_busy.vhd (nonexistent) +++ astron_multiplexer/trunk/dp_frame_busy.vhd (revision 2) @@ -0,0 +1,81 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2015 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +-- Purpose: Output frame busy control signal that is active from sop to eop +-- Description: +-- The busy is active during the entire frame from sop to eop, so busy +-- remains active in case valid goes low during a frame. +-- Default use g_pipeline=0 to have snk_in_busy in phase with sop and eop. +-- Use g_pipeline > 0 to register snk_in_busy to ease timing closure. + +LIBRARY IEEE, common_pkg_lib, common_components_lib, dp_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; + +ENTITY dp_frame_busy IS + GENERIC ( + g_pipeline : NATURAL := 0 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + snk_in : IN t_dp_sosi; + snk_in_busy : OUT STD_LOGIC + ); +END dp_frame_busy; + + +ARCHITECTURE str OF dp_frame_busy IS + + SIGNAL busy : STD_LOGIC; + +BEGIN + + u_common_switch : ENTITY common_components_lib.common_switch + GENERIC MAP ( + g_rst_level => '0', -- Defines the output level at reset. + g_priority_lo => TRUE, -- When TRUE then input switch_low has priority, else switch_high. Don't care when switch_high and switch_low are pulses that do not occur simultaneously. + g_or_high => TRUE, -- When TRUE and priority hi then the registered switch_level is OR-ed with the input switch_high to get out_level, else out_level is the registered switch_level + g_and_low => FALSE -- When TRUE and priority lo then the registered switch_level is AND-ed with the input switch_low to get out_level, else out_level is the registered switch_level + ) + PORT MAP ( + rst => rst, + clk => clk, + switch_high => snk_in.sop, -- A pulse on switch_high makes the out_level go high + switch_low => snk_in.eop, -- A pulse on switch_low makes the out_level go low + out_level => busy + ); + + u_common_pipeline_sl : ENTITY common_components_lib.common_pipeline_sl + GENERIC MAP ( + g_pipeline => g_pipeline, -- 0 for wires, > 0 for registers, + g_reset_value => 0, -- 0 or 1, bit reset value, + g_out_invert => FALSE + ) + PORT MAP ( + rst => rst, + clk => clk, + in_dat => busy, + out_dat => snk_in_busy + ); + +END str;
astron_multiplexer/trunk/dp_frame_busy.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/dp_frame_busy_arr.vhd =================================================================== --- astron_multiplexer/trunk/dp_frame_busy_arr.vhd (nonexistent) +++ astron_multiplexer/trunk/dp_frame_busy_arr.vhd (revision 2) @@ -0,0 +1,60 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2015 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +-- Purpose: Output frame busy control signal for array of streams +-- Description: +-- See dp_frame_busy. + +LIBRARY IEEE, dp_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; + +ENTITY dp_frame_busy_arr IS + GENERIC ( + g_nof_inputs : NATURAL := 1; + g_pipeline : NATURAL := 0 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + snk_in_arr : IN t_dp_sosi_arr(g_nof_inputs-1 DOWNTO 0); + snk_in_busy_arr : OUT STD_LOGIC_VECTOR(g_nof_inputs-1 DOWNTO 0) + ); +END dp_frame_busy_arr; + + +ARCHITECTURE str OF dp_frame_busy_arr IS +BEGIN + + gen_nof_inputs : FOR I IN 0 TO g_nof_inputs-1 GENERATE + u_dp_frame_busy : ENTITY work.dp_frame_busy + GENERIC MAP ( + g_pipeline => g_pipeline + ) + PORT MAP ( + rst => rst, + clk => clk, + snk_in => snk_in_arr(I), + snk_in_busy => snk_in_busy_arr(I) + ); + END GENERATE; + +END str;
astron_multiplexer/trunk/dp_frame_busy_arr.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/dp_mux.vhd =================================================================== --- astron_multiplexer/trunk/dp_mux.vhd (nonexistent) +++ astron_multiplexer/trunk/dp_mux.vhd (revision 2) @@ -0,0 +1,418 @@ +-------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +-------------------------------------------------------------------------------- + +-- Purpose: +-- Multiplex frames from one or more input streams into one output stream. +-- Description: +-- The frames are marked by sop and eop. The input selection scheme depends +-- on g_mode: +-- 0: Framed round-robin with fair chance. +-- Uses eop to select next input after the frame has been passed on or +-- select the next input when there is no frame coming in on the current +-- input, so it has had its chance. +-- 1: Framed round-robin in forced order from each input. +-- Uses eop to select next output. Holds input selection until sop is +-- detected on that input. Results in ordered (low to high) but blocking +-- (on absence of sop) input selection. +-- 2: Unframed external MM control input to select the output. +-- Three options have been considered for the flow control: +-- a) Use src_in for all inputs, data from the not selected inputs +-- will get lost. In case FIFOs are used they are only useful used for +-- the selected input. +-- b) Use c_dp_siso_rdy for unused inputs, this flushes them like with +-- option a) but possibly even faster in case the src_in.ready may get +-- inactive to apply backpressure. +-- c) Use c_dp_siso_hold for unused inputs, to stop them until they get +-- selected again. +-- Support only option a) because assume that the sel_ctrl is rather +-- static and the data from the unused inputs can be ignored. +-- 3: Framed external sel_ctrl input to select the output. +-- This scheme is identical to g_mode=0, but with xon='1' only for the +-- selected input. The other not selected inputs have xon='0', so they +-- will stop getting input frames and the round-robin scheme of g_mode=0 +-- will then automatically select only remaining active input. +-- The assumption is that the upstream input sources do stop their output +-- after they finished the current frame when xon='0'. If necessary +-- dp_xonoff could be used to add such frame flow control to an input +-- stream that does not yet support xon/xoff. But better use g_mode=4 +-- instead of g_mode=3, because the implementation of g_mode=4 is more +-- simple. +-- 4) Framed external sel_ctrl input to select the output without ready. +-- This is preferred over g_mode=3 because it passes on the ready but +-- does not use it self. Not selected inputs have xon='0'. Only the +-- selected input has xon='1'. When sel_ctrl changes then briefly all +-- inputs get xon='0'. The new selected input only gets xon='1' when +-- the current selected input is idle or has become idle. +-- +-- The low part of the src_out.channel has c_sel_w = log2(g_nof_input) nof +-- bits and equals the input port number. The snk_in_arr().channel bits are +-- copied into the high part of the src_out.channel. Hence the total +-- effective output channel width becomes g_in_channel_w+c_sel_w when +-- g_use_in_channel=TRUE else c_sel_w. +-- If g_use_fifo=TRUE then the frames are buffered at the input, else the +-- connecting inputs need to take care of that. +-- Remark: +-- . Using g_nof_input=1 is transparent. +-- . Difference with dp_frame_scheduler is that dp_frame_scheduler does not +-- support back pressure via the ready signals. +-- . This dp_mux adds true_log2(nof ports) low bits to out_channel and the +-- dp_demux removes true_log2(nof ports) low bits from in_channel. +-- . For multiplexing time series frames or sample it can be applicable to +-- use g_append_channel_lo=FALSE in combination with g_mode=2. + +LIBRARY IEEE, common_pkg_lib, dp_pkg_lib, dp_components_lib, dp_fifo_lib, technology_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +ENTITY dp_mux IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + -- MUX + g_mode : NATURAL := 0; + g_nof_input : NATURAL := 2; -- >= 1 + g_append_channel_lo : BOOLEAN := TRUE; + g_sel_ctrl_invert : BOOLEAN := FALSE; -- Use default FALSE when stream array IO are indexed (0 TO g_nof_input-1), else use TRUE when indexed (g_nof_input-1 DOWNTO 0) + -- Input FIFO + g_use_fifo : BOOLEAN := FALSE; + g_bsn_w : NATURAL := 16; + g_data_w : NATURAL := 16; + g_empty_w : NATURAL := 1; + g_in_channel_w : NATURAL := 1; + g_error_w : NATURAL := 1; + g_use_bsn : BOOLEAN := FALSE; + g_use_empty : BOOLEAN := FALSE; + g_use_in_channel : BOOLEAN := FALSE; + g_use_error : BOOLEAN := FALSE; + g_use_sync : BOOLEAN := FALSE; + g_fifo_af_margin : NATURAL := 4; -- Nof words below max (full) at which fifo is considered almost full + g_fifo_size : t_natural_arr := array_init(1024, 2); -- must match g_nof_input, even when g_use_fifo=FALSE + g_fifo_fill : t_natural_arr := array_init( 0, 2) -- must match g_nof_input, even when g_use_fifo=FALSE + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + -- Control + sel_ctrl : IN NATURAL RANGE 0 TO g_nof_input-1 := 0; -- used by g_mode = 2, 3, 4 + -- ST sinks + snk_out_arr : OUT t_dp_siso_arr(0 TO g_nof_input-1); + snk_in_arr : IN t_dp_sosi_arr(0 TO g_nof_input-1); + -- ST source + src_in : IN t_dp_siso; + src_out : OUT t_dp_sosi + ); +END dp_mux; + + +ARCHITECTURE rtl OF dp_mux IS + + -- Convert unconstrained range (that starts at INTEGER'LEFT) to 0 TO g_nof_input-1 range + CONSTANT c_fifo_fill : t_natural_arr(0 TO g_nof_input-1) := g_fifo_fill; + CONSTANT c_fifo_size : t_natural_arr(0 TO g_nof_input-1) := g_fifo_size; + + -- The low part of src_out.channel is used to represent the input port and the high part of src_out.channel is copied from snk_in_arr().channel + CONSTANT c_sel_w : NATURAL := true_log2(g_nof_input); + + CONSTANT c_rl : NATURAL := 1; + SIGNAL tb_ready_reg : STD_LOGIC_VECTOR(0 TO g_nof_input*(1+c_rl)-1); + + TYPE state_type IS (s_idle, s_output); + + SIGNAL state : state_type; + SIGNAL nxt_state : state_type; + + SIGNAL i_snk_out_arr : t_dp_siso_arr(0 TO g_nof_input-1); + + SIGNAL sel_ctrl_reg : NATURAL RANGE 0 TO g_nof_input-1; + SIGNAL nxt_sel_ctrl_reg : NATURAL; + SIGNAL sel_ctrl_evt : STD_LOGIC; + SIGNAL nxt_sel_ctrl_evt : STD_LOGIC; + + SIGNAL in_sel : NATURAL RANGE 0 TO g_nof_input-1; -- input port low part of src_out.channel + SIGNAL nxt_in_sel : NATURAL; + SIGNAL next_sel : NATURAL; + + SIGNAL rd_siso_arr : t_dp_siso_arr(0 TO g_nof_input-1); + SIGNAL rd_sosi_arr : t_dp_sosi_arr(0 TO g_nof_input-1); + SIGNAL rd_sosi_busy_arr : STD_LOGIC_VECTOR(0 TO g_nof_input-1); + + SIGNAL hold_src_in_arr : t_dp_siso_arr(0 TO g_nof_input-1); + SIGNAL next_src_out_arr : t_dp_sosi_arr(0 TO g_nof_input-1); + SIGNAL pend_src_out_arr : t_dp_sosi_arr(0 TO g_nof_input-1); -- SOSI control + + SIGNAL in_xon_arr : STD_LOGIC_VECTOR(0 TO g_nof_input-1); + SIGNAL nxt_in_xon_arr : STD_LOGIC_VECTOR(0 TO g_nof_input-1); + + SIGNAL prev_src_in : t_dp_siso; + SIGNAL src_out_hi : t_dp_sosi; -- snk_in_arr().channel as high part of src_out.channel + SIGNAL nxt_src_out_hi : t_dp_sosi; + SIGNAL channel_lo : STD_LOGIC_VECTOR(c_sel_w-1 DOWNTO 0); + SIGNAL nxt_channel_lo : STD_LOGIC_VECTOR(c_sel_w-1 DOWNTO 0); + +BEGIN + + snk_out_arr <= i_snk_out_arr; + + -- Monitor sink valid input and sink ready output + proc_dp_siso_alert(clk, snk_in_arr, i_snk_out_arr, tb_ready_reg); + + p_src_out_wires : PROCESS(src_out_hi, channel_lo) + BEGIN + -- SOSI + src_out <= src_out_hi; + + IF g_append_channel_lo=TRUE THEN + -- The high part of src_out.channel copies the snk_in_arr().channel, the low part of src_out.channel is used to indicate the input port + src_out.channel <= SHIFT_UVEC(src_out_hi.channel, -c_sel_w); + src_out.channel(c_sel_w-1 DOWNTO 0) <= channel_lo; + END IF; + END PROCESS; + + p_clk: PROCESS(clk, rst) + BEGIN + IF rst='1' THEN + sel_ctrl_reg <= 0; + sel_ctrl_evt <= '0'; + in_xon_arr <= (OTHERS=>'0'); + in_sel <= 0; + prev_src_in <= c_dp_siso_rst; + state <= s_idle; + src_out_hi <= c_dp_sosi_rst; + channel_lo <= (OTHERS=>'0'); + ELSIF rising_edge(clk) THEN + sel_ctrl_reg <= nxt_sel_ctrl_reg; + sel_ctrl_evt <= nxt_sel_ctrl_evt; + in_xon_arr <= nxt_in_xon_arr; + in_sel <= nxt_in_sel; + prev_src_in <= src_in; + state <= nxt_state; + src_out_hi <= nxt_src_out_hi; + channel_lo <= nxt_channel_lo; + END IF; + END PROCESS; + + gen_input : FOR I IN 0 TO g_nof_input-1 GENERATE + gen_fifo : IF g_use_fifo=TRUE GENERATE + u_fill : ENTITY dp_fifo_lib.dp_fifo_fill + GENERIC MAP ( + g_technology => g_technology, + g_bsn_w => g_bsn_w, + g_data_w => g_data_w, + g_empty_w => g_empty_w, + g_channel_w => g_in_channel_w, + g_error_w => g_error_w, + g_use_bsn => g_use_bsn, + g_use_empty => g_use_empty, + g_use_channel => g_use_in_channel, + g_use_error => g_use_error, + g_use_sync => g_use_sync, + g_fifo_fill => c_fifo_fill(I), + g_fifo_size => c_fifo_size(I), + g_fifo_af_margin => g_fifo_af_margin, + g_fifo_rl => 1 + ) + PORT MAP ( + rst => rst, + clk => clk, + -- ST sink + snk_out => i_snk_out_arr(I), + snk_in => snk_in_arr(I), + -- ST source + src_in => rd_siso_arr(I), + src_out => rd_sosi_arr(I) + ); + END GENERATE; + no_fifo : IF g_use_fifo=FALSE GENERATE + i_snk_out_arr <= rd_siso_arr; + rd_sosi_arr <= snk_in_arr; + END GENERATE; + + -- Hold the sink input to be able to register the source output + u_hold : ENTITY dp_components_lib.dp_hold_input + PORT MAP ( + rst => rst, + clk => clk, + -- ST sink + snk_out => OPEN, -- SISO ready + snk_in => rd_sosi_arr(I), -- SOSI + -- ST source + src_in => hold_src_in_arr(I), -- SISO ready + next_src_out => next_src_out_arr(I), -- SOSI + pend_src_out => pend_src_out_arr(I), + src_out_reg => src_out_hi + ); + END GENERATE; + + -- Register and adjust external MM sel_ctrl for g_sel_ctrl_invert + nxt_sel_ctrl_reg <= sel_ctrl WHEN g_sel_ctrl_invert=FALSE ELSE g_nof_input-1-sel_ctrl; + + -- Detect change in sel_ctrl + nxt_sel_ctrl_evt <= '1' WHEN nxt_sel_ctrl_reg/=sel_ctrl_reg ELSE '0'; + + -- The output register stage matches RL = 1 for src_in.ready + nxt_src_out_hi <= next_src_out_arr(in_sel); -- default output selected next_src_out_arr + nxt_channel_lo <= TO_UVEC(in_sel, c_sel_w); -- pass on input index via channel low + + ------------------------------------------------------------------------------ + -- Unframed MM controlled input selection scheme + ------------------------------------------------------------------------------ + + gen_sel_ctrl_direct : IF g_mode=2 GENERATE + hold_src_in_arr <= (OTHERS=>src_in); -- pass src_in on to all inputs, only the selected input sosi gets used and the sosi from the other inputs will get lost + rd_siso_arr <= (OTHERS=>src_in); + + nxt_in_sel <= sel_ctrl_reg; -- external MM control selects the input + END GENERATE; + + ------------------------------------------------------------------------------ + -- Framed input selection schemes + ------------------------------------------------------------------------------ + + gen_sel_ctrl_framed : IF g_mode=4 GENERATE + u_dp_frame_busy_arr : ENTITY work.dp_frame_busy_arr + GENERIC MAP ( + g_nof_inputs => g_nof_input, + g_pipeline => 1 -- register snk_in_busy to ease timing closure + ) + PORT MAP ( + rst => rst, + clk => clk, + snk_in_arr => rd_sosi_arr, + snk_in_busy_arr => rd_sosi_busy_arr + ); + + hold_src_in_arr <= (OTHERS=>c_dp_siso_rdy); -- effectively bypass the dp_hold_input + + p_rd_siso_arr : PROCESS(src_in, in_xon_arr) + BEGIN + FOR I IN 0 TO g_nof_input-1 LOOP + rd_siso_arr(I).ready <= src_in.ready; -- default pass on src_in ready flow control to all inputs + rd_siso_arr(I).xon <= in_xon_arr(I); -- use xon to enable one input and stop all other inputs + END LOOP; + END PROCESS; + + p_state : PROCESS(state, in_sel, rd_sosi_busy_arr, sel_ctrl_reg, sel_ctrl_evt) + BEGIN + nxt_state <= state; + nxt_in_sel <= in_sel; + nxt_in_xon_arr <= (OTHERS=>'0'); -- Default stop all inputs + + CASE state IS + WHEN s_idle => + -- Wait until all inputs are inactive (due to xon='0') to ensure that the old input has finished its last frame and the new input has not started yet + IF UNSIGNED(rd_sosi_busy_arr)=0 THEN + nxt_in_sel <= sel_ctrl_reg; + nxt_state <= s_output; + END IF; + + WHEN OTHERS => -- s_output + -- Enable only the selected input via xon='1' + nxt_in_xon_arr(sel_ctrl_reg) <= '1'; + + -- Detect if the input selection changes + IF sel_ctrl_evt='1' THEN + nxt_state <= s_idle; + END IF; + END CASE; + END PROCESS; + END GENERATE; + + + gen_framed : IF g_mode=0 OR g_mode=1 OR g_mode=3 GENERATE + p_hold_src_in_arr : PROCESS(rd_siso_arr, pend_src_out_arr, in_sel, src_in) + BEGIN + hold_src_in_arr <= rd_siso_arr; -- default ready for hold input when ready for sink input + IF pend_src_out_arr(in_sel).eop='1' THEN + hold_src_in_arr(in_sel) <= src_in; -- also ready for hold input when the eop is there + END IF; + END PROCESS; + + next_sel <= in_sel+1 WHEN in_selc_dp_siso_hold); -- default not ready for input, but xon='1' + + nxt_in_sel <= in_sel; + + nxt_state <= state; + + CASE state IS + WHEN s_idle => + -- Need to check pend_src_out_arr(in_sel).sop, which can be active if prev_src_in.ready was '1', + -- because src_in.ready may be '0' and then next_src_out_arr(in_sel).sop is '0' + IF pend_src_out_arr(in_sel).sop='1' THEN + IF pend_src_out_arr(in_sel).eop='1' THEN + rd_siso_arr <= (OTHERS=>c_dp_siso_hold); -- the sop and the eop are there, it is a frame with only one data word, stop reading this input + IF src_in.ready='1' THEN + nxt_in_sel <= next_sel; -- the pend_src_out_arr(in_sel).eop will be output, so continue to next input. + rd_siso_arr(next_sel) <= src_in; + END IF; + ELSE + rd_siso_arr(in_sel) <= src_in; -- the sop is there, so start outputting the frame from this input + nxt_state <= s_output; + END IF; + ELSE + CASE g_mode IS + WHEN 0 | 3 => + -- Framed round-robin with fair chance per input + IF prev_src_in.ready='0' THEN + rd_siso_arr(in_sel) <= src_in; -- no sop, remain at current input to give it a chance + ELSE + nxt_in_sel <= next_sel; -- no sop, select next input, because the current input has had a chance + rd_siso_arr(next_sel) <= src_in; + END IF; + WHEN OTHERS => -- = 1 + -- Framed round-robin in forced order from each input + rd_siso_arr(in_sel) <= src_in; -- no sop, remain at current input to wait for a frame + END CASE; + END IF; + WHEN OTHERS => -- s_output + rd_siso_arr(in_sel) <= src_in; -- output the rest of the selected input frame + IF pend_src_out_arr(in_sel).eop='1' THEN + rd_siso_arr <= (OTHERS=>c_dp_siso_hold); -- the eop is there, stop reading this input + IF src_in.ready='1' THEN + nxt_in_sel <= next_sel; -- the pend_src_out_arr(in_sel).eop will be output, so continue to next input. + rd_siso_arr(next_sel) <= src_in; + nxt_state <= s_idle; + END IF; + END IF; + END CASE; + + -- Pass on frame level flow control + FOR I IN 0 TO g_nof_input-1 LOOP + rd_siso_arr(I).xon <= src_in.xon; + + IF g_mode=3 THEN + -- Framed MM control select input via XON + rd_siso_arr(I).xon <= '0'; -- force xon='0' for not selected inputs + IF sel_ctrl_reg=I THEN + rd_siso_arr(I).xon <= src_in.xon; -- pass on frame level flow control for selected input + END IF; + END IF; + END LOOP; + END PROCESS; + + END GENERATE; + +END rtl;
astron_multiplexer/trunk/dp_mux.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/hdllib.cfg =================================================================== --- astron_multiplexer/trunk/hdllib.cfg (nonexistent) +++ astron_multiplexer/trunk/hdllib.cfg (revision 2) @@ -0,0 +1,27 @@ +hdl_lib_name = astron_multiplexer +hdl_library_clause_name = astron_multiplexer_lib +hdl_lib_uses_synth = common_pkg common_components dp_components dp_pkg dp_fifo +hdl_lib_uses_sim = +hdl_lib_technology = + +synth_files = + common_multiplexer.vhd + common_demultiplexer.vhd + common_zip.vhd + + dp_frame_busy.vhd + dp_frame_busy_arr.vhd + dp_mux.vhd + +test_bench_files = + tb_common_multiplexer.vhd + tb_tb_common_multiplexer.vhd + tb_common_zip.vhd + +regression_test_vhdl = + +[modelsim_project_file] +modelsim_copy_files = + +[quartus_project_file] +
astron_multiplexer/trunk/hdllib.cfg Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/tb_common_multiplexer.vhd =================================================================== --- astron_multiplexer/trunk/tb_common_multiplexer.vhd (nonexistent) +++ astron_multiplexer/trunk/tb_common_multiplexer.vhd (revision 2) @@ -0,0 +1,196 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2013 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, common_components_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_pkg_lib.common_lfsr_sequences_pkg.ALL; +USE common_pkg_lib.tb_common_pkg.ALL; + +-- Purpose: Test bench for common_multiplexer.vhd and common_demultiplexer.vhd +-- Usage: +-- > as 6 +-- > run -all +-- The tb p_verify self-checks the output by using first a 1->g_nof_streams +-- demultiplexer and then a g_nof_streams->1 multiplexer. Both the use the +-- same output and input selection so that the expected output data is again +-- the same as the input stimuli data. +-- Remark: + +ENTITY tb_common_multiplexer IS + GENERIC ( + g_pipeline_demux_in : NATURAL := 1; + g_pipeline_demux_out : NATURAL := 1; + g_nof_streams : NATURAL := 3; + g_pipeline_mux_in : NATURAL := 1; + g_pipeline_mux_out : NATURAL := 1; + g_dat_w : NATURAL := 8; + g_random_in_val : BOOLEAN := FALSE; + g_test_nof_cycles : NATURAL := 500 + ); +END tb_common_multiplexer; + +ARCHITECTURE tb OF tb_common_multiplexer IS + + CONSTANT clk_period : TIME := 10 ns; + + CONSTANT c_rl : NATURAL := 1; + CONSTANT c_init : NATURAL := 0; + + -- DUT constants + CONSTANT c_pipeline_demux : NATURAL := g_pipeline_demux_in + g_pipeline_demux_out; + CONSTANT c_pipeline_mux : NATURAL := g_pipeline_mux_in + g_pipeline_mux_out; + CONSTANT c_pipeline_total : NATURAL := c_pipeline_demux + c_pipeline_mux; + + CONSTANT c_sel_w : NATURAL := ceil_log2(g_nof_streams); + + -- Stimuli + SIGNAL tb_end : STD_LOGIC := '0'; + SIGNAL rst : STD_LOGIC; + SIGNAL clk : STD_LOGIC := '1'; + SIGNAL ready : STD_LOGIC := '1'; + SIGNAL verify_en : STD_LOGIC := '0'; + SIGNAL random_0 : STD_LOGIC_VECTOR(14 DOWNTO 0) := (OTHERS=>'0'); -- use different lengths to have different random sequences + SIGNAL cnt_en : STD_LOGIC := '1'; + + -- DUT input + SIGNAL in_dat : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0) := (OTHERS => '0'); + SIGNAL in_val : STD_LOGIC; + SIGNAL in_sel : STD_LOGIC_VECTOR(c_sel_w-1 DOWNTO 0) := (OTHERS => '0'); + + -- Demux-Mux interface + SIGNAL demux_dat_vec : STD_LOGIC_VECTOR(g_nof_streams*g_dat_w-1 DOWNTO 0); + SIGNAL demux_val_vec : STD_LOGIC_VECTOR(g_nof_streams -1 DOWNTO 0); + SIGNAL demux_val : STD_LOGIC; + SIGNAL demux_sel : STD_LOGIC_VECTOR(c_sel_w-1 DOWNTO 0); + + -- DUT output + SIGNAL out_dat : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL out_val : STD_LOGIC; + + -- Verify + SIGNAL prev_out_dat : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL pipe_dat_vec : STD_LOGIC_VECTOR(0 TO (c_pipeline_total+1)*g_dat_w-1); + SIGNAL pipe_val_vec : STD_LOGIC_VECTOR(0 TO (c_pipeline_total+1)*1 -1); + +BEGIN + + ------------------------------------------------------------------------------ + -- Stimuli + ------------------------------------------------------------------------------ + + -- . tb + clk <= NOT clk OR tb_end AFTER clk_period/2; + rst <= '1', '0' AFTER 3*clk_period; + tb_end <= '0', '1' AFTER g_test_nof_cycles*clk_period; + + -- . data + random_0 <= func_common_random(random_0) WHEN rising_edge(clk); + + cnt_en <= '1' WHEN g_random_in_val=FALSE ELSE random_0(random_0'HIGH); + + proc_common_gen_data(c_rl, c_init, rst, clk, cnt_en, ready, in_dat, in_val); + + -- . selection + in_sel <= INCR_UVEC(in_sel, 1) WHEN rising_edge(clk) AND TO_UINT(in_sel) g_nof_streams --> 1 + ------------------------------------------------------------------------------ + + -- . Demultiplex single input to output[in_sel] + u_demux : ENTITY work.common_demultiplexer + GENERIC MAP ( + g_pipeline_in => g_pipeline_demux_in, + g_pipeline_out => g_pipeline_demux_out, + g_nof_out => g_nof_streams, + g_dat_w => g_dat_w + ) + PORT MAP( + rst => rst, + clk => clk, + + in_dat => in_dat, + in_val => in_val, + + out_sel => in_sel, + out_dat => demux_dat_vec, + out_val => demux_val_vec + ); + + -- . pipeline in_sel to align demux_sel to demux_*_vec + u_pipe_sel : ENTITY common_components_lib.common_pipeline + GENERIC MAP ( + g_pipeline => c_pipeline_demux, + g_in_dat_w => c_sel_w, + g_out_dat_w => c_sel_w + ) + PORT MAP ( + rst => rst, + clk => clk, + in_dat => in_sel, + out_dat => demux_sel + ); + + demux_val <= demux_val_vec(TO_UINT(demux_sel)); + + -- . Multiplex input[demux_sel] back to a single output + u_mux : ENTITY work.common_multiplexer + GENERIC MAP ( + g_pipeline_in => g_pipeline_mux_in, + g_pipeline_out => g_pipeline_mux_out, + g_nof_in => g_nof_streams, + g_dat_w => g_dat_w + ) + PORT MAP ( + rst => rst, + clk => clk, + + in_sel => demux_sel, + in_dat => demux_dat_vec, + in_val => demux_val, + + out_dat => out_dat, + out_val => out_val + ); + + + ------------------------------------------------------------------------------ + -- Verification + ------------------------------------------------------------------------------ + + proc_common_verify_data(c_rl, clk, verify_en, ready, out_val, out_dat, prev_out_dat); -- verify out_dat assuming incrementing data + proc_common_verify_latency("data", c_pipeline_total, clk, verify_en, in_dat, pipe_dat_vec, out_dat); -- verify out_dat using delayed input + proc_common_verify_latency("valid", c_pipeline_total, clk, verify_en, in_val, pipe_val_vec, out_val); -- verify out_val using delayed input + +END tb;
astron_multiplexer/trunk/tb_common_multiplexer.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/tb_common_zip.vhd =================================================================== --- astron_multiplexer/trunk/tb_common_zip.vhd (nonexistent) +++ astron_multiplexer/trunk/tb_common_zip.vhd (revision 2) @@ -0,0 +1,97 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2009 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- +-- +-- Purpose: Test bench for common_zip +-- Features: +-- +-- Usage: +-- > as 10 +-- > run -all +-- Observe manually in Wave Window that the values of the in_dat_arr are zipped +-- to the out_dat vector. + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_pkg_lib.common_lfsr_sequences_pkg.ALL; +USE common_pkg_lib.tb_common_pkg.ALL; + + +ENTITY tb_common_zip IS + GENERIC ( + g_nof_streams : natural := 3; -- Number of input streams to be zipped + g_dat_w : natural := 8 + ); +END tb_common_zip; + + +ARCHITECTURE tb OF tb_common_zip IS + + CONSTANT clk_period : TIME := 10 ns; + CONSTANT c_rl : NATURAL := 1; -- Read Latency = 1 + + SIGNAL rst : STD_LOGIC; + SIGNAL clk : STD_LOGIC := '0'; + SIGNAL tb_end : STD_LOGIC := '0'; + + SIGNAL ready : STD_LOGIC := '1'; -- Ready is always '1' + SIGNAL in_dat_arr : t_slv_64_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL in_val : STD_LOGIC := '1'; + SIGNAL out_dat : std_logic_vector(g_dat_w-1 DOWNTO 0); + SIGNAL out_val : std_logic; + SIGNAL ena : STD_LOGIC := '1'; + SIGNAL ena_mask : STD_LOGIC := '1'; + SIGNAL enable : STD_LOGIC := '1'; +BEGIN + + clk <= NOT clk OR tb_end AFTER clk_period/2; + rst <= '1', '0' AFTER 7 * clk_period; + tb_end <= '0', '1' AFTER 1 us; + + gen_data : FOR I IN 0 TO g_nof_streams-1 GENERATE + proc_common_gen_data(c_rl, I*10, rst, clk, enable, ready, in_dat_arr(I), in_val); + END GENERATE; + + -- The "ena" forms the dutu cycle for the in_val signal + proc_common_gen_pulse(1, g_nof_streams, '1', clk, ena); + + -- The "ena_mask" creates a gap between series of incoming packets in order + -- to simulate the starting and stopping of the incoming streams. + proc_common_gen_pulse(g_nof_streams*10, g_nof_streams*15, '1', clk, ena_mask); + enable <= ena and ena_mask; + + u_dut : ENTITY work.common_zip + GENERIC MAP ( + g_nof_streams => g_nof_streams, + g_dat_w => g_dat_w + ) + PORT MAP ( + rst => rst, + clk => clk, + in_val => in_val, + in_dat_arr => in_dat_arr, + out_val => out_val, + out_dat => out_dat + ); + +END tb; +
astron_multiplexer/trunk/tb_common_zip.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_multiplexer/trunk/tb_tb_common_multiplexer.vhd =================================================================== --- astron_multiplexer/trunk/tb_tb_common_multiplexer.vhd (nonexistent) +++ astron_multiplexer/trunk/tb_tb_common_multiplexer.vhd (revision 2) @@ -0,0 +1,55 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2013 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; + +ENTITY tb_tb_common_multiplexer IS +END tb_tb_common_multiplexer; + +ARCHITECTURE tb OF tb_tb_common_multiplexer IS + SIGNAL tb_end : STD_LOGIC := '0'; -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end' +BEGIN + -- Usage: + -- > as 3 + -- > run -all + + -- g_pipeline_demux_in : NATURAL := 1; + -- g_pipeline_demux_out : NATURAL := 1; + -- g_nof_streams : NATURAL := 4; + -- g_pipeline_mux_in : NATURAL := 1; + -- g_pipeline_mux_out : NATURAL := 1; + -- g_dat_w : NATURAL := 8; + -- g_random_in_val : BOOLEAN := TRUE; + -- g_test_nof_cycles : NATURAL := 500 + + u_demux_mux_p0000 : ENTITY work.tb_common_multiplexer GENERIC MAP (0, 0, 4, 0, 0, 8, TRUE, 500000); + u_demux_mux_p0000_nof_1 : ENTITY work.tb_common_multiplexer GENERIC MAP (0, 0, 1, 0, 0, 8, TRUE, 500000); + u_demux_mux_p0011 : ENTITY work.tb_common_multiplexer GENERIC MAP (0, 0, 4, 1, 1, 8, TRUE, 500000); + u_demux_mux_p1100 : ENTITY work.tb_common_multiplexer GENERIC MAP (1, 1, 4, 0, 0, 8, TRUE, 500000); + u_demux_mux_p1111 : ENTITY work.tb_common_multiplexer GENERIC MAP (1, 1, 4, 1, 1, 8, TRUE, 500000); + u_demux_mux_p1010 : ENTITY work.tb_common_multiplexer GENERIC MAP (1, 0, 4, 1, 0, 8, TRUE, 500000); + u_demux_mux_p0101 : ENTITY work.tb_common_multiplexer GENERIC MAP (0, 1, 4, 0, 1, 8, TRUE, 500000); + u_demux_mux_p1234_nof_1 : ENTITY work.tb_common_multiplexer GENERIC MAP (1, 2, 1, 3, 4, 8, TRUE, 500000); + u_demux_mux_p1234_nof_5 : ENTITY work.tb_common_multiplexer GENERIC MAP (1, 2, 5, 3, 4, 8, TRUE, 500000); + +END tb;
astron_multiplexer/trunk/tb_tb_common_multiplexer.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.