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

Subversion Repositories common_components

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /common_components/trunk
    from Rev 2 to Rev 3
    Reverse comparison

Rev 2 → Rev 3

/common_areset.vhd
0,0 → 1,70
-------------------------------------------------------------------------------
--
-- Copyright (C) 2009
-- 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/>.
--
-------------------------------------------------------------------------------
 
 
-- Purpose: Immediately apply reset and synchronously release it at rising clk
-- Description:
-- Using common_areset is equivalent to using common_async with same signal
-- applied to rst and din.
 
LIBRARY IEEE, common_pkg_lib;
USE IEEE.std_logic_1164.ALL;
USE common_pkg_lib.common_pkg.ALL;
 
ENTITY common_areset IS
GENERIC (
g_rst_level : STD_LOGIC := '1';
g_delay_len : NATURAL := c_meta_delay_len
);
PORT (
in_rst : IN STD_LOGIC;
clk : IN STD_LOGIC;
out_rst : OUT STD_LOGIC
);
END;
 
 
ARCHITECTURE str OF common_areset IS
CONSTANT c_rst_level_n : STD_LOGIC := NOT g_rst_level;
BEGIN
 
-- When in_rst becomes g_rst_level then out_rst follows immediately (asynchronous reset apply).
-- When in_rst becomes NOT g_rst_level then out_rst follows after g_delay_len cycles (synchronous reset release).
-- This block can also synchronise other signals than reset:
-- . g_rst_level = '0': output asynchronoulsy follows the falling edge input and synchronises the rising edge input.
-- . g_rst_level = '1': output asynchronoulsy follows the rising edge input and synchronises the falling edge input.
u_async : ENTITY work.common_async
GENERIC MAP (
g_rst_level => g_rst_level,
g_delay_len => g_delay_len
)
PORT MAP (
rst => in_rst,
clk => clk,
din => c_rst_level_n,
dout => out_rst
);
END str;
common_areset.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_async.vhd =================================================================== --- common_async.vhd (nonexistent) +++ common_async.vhd (revision 3) @@ -0,0 +1,76 @@ +------------------------------------------------------------------------------- +-- +-- 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: Clock an asynchronous din into the clk clock domain +-- Description: +-- The delay line combats the potential meta-stability of clocked in data. + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; + +ENTITY common_async IS + GENERIC ( + g_rising_edge : BOOLEAN := TRUE; + g_rst_level : STD_LOGIC := '0'; + g_delay_len : POSITIVE := c_meta_delay_len -- use common_pipeline if g_delay_len=0 for wires only is also needed + ); + PORT ( + rst : IN STD_LOGIC := '0'; + clk : IN STD_LOGIC; + din : IN STD_LOGIC; + dout : OUT STD_LOGIC + ); +END; + + +ARCHITECTURE rtl OF common_async IS + + SIGNAL din_meta : STD_LOGIC_VECTOR(0 TO g_delay_len-1) := (OTHERS=>g_rst_level); + + -- Synthesis constraint to ensure that register is kept in this instance region + attribute preserve : boolean; + attribute preserve of din_meta : signal is true; + +BEGIN + + p_clk : PROCESS (rst, clk) + BEGIN + IF g_rising_edge=TRUE THEN + -- Default use rising edge + IF rst='1' THEN + din_meta <= (OTHERS=>g_rst_level); + ELSIF rising_edge(clk) THEN + din_meta <= din & din_meta(0 TO din_meta'HIGH-1); + END IF; + ELSE + -- also support using falling edge + IF rst='1' THEN + din_meta <= (OTHERS=>g_rst_level); + ELSIF falling_edge(clk) THEN + din_meta <= din & din_meta(0 TO din_meta'HIGH-1); + END IF; + END IF; + END PROCESS; + + dout <= din_meta(din_meta'HIGH); + +END rtl;
common_async.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_bit_delay.vhd =================================================================== --- common_bit_delay.vhd (nonexistent) +++ common_bit_delay.vhd (revision 3) @@ -0,0 +1,80 @@ +-------------------------------------------------------------------------------- +-- Author: Raj Thilak Rajan : rajan at astron.nl: Nov 2009 +-- Copyright (C) 2009-2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This file is part of the UniBoard software suite. +-- The file 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: Shift register for control data bit +-- Description: +-- Delays input data by g_depth. The delay line shifts when in_val is +-- indicates an active clock cycle. +-- Remark: +-- . This common_bit_delay can not use common_delay.vhd because it needs a reset. +-- . Typically rst may be left not connected, because the internal power up +-- state of the shift_reg is 0. +-- . If dynamic restart control is needed then use in_clr for that. Otherwise +-- leave in_clr also not connected. +-- . For large g_depth Quartus infers a RAM block for this bitDelay even if +-- the same signal is applied to both in_bit and in_val. It does not help +-- to remove in_clr or to not use shift_reg(0) combinatorially. + +library IEEE; +use IEEE.std_logic_1164.all; + +entity common_bit_delay is + generic ( + g_depth : NATURAL := 16 --Quartus infers fifo for 4 to 4096 g_depth, 8 Bits. + ); + port ( + clk : in std_logic; + rst : in std_logic := '0'; -- asynchronous reset for initial start + in_clr : in std_logic := '0'; -- synchronous reset for control of dynamic restart(s) + in_bit : in std_logic; + in_val : in std_logic := '1'; + out_bit : out std_logic + ); +end entity common_bit_delay; + +architecture rtl of common_bit_delay is + + -- Use index (0) as combinatorial input and index(1:g_depth) for the shift + -- delay, in this way the shift_reg type can support all g_depth >= 0 + signal shift_reg : std_logic_vector(0 to g_depth) := (others=>'0'); + +begin + + shift_reg(0) <= in_bit; + + out_bit <= shift_reg(g_depth); + + gen_reg : if g_depth>0 generate + p_clk : process(clk, rst) + begin + if rst='1' then + shift_reg(1 to g_depth) <= (others=>'0'); + elsif rising_edge(clk) then + if in_clr='1' then + shift_reg(1 to g_depth) <= (others=>'0'); + elsif in_val='1' then + shift_reg(1 to g_depth) <= shift_reg(0 to g_depth-1); + end if; + end if; + end process; + end generate; + +end rtl;
common_bit_delay.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_components_pkg.vhd =================================================================== --- common_components_pkg.vhd (nonexistent) +++ common_components_pkg.vhd (revision 3) @@ -0,0 +1,73 @@ +------------------------------------------------------------------------------- +-- +-- 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; +--USE work.common_mem_pkg.ALL; + +-- Purpose: Component declarations to check positional mapping +-- Description: +-- Remarks: + +PACKAGE common_components_pkg IS + + COMPONENT common_pipeline IS + GENERIC ( + g_representation : STRING := "SIGNED"; -- or "UNSIGNED" + g_pipeline : NATURAL := 1; -- 0 for wires, > 0 for registers, + g_reset_value : INTEGER := 0; + g_in_dat_w : NATURAL := 8; + g_out_dat_w : NATURAL := 9 + ); + PORT ( + rst : IN STD_LOGIC := '0'; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_clr : IN STD_LOGIC := '0'; + in_en : IN STD_LOGIC := '1'; + in_dat : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + out_dat : OUT STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0) + ); + END COMPONENT; + + COMPONENT common_pipeline_sl IS + GENERIC ( + g_pipeline : NATURAL := 1; -- 0 for wires, > 0 for registers, + g_reset_value : NATURAL := 0; -- 0 or 1, bit reset value, + g_out_invert : BOOLEAN := FALSE + ); + PORT ( + rst : IN STD_LOGIC := '0'; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_clr : IN STD_LOGIC := '0'; + in_en : IN STD_LOGIC := '1'; + in_dat : IN STD_LOGIC; + out_dat : OUT STD_LOGIC + ); + END COMPONENT; + +END common_components_pkg; + + +PACKAGE BODY common_components_pkg IS +END common_components_pkg;
common_components_pkg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_delay.vhd =================================================================== --- common_delay.vhd (nonexistent) +++ common_delay.vhd (revision 3) @@ -0,0 +1,68 @@ +-------------------------------------------------------------------------------- +-- Author: Raj Thilak Rajan : rajan at astron.nl: Nov 2009 +-- Copyright (C) 2009-2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This file is part of the UniBoard software suite. +-- The file 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: Shift register for data +-- Description: +-- Delays input data by g_depth. The delay line shifts when in_val is +-- indicates an active clock cycle. + +library ieee; +use IEEE.STD_LOGIC_1164.all; + +entity common_delay is + generic ( + g_dat_w : NATURAL := 8; -- need g_dat_w to be able to use (others=>'') assignments for two dimensional unconstraint vector arrays + g_depth : NATURAL := 16 + ); + port ( + clk : in STD_LOGIC; + in_val : in STD_LOGIC := '1'; + in_dat : in STD_LOGIC_VECTOR(g_dat_w-1 downto 0); + out_dat : out STD_LOGIC_VECTOR(g_dat_w-1 downto 0) + ); +end entity common_delay; + +architecture rtl of common_delay is + + -- Use index (0) as combinatorial input and index(1:g_depth) for the shift + -- delay, in this way the t_dly_arr type can support all g_depth >= 0 + type t_dly_arr is array (0 to g_depth) of STD_LOGIC_VECTOR(g_dat_w-1 downto 0); + + signal shift_reg : t_dly_arr := (others=>(others=>'0')); + +begin + + shift_reg(0) <= in_dat; + + out_dat <= shift_reg(g_depth); + + gen_reg : if g_depth>0 generate + p_clk : process(clk) + begin + if rising_edge(clk) then + if in_val='1' then + shift_reg(1 to g_depth) <= shift_reg(0 to g_depth-1); + end if; + end if; + end process; + end generate; + +end rtl;
common_delay.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_pipeline.vhd =================================================================== --- common_pipeline.vhd (nonexistent) +++ common_pipeline.vhd (revision 3) @@ -0,0 +1,78 @@ +------------------------------------------------------------------------------- +-- +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; + +ENTITY common_pipeline IS + GENERIC ( + g_representation : STRING := "SIGNED"; -- or "UNSIGNED" + g_pipeline : NATURAL := 1; -- 0 for wires, > 0 for registers, + g_reset_value : INTEGER := 0; + g_in_dat_w : NATURAL := 8; + g_out_dat_w : NATURAL := 9 + ); + PORT ( + rst : IN STD_LOGIC := '0'; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_clr : IN STD_LOGIC := '0'; + in_en : IN STD_LOGIC := '1'; + in_dat : IN STD_LOGIC_VECTOR(g_in_dat_w-1 DOWNTO 0); + out_dat : OUT STD_LOGIC_VECTOR(g_out_dat_w-1 DOWNTO 0) + ); +END common_pipeline; + + +ARCHITECTURE rtl OF common_pipeline IS + + CONSTANT c_reset_value : STD_LOGIC_VECTOR(out_dat'RANGE) := TO_SVEC(g_reset_value, out_dat'LENGTH); + + TYPE t_out_dat IS ARRAY (NATURAL RANGE <>) OF STD_LOGIC_VECTOR(out_dat'RANGE); + + SIGNAL out_dat_p : t_out_dat(0 TO g_pipeline) := (OTHERS=>c_reset_value); + +BEGIN + + gen_pipe_n : IF g_pipeline>0 GENERATE + p_clk : PROCESS(clk, rst) + BEGIN + IF rst='1' THEN + out_dat_p(1 TO g_pipeline) <= (OTHERS=>c_reset_value); + ELSIF rising_edge(clk) THEN + IF clken='1' THEN + IF in_clr = '1' THEN + out_dat_p(1 TO g_pipeline) <= (OTHERS=>c_reset_value); + ELSIF in_en = '1' THEN + out_dat_p(1 TO g_pipeline) <= out_dat_p(0 TO g_pipeline-1); + END IF; + END IF; + END IF; + END PROCESS; + END GENERATE; + + out_dat_p(0) <= RESIZE_SVEC(in_dat, out_dat'LENGTH) WHEN g_representation= "SIGNED" ELSE + RESIZE_UVEC(in_dat, out_dat'LENGTH) WHEN g_representation="UNSIGNED"; + + out_dat <= out_dat_p(g_pipeline); + +END rtl;
common_pipeline.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_pipeline_sl.vhd =================================================================== --- common_pipeline_sl.vhd (nonexistent) +++ common_pipeline_sl.vhd (revision 3) @@ -0,0 +1,73 @@ +------------------------------------------------------------------------------- +-- +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; + +ENTITY common_pipeline_sl IS + GENERIC ( + g_pipeline : NATURAL := 1; -- 0 for wires, > 0 for registers, + g_reset_value : NATURAL := 0; -- 0 or 1, bit reset value, + g_out_invert : BOOLEAN := FALSE + ); + PORT ( + rst : IN STD_LOGIC := '0'; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + in_clr : IN STD_LOGIC := '0'; + in_en : IN STD_LOGIC := '1'; + in_dat : IN STD_LOGIC; + out_dat : OUT STD_LOGIC + ); +END common_pipeline_sl; + + +ARCHITECTURE str OF common_pipeline_sl IS + + SIGNAL in_dat_slv : STD_LOGIC_VECTOR(0 DOWNTO 0); + SIGNAL out_dat_slv : STD_LOGIC_VECTOR(0 DOWNTO 0); + +BEGIN + + in_dat_slv(0) <= in_dat WHEN g_out_invert=FALSE ELSE NOT in_dat; + out_dat <= out_dat_slv(0); + + u_sl : ENTITY work.common_pipeline + GENERIC MAP ( + g_representation => "UNSIGNED", + g_pipeline => g_pipeline, + g_reset_value => sel_a_b(g_out_invert, 1-g_reset_value, g_reset_value), + g_in_dat_w => 1, + g_out_dat_w => 1 + ) + PORT MAP ( + rst => rst, + clk => clk, + clken => clken, + in_clr => in_clr, + in_en => in_en, + in_dat => in_dat_slv, + out_dat => out_dat_slv + ); + +END str;
common_pipeline_sl.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_select_symbol.vhd =================================================================== --- common_select_symbol.vhd (nonexistent) +++ common_select_symbol.vhd (revision 3) @@ -0,0 +1,108 @@ +------------------------------------------------------------------------------- +-- +-- 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; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE work.common_components_pkg.ALL; + +-- Purpose: Select symbol from input data stream +-- Description: +-- The in_data is a concatenation of g_nof_symbols, that are each g_symbol_w +-- bits wide. The symbol with index set by in_sel is passed on to the output +-- out_dat. +-- Remarks: +-- . If the in_select index is too large for g_nof_input range then the output +-- passes on symbol 0. + +ENTITY common_select_symbol IS + GENERIC ( + g_pipeline_in : NATURAL := 0; + g_pipeline_out : NATURAL := 1; + g_nof_symbols : NATURAL := 4; + g_symbol_w : NATURAL := 16; + g_sel_w : NATURAL := 2 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + + in_data : IN STD_LOGIC_VECTOR(g_nof_symbols*g_symbol_w-1 DOWNTO 0); + in_val : IN STD_LOGIC := '0'; + in_sop : IN STD_LOGIC := '0'; + in_eop : IN STD_LOGIC := '0'; + in_sync : IN STD_LOGIC := '0'; + + in_sel : IN STD_LOGIC_VECTOR(g_sel_w-1 DOWNTO 0); + out_sel : OUT STD_LOGIC_VECTOR(g_sel_w-1 DOWNTO 0); -- pipelined in_sel, use range to allow leaving it OPEN + + out_symbol : OUT STD_LOGIC_VECTOR(g_symbol_w-1 DOWNTO 0); + out_val : OUT STD_LOGIC; -- pipelined in_val + out_sop : OUT STD_LOGIC; -- pipelined in_sop + out_eop : OUT STD_LOGIC; -- pipelined in_eop + out_sync : OUT STD_LOGIC -- pipelined in_sync + ); +END common_select_symbol; + + +ARCHITECTURE rtl OF common_select_symbol IS + + CONSTANT c_pipeline : NATURAL := g_pipeline_in + g_pipeline_out; + + SIGNAL in_data_reg : STD_LOGIC_VECTOR(in_data'RANGE); + SIGNAL in_sel_reg : STD_LOGIC_VECTOR(in_sel'RANGE); + + SIGNAL sel_symbol : STD_LOGIC_VECTOR(g_symbol_w-1 DOWNTO 0); + +BEGIN + + -- pipeline input + u_pipe_in_data : common_pipeline GENERIC MAP ("SIGNED", g_pipeline_in, 0, in_data'LENGTH, in_data'LENGTH) PORT MAP (rst, clk, '1', '0', '1', in_data, in_data_reg); + u_pipe_in_sel : common_pipeline GENERIC MAP ("SIGNED", g_pipeline_in, 0, g_sel_w, g_sel_w) PORT MAP (rst, clk, '1', '0', '1', in_sel, in_sel_reg); + + no_sel : IF g_nof_symbols=1 GENERATE + sel_symbol <= in_data_reg; + END GENERATE; + + gen_sel : IF g_nof_symbols>1 GENERATE + -- Default pass on symbol 0 else if supported pass on the selected symbol + p_sel : PROCESS(in_sel_reg, in_data_reg) + BEGIN + sel_symbol <= in_data_reg(g_symbol_w-1 DOWNTO 0); + + FOR I IN g_nof_symbols-1 DOWNTO 0 LOOP + IF TO_UINT(in_sel_reg)=I THEN + sel_symbol <= in_data_reg((I+1)*g_symbol_w-1 DOWNTO I*g_symbol_w); + END IF; + END LOOP; + END PROCESS; + END GENERATE; + + -- pipeline selected symbol output and control outputs + u_pipe_out_symbol : common_pipeline GENERIC MAP ("SIGNED", g_pipeline_out, 0, g_symbol_w, g_symbol_w) PORT MAP (rst, clk, '1', '0', '1', sel_symbol, out_symbol); + u_pipe_out_sel : common_pipeline GENERIC MAP ("SIGNED", c_pipeline, 0, in_sel'LENGTH, in_sel'LENGTH) PORT MAP (rst, clk, '1', '0', '1', in_sel, out_sel); + + u_pipe_out_val : common_pipeline_sl GENERIC MAP (c_pipeline, 0, FALSE) PORT MAP (rst, clk, '1', '0', '1', in_val, out_val); + u_pipe_out_sop : common_pipeline_sl GENERIC MAP (c_pipeline, 0, FALSE) PORT MAP (rst, clk, '1', '0', '1', in_sop, out_sop); + u_pipe_out_eop : common_pipeline_sl GENERIC MAP (c_pipeline, 0, FALSE) PORT MAP (rst, clk, '1', '0', '1', in_eop, out_eop); + u_pipe_out_sync : common_pipeline_sl GENERIC MAP (c_pipeline, 0, FALSE) PORT MAP (rst, clk, '1', '0', '1', in_sync, out_sync); + +END rtl;
common_select_symbol.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: common_spulse.vhd =================================================================== --- common_spulse.vhd (nonexistent) +++ common_spulse.vhd (revision 3) @@ -0,0 +1,110 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2010 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- JIVE (Joint Institute for VLBI in Europe) +-- 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: Get in_pulse from in_clk to out_pulse in the out_clk domain. +-- Description: +-- The in_pulse is captured in the in_clk domain and then transfered to the +-- out_clk domain. The out_pulse is also only one cycle wide and transfered +-- back to the in_clk domain to serve as an acknowledge signal to ensure +-- that the in_pulse was recognized also in case the in_clk is faster than +-- the out_clk. The in_busy is active during the entire transfer. Hence the +-- rate of pulses that can be transfered is limited by g_delay_len and by +-- the out_clk rate. + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; + +ENTITY common_spulse IS + GENERIC ( + g_delay_len : NATURAL := c_meta_delay_len + ); + PORT ( + in_rst : IN STD_LOGIC := '0'; + in_clk : IN STD_LOGIC; + in_clken : IN STD_LOGIC := '1'; + in_pulse : IN STD_LOGIC; + in_busy : OUT STD_LOGIC; + out_rst : IN STD_LOGIC := '0'; + out_clk : IN STD_LOGIC; + out_clken : IN STD_LOGIC := '1'; + out_pulse : OUT STD_LOGIC + ); +END; + +ARCHITECTURE rtl OF common_spulse IS + + SIGNAL in_level : STD_LOGIC; + SIGNAL meta_level : STD_LOGIC_VECTOR(0 TO g_delay_len-1); + SIGNAL out_level : STD_LOGIC; + SIGNAL prev_out_level : STD_LOGIC; + SIGNAL meta_ack : STD_LOGIC_VECTOR(0 TO g_delay_len-1); + SIGNAL pulse_ack : STD_LOGIC; + SIGNAL nxt_out_pulse : STD_LOGIC; + +BEGIN + + capture_in_pulse : ENTITY work.common_switch + PORT MAP ( + clk => in_clk, + clken => in_clken, + rst => in_rst, + switch_high => in_pulse, + switch_low => pulse_ack, + out_level => in_level + ); + + in_busy <= in_level OR pulse_ack; + + p_out_clk : PROCESS(out_rst, out_clk) + BEGIN + IF out_rst='1' THEN + meta_level <= (OTHERS=>'0'); + out_level <= '0'; + prev_out_level <= '0'; + out_pulse <= '0'; + ELSIF RISING_EDGE(out_clk) THEN + IF out_clken='1' THEN + meta_level <= in_level & meta_level(0 TO meta_level'HIGH-1); + out_level <= meta_level(meta_level'HIGH); + prev_out_level <= out_level; + out_pulse <= nxt_out_pulse; + END IF; + END IF; + END PROCESS; + + p_in_clk : PROCESS(in_rst, in_clk) + BEGIN + IF in_rst='1' THEN + meta_ack <= (OTHERS=>'0'); + pulse_ack <= '0'; + ELSIF RISING_EDGE(in_clk) THEN + IF in_clken='1' THEN + meta_ack <= out_level & meta_ack(0 TO meta_ack'HIGH-1); + pulse_ack <= meta_ack(meta_ack'HIGH); + END IF; + END IF; + END PROCESS; + + nxt_out_pulse <= out_level AND NOT prev_out_level; + +END rtl;
common_spulse.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: hdllib.cfg =================================================================== --- hdllib.cfg (revision 2) +++ hdllib.cfg (revision 3) @@ -1,13 +1,24 @@ hdl_lib_name = common_components hdl_library_clause_name = common_components_lib -hdl_lib_uses_synth = +hdl_lib_uses_synth = common_pkg hdl_lib_uses_sim = hdl_lib_technology = synth_files = + common_components_pkg.vhd common_switch.vhd - + common_pipeline.vhd + common_pipeline_sl.vhd + common_select_symbol.vhd + common_delay.vhd + common_bit_delay.vhd + common_async.vhd + common_areset.vhd + common_spulse.vhd + test_bench_files = + tb_common_switch.vhd + tb_common_spulse.vhd regression_test_vhdl =
/tb_common_spulse.vhd
0,0 → 1,92
-------------------------------------------------------------------------------
--
-- Copyright (C) 2009
-- 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/>.
--
-------------------------------------------------------------------------------
 
-- Purpose: Testbench for common_spulse.
-- Description:
-- The tb is not self checking, so manually observe working in Wave window.
-- Usage:
-- > as 10
-- > run 1 us
 
LIBRARY IEEE, common_pkg_lib;
USE IEEE.std_logic_1164.ALL;
USE IEEE.numeric_std.ALL;
USE common_pkg_lib.common_pkg.ALL;
 
ENTITY tb_common_spulse IS
END tb_common_spulse;
 
ARCHITECTURE tb OF tb_common_spulse IS
 
CONSTANT c_meta_delay : NATURAL := 2;
--CONSTANT in_clk_period : TIME := 10 ns;
CONSTANT in_clk_period : TIME := 27 ns;
CONSTANT out_clk_period : TIME := 17 ns;
 
SIGNAL in_rst : STD_LOGIC;
SIGNAL out_rst : STD_LOGIC;
SIGNAL in_clk : STD_LOGIC := '0';
SIGNAL out_clk : STD_LOGIC := '0';
SIGNAL in_pulse : STD_LOGIC;
SIGNAL out_pulse : STD_LOGIC;
 
BEGIN
 
in_clk <= NOT in_clk AFTER in_clk_period/2;
out_clk <= NOT out_clk AFTER out_clk_period/2;
p_in_stimuli : PROCESS
BEGIN
in_rst <= '1';
in_pulse <= '0';
WAIT UNTIL rising_edge(in_clk);
in_rst <= '0';
FOR I IN 0 TO 9 LOOP
WAIT UNTIL rising_edge(in_clk);
END LOOP;
in_pulse <= '1';
WAIT UNTIL rising_edge(in_clk);
in_pulse <= '0';
WAIT;
END PROCESS;
 
u_out_rst : ENTITY work.common_areset
PORT MAP (
in_rst => in_rst,
clk => out_clk,
out_rst => out_rst
);
u_spulse : ENTITY work.common_spulse
GENERIC MAP (
g_delay_len => c_meta_delay
)
PORT MAP (
in_clk => in_clk,
in_rst => in_rst,
in_pulse => in_pulse,
out_clk => out_clk,
out_rst => out_rst,
out_pulse => out_pulse
);
END tb;
tb_common_spulse.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: tb_common_switch.vhd =================================================================== --- tb_common_switch.vhd (nonexistent) +++ tb_common_switch.vhd (revision 3) @@ -0,0 +1,245 @@ +------------------------------------------------------------------------------- +-- +-- 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 . +-- +------------------------------------------------------------------------------- + +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.tb_common_pkg.ALL; + +ENTITY tb_common_switch IS +END tb_common_switch; + +-- Usage: +-- > as 10 +-- > run -all +-- . expand out_level in the Wave window to check the behaviour of the 16 possible BOOLEAN generic setttings +-- . for expected Wave window see tb_common_switch.jpg +-- +-- Description: +-- Runs 8 instances in parallel to try all combinations of: +-- . g_priority_lo +-- . g_or_high +-- . g_and_low + + +ARCHITECTURE tb OF tb_common_switch IS + + CONSTANT clk_period : TIME := 10 ns; + + CONSTANT c_nof_generics : NATURAL := 3; + + CONSTANT c_nof_dut : NATURAL := 2**c_nof_generics; + CONSTANT c_generics_matrix : t_boolean_matrix(0 TO c_nof_dut-1, 0 TO c_nof_generics-1) := ((FALSE, FALSE, FALSE), + (FALSE, FALSE, TRUE), + (FALSE, TRUE, FALSE), + (FALSE, TRUE, TRUE), + ( TRUE, FALSE, FALSE), + ( TRUE, FALSE, TRUE), + ( TRUE, TRUE, FALSE), + ( TRUE, TRUE, TRUE)); + -- View constants in Wave window + SIGNAL dbg_c_generics_matrix : t_boolean_matrix(0 TO c_nof_dut-1, 0 TO c_nof_generics-1) := c_generics_matrix; + SIGNAL dbg_state : NATURAL; + + SIGNAL rst : STD_LOGIC; + SIGNAL clk : STD_LOGIC := '0'; + SIGNAL tb_end : STD_LOGIC := '0'; + SIGNAL in_hi : STD_LOGIC; + SIGNAL in_lo : STD_LOGIC; + + SIGNAL dbg_prio_lo : STD_LOGIC; + SIGNAL dbg_prio_lo_and : STD_LOGIC; + SIGNAL dbg_prio_lo_or : STD_LOGIC; + SIGNAL dbg_prio_lo_or_and : STD_LOGIC; + + SIGNAL dbg_prio_hi : STD_LOGIC; + SIGNAL dbg_prio_hi_and : STD_LOGIC; + SIGNAL dbg_prio_hi_or : STD_LOGIC; + SIGNAL dbg_prio_hi_or_and : STD_LOGIC; + + SIGNAL out_level : STD_LOGIC_VECTOR(0 TO c_nof_dut-1); + +BEGIN + + clk <= NOT clk OR tb_end AFTER clk_period/2; + + p_in_stimuli : PROCESS + BEGIN + dbg_state <= 0; + rst <= '1'; + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 1); + rst <= '0'; + proc_common_wait_some_cycles(clk, 10); + -- 1) Single hi pulse + dbg_state <= 1; + in_hi <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + -- 2) Second hi pulse during active lo gets ignored + dbg_state <= 2; + in_hi <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_hi <= '1'; + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + -- 3) Second hi pulse while lo is just active, should be recognized as second out pulse + dbg_state <= 3; + in_hi <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_hi <= '1'; + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 5); + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + -- 4) Continue active hi with single lo pulse + dbg_state <= 4; + in_hi <= '1'; + proc_common_wait_some_cycles(clk, 5); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 3); + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + in_hi <= '0'; + proc_common_wait_some_cycles(clk, 3); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + -- 5) Active hi immediately after active lo + dbg_state <= 5; + in_hi <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_lo <= '0'; + in_hi <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + -- 6) Simultaneous hi pulse and lo pulse + dbg_state <= 6; + in_hi <= '1'; + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + -- 7) Multiple simultaneous hi pulse and lo pulse + dbg_state <= 7; + in_hi <= '1'; + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_hi <= '1'; + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_hi <= '1'; + in_lo <= '1'; + proc_common_wait_some_cycles(clk, 1); + in_hi <= '0'; + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 5); + in_lo <= '1'; -- ensure low output if it was still high + proc_common_wait_some_cycles(clk, 1); + in_lo <= '0'; + proc_common_wait_some_cycles(clk, 10); + + dbg_state <= 255; + proc_common_wait_some_cycles(clk, 10); + tb_end <= '1'; + WAIT; + END PROCESS; + + dbg_prio_lo <= out_level(4); + dbg_prio_lo_and <= out_level(5); + dbg_prio_lo_or <= out_level(6); + dbg_prio_lo_or_and <= out_level(7); + + dbg_prio_hi <= out_level(0); + dbg_prio_hi_and <= out_level(1); + dbg_prio_hi_or <= out_level(2); + dbg_prio_hi_or_and <= out_level(3); + + gen_dut : FOR I IN 0 TO c_nof_dut-1 GENERATE + u_switch : ENTITY work.common_switch + GENERIC MAP ( + g_rst_level => '0', -- output level at reset. + --g_rst_level => '1', + g_priority_lo => c_generics_matrix(I,0), + g_or_high => c_generics_matrix(I,1), + g_and_low => c_generics_matrix(I,2) + ) + PORT MAP ( + clk => clk, + rst => rst, + switch_high => in_hi, + switch_low => in_lo, + out_level => out_level(I) + ); + END GENERATE; + +END tb;
tb_common_switch.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.