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

Subversion Repositories astron_fifo

Compare Revisions

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

Rev 1 → Rev 2

/astron_fifo/trunk/common_fifo_dc.vhd
0,0 → 1,140
-------------------------------------------------------------------------------
--
-- 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: Dual clock FIFO
 
LIBRARY IEEE, common_pkg_lib, common_components_lib, technology_lib, tech_fifo_lib;
USE IEEE.STD_LOGIC_1164.ALL;
USE common_pkg_lib.common_pkg.ALL;
USE technology_lib.technology_select_pkg.ALL;
 
ENTITY common_fifo_dc IS
GENERIC (
g_technology : NATURAL := c_tech_select_default;
g_note_is_ful : BOOLEAN := TRUE; -- when TRUE report NOTE when FIFO goes full, fifo overflow is always reported as FAILURE
g_fail_rd_emp : BOOLEAN := FALSE; -- when TRUE report FAILURE when read from an empty FIFO
g_dat_w : NATURAL := 36;
g_nof_words : NATURAL := 256 -- 36 * 256 = 1 M9K
);
PORT (
rst : IN STD_LOGIC;
wr_clk : IN STD_LOGIC;
wr_dat : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0);
wr_req : IN STD_LOGIC;
wr_ful : OUT STD_LOGIC;
wrusedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_nof_words)-1 DOWNTO 0);
rd_clk : IN STD_LOGIC;
rd_dat : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0);
rd_req : IN STD_LOGIC;
rd_emp : OUT STD_LOGIC;
rdusedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_nof_words)-1 DOWNTO 0);
rd_val : OUT STD_LOGIC := '0'
);
END common_fifo_dc;
 
 
ARCHITECTURE str of common_fifo_dc IS
 
CONSTANT c_nof_words : NATURAL := 2**ceil_log2(g_nof_words); -- ensure size is power of 2 for dual clock FIFO
 
SIGNAL wr_rst : STD_LOGIC;
SIGNAL wr_init : STD_LOGIC;
SIGNAL wr_en : STD_LOGIC;
SIGNAL rd_en : STD_LOGIC;
SIGNAL ful : STD_LOGIC;
SIGNAL emp : STD_LOGIC;
SIGNAL nxt_rd_val : STD_LOGIC;
 
BEGIN
 
-- Control logic copied from LOFAR common_fifo_dc(virtex4).vhd
-- Need to make sure the reset lasts at least 3 cycles (see fifo_generator_ug175.pdf)
-- Wait at least 4 cycles after reset release before allowing FIFO wr_en (see fifo_generator_ug175.pdf)
-- Use common_areset to:
-- . asynchronously detect rst even when the wr_clk is stopped
-- . synchronize release of rst to wr_clk domain
-- Using common_areset is equivalent to using common_async with same signal applied to rst and din.
u_wr_rst : ENTITY common_components_lib.common_areset
GENERIC MAP (
g_rst_level => '1',
g_delay_len => 3
)
PORT MAP (
in_rst => rst,
clk => wr_clk,
out_rst => wr_rst
);
 
-- Delay wr_init to ensure that FIFO ful has gone low after reset release
u_wr_init : ENTITY common_components_lib.common_areset
GENERIC MAP (
g_rst_level => '1',
g_delay_len => 4
)
PORT MAP (
in_rst => wr_rst,
clk => wr_clk,
out_rst => wr_init -- assume init has finished g_delay_len cycles after release of wr_rst
);
-- The FIFO under read and over write protection are kept enabled in the MegaWizard
wr_en <= wr_req AND NOT wr_init; -- check on NOT ful is not necessary when overflow_checking="ON" (Altera) or according to fifo_generator_ug175.pdf (Xilinx)
rd_en <= rd_req; -- check on NOT emp is not necessary when underflow_checking="ON" (Altera)
 
nxt_rd_val <= rd_req AND NOT emp; -- check on NOT emp is necessary for rd_val
 
wr_ful <= ful WHEN wr_init='0' ELSE '0';
 
rd_emp <= emp;
p_rd_clk : PROCESS(rd_clk)
BEGIN
IF rising_edge(rd_clk) THEN
rd_val <= nxt_rd_val;
END IF;
END PROCESS;
u_fifo : ENTITY tech_fifo_lib.tech_fifo_dc
GENERIC MAP (
g_technology => g_technology,
g_dat_w => g_dat_w,
g_nof_words => c_nof_words
)
PORT MAP (
aclr => wr_rst, -- MegaWizard fifo_dc seems to use aclr synchronous with wr_clk
data => wr_dat,
rdclk => rd_clk,
rdreq => rd_en,
wrclk => wr_clk,
wrreq => wr_en,
q => rd_dat,
rdempty => emp,
rdusedw => rdusedw,
wrfull => ful,
wrusedw => wrusedw
);
proc_common_fifo_asserts("common_fifo_dc", g_note_is_ful, g_fail_rd_emp, wr_rst, wr_clk, ful, wr_en, rd_clk, emp, rd_en);
END str;
astron_fifo/trunk/common_fifo_dc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/common_fifo_rd.vhd =================================================================== --- astron_fifo/trunk/common_fifo_rd.vhd (nonexistent) +++ astron_fifo/trunk/common_fifo_rd.vhd (revision 2) @@ -0,0 +1,78 @@ +------------------------------------------------------------------------------- +-- +-- 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 . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; + +-- Purpose: Adapt from ready latency 1 to 0 to make a look ahead FIFO +-- Description: - +-- Remark: +-- . Derived from dp_latency_adapter.vhd. +-- . There is no need for a rd_emp output signal, because a show ahead FIFO +-- will have rd_val='0' when it is empty. + + +ENTITY common_fifo_rd IS + GENERIC ( + g_dat_w : NATURAL := 18 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + -- ST sink: RL = 1 + fifo_req : OUT STD_LOGIC; + fifo_dat : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + fifo_val : IN STD_LOGIC := '0'; + -- ST source: RL = 0 + rd_req : IN STD_LOGIC; + rd_dat : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + rd_val : OUT STD_LOGIC + ); +END common_fifo_rd; + + +ARCHITECTURE wrap OF common_fifo_rd IS + + +BEGIN + + u_rl0 : ENTITY work.common_rl_decrease + GENERIC MAP ( + g_adapt => TRUE, + g_dat_w => g_dat_w + ) + PORT MAP ( + rst => rst, + clk => clk, + -- ST sink: RL = 1 + snk_out_ready => fifo_req, + snk_in_dat => fifo_dat, + snk_in_val => fifo_val, + -- ST source: RL = 0 + src_in_ready => rd_req, + src_out_dat => rd_dat, + src_out_val => rd_val + ); + +END wrap;
astron_fifo/trunk/common_fifo_rd.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/common_fifo_sc.vhd =================================================================== --- astron_fifo/trunk/common_fifo_sc.vhd (nonexistent) +++ astron_fifo/trunk/common_fifo_sc.vhd (revision 2) @@ -0,0 +1,177 @@ +------------------------------------------------------------------------------- +-- +-- 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: Single clock FIFO + +LIBRARY IEEE, common_pkg_lib, common_components_lib, technology_lib, tech_fifo_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +ENTITY common_fifo_sc IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_note_is_ful : BOOLEAN := TRUE; -- when TRUE report NOTE when FIFO goes full, fifo overflow is always reported as FAILURE + g_fail_rd_emp : BOOLEAN := FALSE; -- when TRUE report FAILURE when read from an empty FIFO + g_use_lut : BOOLEAN := FALSE; -- when TRUE then force using LUTs via Altera eab="OFF", + -- else use default eab="ON" and ram_block_type="AUTO", default ram_block_type="AUTO" is sufficient, because + -- there seems no need to force using RAM and there are two types of Stratix IV RAM (M9K and M144K) + g_reset : BOOLEAN := FALSE; -- when TRUE release FIFO reset some cycles after rst release, else use rst directly + g_init : BOOLEAN := FALSE; -- when TRUE force wr_req inactive for some cycles after FIFO reset release, else use wr_req as is + g_dat_w : NATURAL := 36; -- 36 * 256 = 1 M9K + g_nof_words : NATURAL := c_bram_m9k_fifo_depth; + g_af_margin : NATURAL := 0 -- FIFO almost full margin for wr_aful flagging + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + wr_dat : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + wr_req : IN STD_LOGIC; + wr_ful : OUT STD_LOGIC; + wr_aful : OUT STD_LOGIC; -- registered FIFO almost full flag + rd_dat : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + rd_req : IN STD_LOGIC; + rd_emp : OUT STD_LOGIC; + rd_val : OUT STD_LOGIC; + usedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_nof_words)-1 DOWNTO 0) + ); +END common_fifo_sc; + + +ARCHITECTURE str OF common_fifo_sc IS + + CONSTANT c_use_eab : STRING := sel_a_b(g_use_lut, "OFF", "ON"); -- when g_use_lut=TRUE then force using LUTs via Altera eab="OFF", else default to ram_block_type = "AUTO" + + CONSTANT c_fifo_af_latency : NATURAL := 1; -- pipeline register wr_aful + CONSTANT c_fifo_af_margin : NATURAL := g_af_margin+c_fifo_af_latency; -- FIFO almost full level + + SIGNAL fifo_rst : STD_LOGIC; + SIGNAL fifo_init : STD_LOGIC; + SIGNAL fifo_wr_en : STD_LOGIC; + SIGNAL nxt_fifo_wr_en : STD_LOGIC; + SIGNAL fifo_wr_dat : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL nxt_fifo_wr_dat : STD_LOGIC_VECTOR(fifo_wr_dat'RANGE); + SIGNAL fifo_rd_en : STD_LOGIC; + SIGNAL fifo_full : STD_LOGIC; + SIGNAL fifo_empty : STD_LOGIC; + SIGNAL fifo_usedw : STD_LOGIC_VECTOR(usedw'RANGE); + + SIGNAL nxt_wr_aful : STD_LOGIC; + SIGNAL nxt_rd_val : STD_LOGIC; + +BEGIN + + -- Control logic copied from common_fifo_sc(virtex4).vhd + + gen_fifo_rst : IF g_reset=TRUE GENERATE + -- Make sure the reset lasts at least 3 cycles (see fifo_generator_ug175.pdf). This is necessary in case + -- the FIFO reset is also used functionally to flush it, so not only after power up. + u_fifo_rst : ENTITY common_components_lib.common_areset + GENERIC MAP ( + g_rst_level => '1', + g_delay_len => 4 + ) + PORT MAP ( + in_rst => rst, + clk => clk, + out_rst => fifo_rst + ); + END GENERATE; + no_fifo_rst : IF g_reset=FALSE GENERATE + fifo_rst <= rst; + END GENERATE; + + gen_init : IF g_init=TRUE GENERATE + -- Wait at least 3 cycles after reset release before allowing fifo_wr_en (see fifo_generator_ug175.pdf) + u_fifo_init : ENTITY common_components_lib.common_areset + GENERIC MAP ( + g_rst_level => '1', + g_delay_len => 4 + ) + PORT MAP ( + in_rst => fifo_rst, + clk => clk, + out_rst => fifo_init + ); + + p_init_reg : PROCESS(fifo_rst, clk) + BEGIN + IF fifo_rst='1' THEN + fifo_wr_en <= '0'; + ELSIF rising_edge(clk) THEN + fifo_wr_dat <= nxt_fifo_wr_dat; + fifo_wr_en <= nxt_fifo_wr_en; + END IF; + END PROCESS; + + nxt_fifo_wr_dat <= wr_dat; + nxt_fifo_wr_en <= wr_req AND NOT fifo_init; -- check on NOT full is not necessary according to fifo_generator_ug175.pdf + END GENERATE; + no_init : IF g_init=FALSE GENERATE + fifo_wr_dat <= wr_dat; + fifo_wr_en <= wr_req; -- check on NOT full is not necessary according to fifo_generator_ug175.pdf + END GENERATE; + + wr_ful <= fifo_full; + rd_emp <= fifo_empty; + usedw <= fifo_usedw; + + fifo_rd_en <= rd_req; -- check on NOT empty is not necessary according to fifo_generator_ds317.pdf, so skip it to easy synthesis timing + + nxt_rd_val <= fifo_rd_en AND NOT fifo_empty; -- check on NOT empty is necessary for rd_val + + nxt_wr_aful <= '0' WHEN TO_UINT(fifo_usedw) g_technology, + g_use_eab => c_use_eab, + g_dat_w => g_dat_w, + g_nof_words => g_nof_words + ) + PORT MAP ( + aclr => fifo_rst, + clock => clk, + data => fifo_wr_dat, + rdreq => fifo_rd_en, + wrreq => fifo_wr_en, + empty => fifo_empty, + full => fifo_full, + q => rd_dat, + usedw => fifo_usedw + ); + + proc_common_fifo_asserts("common_fifo_sc", g_note_is_ful, g_fail_rd_emp, fifo_rst, clk, fifo_full, fifo_wr_en, clk, fifo_empty, fifo_rd_en); + +END str;
astron_fifo/trunk/common_fifo_sc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/common_rl_decrease.vhd =================================================================== --- astron_fifo/trunk/common_rl_decrease.vhd (nonexistent) +++ astron_fifo/trunk/common_rl_decrease.vhd (revision 2) @@ -0,0 +1,143 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2013 +-- 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 . +-- +------------------------------------------------------------------------------- + +-- >>> Ported from UniBoard dp_latency_adapter for fixed RL 0 --> 1 + +LIBRARY IEEE; +USE IEEE.std_logic_1164.ALL; + +-- Purpose: Adapt from ready latency 1 to 0 to make a look ahead FIFO +-- Description: - +-- Remark: +-- . A show ahead FIFO with RL=0 does not need a rd_emp output signal, because +-- with RL=0 the rd_val='0' when it is empty (so emp <= NOT rd_val). + + +ENTITY common_rl_decrease IS + GENERIC ( + g_adapt : BOOLEAN := TRUE; -- default when TRUE then decrease sink RL 1 to source RL 0, else then implement wires + g_dat_w : NATURAL := 18 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + -- ST sink: RL = 1 + snk_out_ready : OUT STD_LOGIC; + snk_in_dat : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + snk_in_val : IN STD_LOGIC := 'X'; + -- ST source: RL = 0 + src_in_ready : IN STD_LOGIC; + src_out_dat : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + src_out_val : OUT STD_LOGIC + ); +END common_rl_decrease; + + +ARCHITECTURE rtl OF common_rl_decrease IS + + -- Internally use streaming record for the SOSI, for the SISO.ready directly use src_in_ready + TYPE t_sosi IS RECORD -- Source Out or Sink In + data : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + valid : STD_LOGIC; + END RECORD; + + TYPE t_sosi_arr IS ARRAY (INTEGER RANGE <>) OF t_sosi; + + CONSTANT c_sosi_rst : t_sosi := ((OTHERS=>'0'), '0'); + + -- SOSI IO + SIGNAL snk_in : t_sosi; + SIGNAL src_out : t_sosi; + + -- The default FIFO has ready latency RL = 1, need to use input RL + 1 words for the buf array, to go to output RL = 0 for show ahead FIFO + SIGNAL buf : t_sosi_arr(1 DOWNTO 0); + SIGNAL nxt_buf : t_sosi_arr(1 DOWNTO 0); + +BEGIN + + gen_wires : IF g_adapt=FALSE GENERATE + snk_out_ready <= src_in_ready; + + src_out_dat <= snk_in_dat; + src_out_val <= snk_in_val; + END GENERATE; + + gen_adapt : IF g_adapt=TRUE GENERATE + snk_in.data <= snk_in_dat; + snk_in.valid <= snk_in_val; + + src_out_dat <= src_out.data; + src_out_val <= src_out.valid; + + -- Buf[0] contains the FIFO output with zero ready latency + src_out <= buf(0); + + p_clk : PROCESS(rst, clk) + BEGIN + IF rst='1' THEN + buf <= (OTHERS=>c_sosi_rst); + ELSIF rising_edge(clk) THEN + buf <= nxt_buf; + END IF; + END PROCESS; + + p_snk_out_ready : PROCESS(buf, src_in_ready, snk_in) + BEGIN + snk_out_ready <= '0'; + IF src_in_ready='1' THEN + -- Default snk_out_ready when src_in_ready. + snk_out_ready <= '1'; + ELSE + -- Extra snk_out_ready to look ahead for RL = 0. + IF buf(0).valid='0' THEN + snk_out_ready <= '1'; + ELSIF buf(1).valid='0' THEN + snk_out_ready <= NOT(snk_in.valid); + END IF; + END IF; + END PROCESS; + + p_buf : PROCESS(buf, src_in_ready, snk_in) + BEGIN + -- Keep or shift the buf dependent on src_in_ready, no need to explicitly check buf().valid + nxt_buf <= buf; + IF src_in_ready='1' THEN + nxt_buf(0) <= buf(1); + nxt_buf(1).valid <= '0'; -- not strictly necessary, but robust + END IF; + + -- Put input data at the first available location dependent on src_in_ready, no need to explicitly check snk_in_val + IF buf(0).valid='0' THEN + nxt_buf(0) <= snk_in; + ELSE + IF buf(1).valid='0' THEN + IF src_in_ready='0' THEN + nxt_buf(1) <= snk_in; + ELSE + nxt_buf(0) <= snk_in; + END IF; + END IF; + END IF; + END PROCESS; + END GENERATE; + +END rtl;
astron_fifo/trunk/common_rl_decrease.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/dp_fifo_core.vhd =================================================================== --- astron_fifo/trunk/dp_fifo_core.vhd (nonexistent) +++ astron_fifo/trunk/dp_fifo_core.vhd (revision 2) @@ -0,0 +1,260 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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: +-- Provide input ready control and use output ready control to the FIFO. +-- Pass sop and eop along with the data through the FIFO if g_use_ctrl=TRUE. +-- Default the RL=1, use g_fifo_rl=0 for a the show ahead FIFO. +-- Description: +-- Provide the sink ready for FIFO write control and use source ready for +-- FIFO read access. The sink ready output is derived from FIFO almost full. +-- Data without framing can use g_use_ctrl=FALSE to avoid implementing two +-- data bits for sop and eop in the FIFO word width. Idem for g_use_sync, +-- g_use_empty, g_use_channel and g_use_error. +-- Remark: +-- . The bsn, empty, channel and error fields are valid at the sop and or eop. +-- Therefore alternatively these fields can be passed on through a separate +-- FIFO, with only one entry per frame, to save FIFO memory in case +-- concatenating them makes the FIFO word width larger than a standard +-- memory data word width. +-- . The FIFO makes that the src_in.ready and snk_out.ready are not +-- combinatorially connected, so this can ease the timing closure for the +-- ready signal. + +LIBRARY IEEE, common_pkg_lib, dp_components_lib, common_fifo_lib, dp_pkg_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_fifo_core IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_note_is_ful : BOOLEAN := TRUE; -- when TRUE report NOTE when FIFO goes full, fifo overflow is always reported as FAILURE + g_use_dual_clock : BOOLEAN := FALSE; + g_use_lut_sc : BOOLEAN := FALSE; -- when TRUE then force using LUTs instead of block RAM for single clock FIFO (bot available for dual clock FIFO) + g_data_w : NATURAL := 16; -- Should be 2 times the c_complex_w if g_use_complex = TRUE + g_data_signed : BOOLEAN := FALSE; -- TRUE extends g_data_w bits with the sign bit, FALSE pads g_data_w bits with zeros. + g_bsn_w : NATURAL := 1; + g_empty_w : NATURAL := 1; + g_channel_w : NATURAL := 1; + g_error_w : NATURAL := 1; + g_use_bsn : BOOLEAN := FALSE; + g_use_empty : BOOLEAN := FALSE; + g_use_channel : BOOLEAN := FALSE; + g_use_error : BOOLEAN := FALSE; + g_use_sync : BOOLEAN := FALSE; + g_use_ctrl : BOOLEAN := TRUE; -- sop & eop + g_use_complex : BOOLEAN := FALSE; -- TRUE feeds the concatenated complex fields (im & re) through the FIFO instead of the data field. + g_fifo_size : NATURAL := 512; -- (16+2) * 512 = 1 M9K, g_data_w+2 for sop and eop + g_fifo_af_margin : NATURAL := 4; -- >=4, Nof words below max (full) at which fifo is considered almost full + g_fifo_rl : NATURAL := 1 + ); + PORT ( + wr_rst : IN STD_LOGIC; + wr_clk : IN STD_LOGIC; + rd_rst : IN STD_LOGIC; + rd_clk : IN STD_LOGIC; + -- Monitor FIFO filling + wr_ful : OUT STD_LOGIC; -- corresponds to the carry bit of wr_usedw when FIFO is full + wr_usedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_fifo_size)-1 DOWNTO 0); + rd_usedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_fifo_size)-1 DOWNTO 0); + rd_emp : OUT STD_LOGIC; + -- ST sink + snk_out : OUT t_dp_siso; + snk_in : IN t_dp_sosi; + -- ST source + src_in : IN t_dp_siso; + src_out : OUT t_dp_sosi + ); +END dp_fifo_core; + + +ARCHITECTURE str OF dp_fifo_core IS + + CONSTANT c_use_data : BOOLEAN := TRUE; + CONSTANT c_ctrl_w : NATURAL := 2; -- sop and eop + + CONSTANT c_complex_w : NATURAL := smallest(c_dp_stream_dsp_data_w, g_data_w/2); -- needed to cope with g_data_w > 2*c_dp_stream_dsp_data_w + + CONSTANT c_fifo_almost_full : NATURAL := g_fifo_size-g_fifo_af_margin; -- FIFO almost full level for snk_out.ready + CONSTANT c_fifo_dat_w : NATURAL := func_slv_concat_w(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, + g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w); -- concat via FIFO + + SIGNAL nxt_snk_out : t_dp_siso := c_dp_siso_rst; + + SIGNAL arst : STD_LOGIC; + + SIGNAL wr_data_complex : STD_LOGIC_VECTOR(2*c_complex_w-1 DOWNTO 0); + SIGNAL wr_data : STD_LOGIC_VECTOR(g_data_w-1 DOWNTO 0); + SIGNAL rd_data : STD_LOGIC_VECTOR(g_data_w-1 DOWNTO 0); + + SIGNAL fifo_wr_dat : STD_LOGIC_VECTOR(c_fifo_dat_w-1 DOWNTO 0); + SIGNAL fifo_wr_req : STD_LOGIC; + SIGNAL fifo_wr_ful : STD_LOGIC; + SIGNAL fifo_wr_usedw : STD_LOGIC_VECTOR(wr_usedw'RANGE); + + SIGNAL fifo_rd_dat : STD_LOGIC_VECTOR(c_fifo_dat_w-1 DOWNTO 0) := (OTHERS=>'0'); + SIGNAL fifo_rd_val : STD_LOGIC; + SIGNAL fifo_rd_req : STD_LOGIC; + SIGNAL fifo_rd_emp : STD_LOGIC; + SIGNAL fifo_rd_usedw : STD_LOGIC_VECTOR(rd_usedw'RANGE); + + SIGNAL wr_sync : STD_LOGIC_VECTOR(0 DOWNTO 0); + SIGNAL rd_sync : STD_LOGIC_VECTOR(0 DOWNTO 0); + SIGNAL wr_ctrl : STD_LOGIC_VECTOR(1 DOWNTO 0); + SIGNAL rd_ctrl : STD_LOGIC_VECTOR(1 DOWNTO 0); + + SIGNAL rd_siso : t_dp_siso; + SIGNAL rd_sosi : t_dp_sosi := c_dp_sosi_rst; -- initialize default values for unused sosi fields + +BEGIN + + -- Output monitor FIFO filling + wr_ful <= fifo_wr_ful; + wr_usedw <= fifo_wr_usedw; + rd_usedw <= fifo_rd_usedw; + rd_emp <= fifo_rd_emp; + + p_wr_clk: PROCESS(wr_clk, wr_rst) + BEGIN + IF wr_rst='1' THEN + snk_out <= c_dp_siso_rst; + ELSIF rising_edge(wr_clk) THEN + snk_out <= nxt_snk_out; + END IF; + END PROCESS; + + wr_sync(0) <= snk_in.sync; + wr_ctrl <= snk_in.sop & snk_in.eop; + + -- Assign the snk_in data field or concatenated complex fields to the FIFO wr_data depending on g_use_complex + wr_data_complex <= snk_in.im(c_complex_w-1 DOWNTO 0) & snk_in.re(c_complex_w-1 DOWNTO 0); + wr_data <= snk_in.data(g_data_w-1 DOWNTO 0) WHEN g_use_complex = FALSE ELSE RESIZE_UVEC(wr_data_complex, g_data_w); + + -- fifo wr wires + fifo_wr_req <= snk_in.valid; + fifo_wr_dat <= func_slv_concat(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, + wr_data, + snk_in.bsn( g_bsn_w-1 DOWNTO 0), + snk_in.empty( g_empty_w-1 DOWNTO 0), + snk_in.channel(g_channel_w-1 DOWNTO 0), + snk_in.err( g_error_w-1 DOWNTO 0), + wr_sync, + wr_ctrl); + + -- pass on frame level flow control + nxt_snk_out.xon <= src_in.xon; + + -- up stream use fifo almost full to control snk_out.ready + nxt_snk_out.ready <= '1' WHEN UNSIGNED(fifo_wr_usedw) g_technology, + g_note_is_ful => g_note_is_ful, + g_use_lut => g_use_lut_sc, + g_dat_w => c_fifo_dat_w, + g_nof_words => g_fifo_size + ) + PORT MAP ( + rst => rd_rst, + clk => rd_clk, + wr_dat => fifo_wr_dat, + wr_req => fifo_wr_req, + wr_ful => fifo_wr_ful, + rd_dat => fifo_rd_dat, + rd_req => fifo_rd_req, + rd_emp => fifo_rd_emp, + rd_val => fifo_rd_val, + usedw => fifo_rd_usedw + ); + + fifo_wr_usedw <= fifo_rd_usedw; + END GENERATE; + + gen_common_fifo_dc : IF g_use_dual_clock=TRUE GENERATE + u_common_fifo_dc : ENTITY common_fifo_lib.common_fifo_dc + GENERIC MAP ( + g_technology => g_technology, + g_dat_w => c_fifo_dat_w, + g_nof_words => g_fifo_size + ) + PORT MAP ( + rst => arst, + wr_clk => wr_clk, + wr_dat => fifo_wr_dat, + wr_req => fifo_wr_req, + wr_ful => fifo_wr_ful, + wrusedw => fifo_wr_usedw, + rd_clk => rd_clk, + rd_dat => fifo_rd_dat, + rd_req => fifo_rd_req, + rd_emp => fifo_rd_emp, + rdusedw => fifo_rd_usedw, + rd_val => fifo_rd_val + ); + + arst <= wr_rst OR rd_rst; + END GENERATE; + + -- Extract the data from the wide FIFO output SLV. rd_data will be assigned to rd_sosi.data or rd_sosi.im & rd_sosi.re depending on g_use_complex. + rd_data <= func_slv_extract(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w, fifo_rd_dat, 0); + + -- fifo rd wires + -- SISO + fifo_rd_req <= rd_siso.ready; + + -- SOSI + rd_sosi.data <= RESIZE_DP_SDATA(rd_data) WHEN g_data_signed=TRUE ELSE RESIZE_DP_DATA(rd_data); + rd_sosi.re <= RESIZE_DP_DSP_DATA(rd_data( c_complex_w-1 DOWNTO 0)); + rd_sosi.im <= RESIZE_DP_DSP_DATA(rd_data(2*c_complex_w-1 DOWNTO c_complex_w)); + rd_sosi.bsn <= RESIZE_DP_BSN(func_slv_extract(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w, fifo_rd_dat, 1)); + rd_sosi.empty <= RESIZE_DP_EMPTY(func_slv_extract(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w, fifo_rd_dat, 2)); + rd_sosi.channel <= RESIZE_DP_CHANNEL(func_slv_extract(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w, fifo_rd_dat, 3)); + rd_sosi.err <= RESIZE_DP_ERROR(func_slv_extract(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w, fifo_rd_dat, 4)); + rd_sync <= func_slv_extract(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w, fifo_rd_dat, 5); + rd_ctrl <= func_slv_extract(c_use_data, g_use_bsn, g_use_empty, g_use_channel, g_use_error, g_use_sync, g_use_ctrl, g_data_w, g_bsn_w, g_empty_w, g_channel_w, g_error_w, 1, c_ctrl_w, fifo_rd_dat, 6); + + rd_sosi.sync <= fifo_rd_val AND rd_sync(0); + rd_sosi.valid <= fifo_rd_val; + rd_sosi.sop <= fifo_rd_val AND rd_ctrl(1); + rd_sosi.eop <= fifo_rd_val AND rd_ctrl(0); + + u_ready_latency : ENTITY dp_components_lib.dp_latency_adapter + GENERIC MAP ( + g_in_latency => 1, + g_out_latency => g_fifo_rl + ) + PORT MAP ( + rst => rd_rst, + clk => rd_clk, + -- ST sink + snk_out => rd_siso, + snk_in => rd_sosi, + -- ST source + src_in => src_in, + src_out => src_out + ); + +END str;
astron_fifo/trunk/dp_fifo_core.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/dp_fifo_dc.vhd =================================================================== --- astron_fifo/trunk/dp_fifo_dc.vhd (nonexistent) +++ astron_fifo/trunk/dp_fifo_dc.vhd (revision 2) @@ -0,0 +1,112 @@ +-------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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: DP FIFO for dual clock (= dc) domain wr and rd. +-- Description: See dp_fifo_core.vhd. + +LIBRARY IEEE, common_pkg_lib, dp_pkg_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_fifo_dc IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_data_w : NATURAL := 16; -- Should be 2 times the c_complex_w if g_use_complex = TRUE + g_bsn_w : NATURAL := 1; + g_empty_w : NATURAL := 1; + g_channel_w : NATURAL := 1; + g_error_w : NATURAL := 1; + g_use_bsn : BOOLEAN := FALSE; + g_use_empty : BOOLEAN := FALSE; + g_use_channel : BOOLEAN := FALSE; + g_use_error : BOOLEAN := FALSE; + g_use_sync : BOOLEAN := FALSE; + g_use_ctrl : BOOLEAN := TRUE; -- sop & eop + g_use_complex : BOOLEAN := FALSE; -- TRUE feeds the concatenated complex fields (im & re) through the FIFO instead of the data field. + g_fifo_size : NATURAL := 512; -- (16+2) * 512 = 1 M9K, g_data_w+2 for sop and eop + g_fifo_af_margin : NATURAL := 4; -- >=4, Nof words below max (full) at which fifo is considered almost full + g_fifo_rl : NATURAL := 1 + ); + PORT ( + wr_rst : IN STD_LOGIC; + wr_clk : IN STD_LOGIC; + rd_rst : IN STD_LOGIC; + rd_clk : IN STD_LOGIC; + -- Monitor FIFO filling + wr_ful : OUT STD_LOGIC; + wr_usedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_fifo_size)-1 DOWNTO 0); + rd_usedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_fifo_size)-1 DOWNTO 0); + rd_emp : OUT STD_LOGIC; + -- ST sink + snk_out : OUT t_dp_siso; + snk_in : IN t_dp_sosi; + -- ST source + src_in : IN t_dp_siso; + src_out : OUT t_dp_sosi + ); +END dp_fifo_dc; + + +ARCHITECTURE str OF dp_fifo_dc IS +BEGIN + + u_dp_fifo_core : ENTITY work.dp_fifo_core + GENERIC MAP ( + g_technology => g_technology, + g_use_dual_clock => TRUE, + g_data_w => g_data_w, + g_bsn_w => g_bsn_w, + g_empty_w => g_empty_w, + g_channel_w => g_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_channel, + g_use_error => g_use_error, + g_use_sync => g_use_sync, + g_use_ctrl => g_use_ctrl, + g_use_complex => g_use_complex, + g_fifo_size => g_fifo_size, + g_fifo_af_margin => g_fifo_af_margin, + g_fifo_rl => g_fifo_rl + ) + PORT MAP ( + wr_rst => wr_rst, + wr_clk => wr_clk, + rd_rst => rd_rst, + rd_clk => rd_clk, + -- Monitor FIFO filling + wr_ful => wr_ful, + wr_usedw => wr_usedw, + rd_usedw => rd_usedw, + rd_emp => rd_emp, + -- ST sink + snk_out => snk_out, + snk_in => snk_in, + -- ST source + src_in => src_in, + src_out => src_out + ); + +END str;
astron_fifo/trunk/dp_fifo_dc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/dp_fifo_fill.vhd =================================================================== --- astron_fifo/trunk/dp_fifo_fill.vhd (nonexistent) +++ astron_fifo/trunk/dp_fifo_fill.vhd (revision 2) @@ -0,0 +1,122 @@ +-------------------------------------------------------------------------------- +-- +-- 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: Wrapper of dp_fifo_fill_sc.vhd +-- Description: See dp_fifo_fill_core.vhd +-- Remark: +-- This wrapper is for backwards compatibility, better use dp_fifo_fill_sc.vhd +-- for new designs. + +LIBRARY IEEE, common_pkg_lib, dp_pkg_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_fifo_fill IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_data_w : NATURAL := 16; + g_bsn_w : NATURAL := 1; + g_empty_w : NATURAL := 1; + g_channel_w : NATURAL := 1; + g_error_w : NATURAL := 1; + g_use_bsn : BOOLEAN := FALSE; + g_use_empty : BOOLEAN := FALSE; + g_use_channel : BOOLEAN := FALSE; + g_use_error : BOOLEAN := FALSE; + g_use_sync : BOOLEAN := FALSE; + g_use_complex : BOOLEAN := FALSE; -- TRUE feeds the concatenated complex fields (im & re) through the FIFO instead of the data field. + g_fifo_fill : NATURAL := 0; + g_fifo_size : NATURAL := 256; -- (32+2) * 256 = 1 M9K, g_data_w+2 for sop and eop + g_fifo_af_margin : NATURAL := 4; -- Nof words below max (full) at which fifo is considered almost full + g_fifo_rl : NATURAL := 1 -- use RL=0 for internal show ahead FIFO, default use RL=1 for internal normal FIFO + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + + -- Monitor FIFO filling + wr_ful : OUT STD_LOGIC; + usedw : OUT STD_LOGIC_VECTOR(ceil_log2(largest(g_fifo_size, g_fifo_fill + g_fifo_af_margin + 2))-1 DOWNTO 0); -- = ceil_log2(c_fifo_size)-1 DOWNTO 0 + rd_emp : OUT STD_LOGIC; + + -- MM control FIFO filling (assume 32 bit MM interface) + wr_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); -- = wr_usedw + rd_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); -- = rd_usedw + rd_fill_32b : IN STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := TO_UVEC(g_fifo_fill, c_word_w); + + -- ST sink + snk_out : OUT t_dp_siso; + snk_in : IN t_dp_sosi; + -- ST source + src_in : IN t_dp_siso; + src_out : OUT t_dp_sosi + ); +END dp_fifo_fill; + + +ARCHITECTURE str OF dp_fifo_fill IS +BEGIN + + u_dp_fifo_fill_sc : ENTITY work.dp_fifo_fill_sc + GENERIC MAP ( + g_technology => g_technology, + g_data_w => g_data_w, + g_bsn_w => g_bsn_w, + g_empty_w => g_empty_w, + g_channel_w => g_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_channel, + g_use_error => g_use_error, + g_use_sync => g_use_sync, + g_use_complex => g_use_complex, + g_fifo_fill => g_fifo_fill, + g_fifo_size => g_fifo_size, + g_fifo_af_margin => g_fifo_af_margin, + g_fifo_rl => g_fifo_rl + ) + PORT MAP ( + rst => rst, + clk => clk, + + -- Monitor FIFO filling + wr_ful => wr_ful, + usedw => usedw, + rd_emp => rd_emp, + + -- MM control FIFO filling (assume 32 bit MM interface) + wr_usedw_32b => wr_usedw_32b, + rd_usedw_32b => rd_usedw_32b, + rd_fill_32b => rd_fill_32b, + + -- ST sink + snk_out => snk_out, + snk_in => snk_in, + -- ST source + src_in => src_in, + src_out => src_out + ); + +END str;
astron_fifo/trunk/dp_fifo_fill.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/dp_fifo_fill_core.vhd =================================================================== --- astron_fifo/trunk/dp_fifo_fill_core.vhd (nonexistent) +++ astron_fifo/trunk/dp_fifo_fill_core.vhd (revision 2) @@ -0,0 +1,404 @@ +-------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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: +-- The FIFO starts outputting data when the output is ready and it has been +-- filled with more than g_fifo_fill words. Given a fixed frame length, this +-- is useful when the in_val is throttled while the out_val should not be +-- inactive valid between out_sop to out_eop. This is necessary for frame +-- transport over a PHY link without separate data valid signal. +-- Description: +-- The FIFO is filled sufficiently for each input frame, as defined by the +-- sop and then read until the eop. +-- The rd_fill_32b control input is used for dynamic control of the fill +-- level on the read side of the FIFO. The rd_fill_32b defaults to +-- g_fifo_fill, so if rd_fill_32b is not connected then the fill level is +-- fixed to g_fifo_fill. A g_fifo_fill disables the fifo fill mechanism. +-- The rd_fill_32b signal must be stable in the rd_clk domain. +-- Remarks: +-- . Reuse from LOFAR rad_frame_scheduler.vhd and rad_frame_scheduler(rtl).vhd +-- . For g_fifo_fill=0 this dp_fifo_fill_core defaults to dp_fifo_core. +-- . The architecture offers two implementations via g_fifo_rl. Use 0 for show +-- ahead FIFO or 1 for normal FIFO. At the output of dp_fifo_fill_core the +-- RL=1 independent of g_fifo_rl, the g_fifo_rl only applies to the internal +-- FIFO. The show ahead FIFO uses the dp_latency_adapter to get to RL 0 +-- internally. The normal FIFO is prefered, because it uses less logic. It +-- keeps the RL internally also at 1. +-- . Note that the structure of p_state is idendical in both architectures +-- for both g_fifo_rl=0 or 1. Hence the implementation of g_fifo_rl=1 with +-- dp_input_hold is an example of how to use dp_input_hold to get the same +-- behaviour as if the input had g_fifo_rl=0 as with the show ahead FIFO. +-- . To view the similarity of the p_state process for both g_fifo_rl e.g. +-- open the file in two editors or do repeatedly find (F3) on a text +-- section like 'WHEN s_fill =>' that only occurs one in each p_state. +-- . The next_src_out = pend_src_out when src_in.ready='1'. However it is more +-- clear to only use pend_src_out and explicitely write the condition on +-- src_in.ready in the code, because then the structure of p_state is the +-- same for both g_fifo_rl=0 or 1. Furthermore using pend_src_out and +-- src_in.ready is often more clear to comprehend then using next_src_out +-- directly. + +LIBRARY IEEE, common_pkg_lib, dp_pkg_lib, dp_components_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_fifo_fill_core IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_use_dual_clock : BOOLEAN := FALSE; + g_data_w : NATURAL := 16; + g_bsn_w : NATURAL := 1; + g_empty_w : NATURAL := 1; + g_channel_w : NATURAL := 1; + g_error_w : NATURAL := 1; + g_use_bsn : BOOLEAN := FALSE; + g_use_empty : BOOLEAN := FALSE; + g_use_channel : BOOLEAN := FALSE; + g_use_error : BOOLEAN := FALSE; + g_use_sync : BOOLEAN := FALSE; + g_use_complex : BOOLEAN := FALSE; -- TRUE feeds the concatenated complex fields (im & re) through the FIFO instead of the data field. + g_fifo_fill : NATURAL := 0; + g_fifo_size : NATURAL := 256; -- (32+2) * 256 = 1 M9K, g_data_w+2 for sop and eop + g_fifo_af_margin : NATURAL := 4; -- Nof words below max (full) at which fifo is considered almost full + g_fifo_rl : NATURAL := 1 -- use RL=0 for internal show ahead FIFO, default use RL=1 for internal normal FIFO + ); + PORT ( + wr_rst : IN STD_LOGIC; + wr_clk : IN STD_LOGIC; + rd_rst : IN STD_LOGIC; + rd_clk : IN STD_LOGIC; + -- Monitor FIFO filling + wr_ful : OUT STD_LOGIC; -- corresponds to the carry bit of wr_usedw when FIFO is full + wr_usedw : OUT STD_LOGIC_VECTOR(ceil_log2(largest(g_fifo_size, g_fifo_fill + g_fifo_af_margin + 2))-1 DOWNTO 0); -- = ceil_log2(c_fifo_size)-1 DOWNTO 0 + rd_usedw : OUT STD_LOGIC_VECTOR(ceil_log2(largest(g_fifo_size, g_fifo_fill + g_fifo_af_margin + 2))-1 DOWNTO 0); -- = ceil_log2(c_fifo_size)-1 DOWNTO 0 + rd_emp : OUT STD_LOGIC; + -- MM control FIFO filling (assume 32 bit MM interface) + wr_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); -- = wr_usedw + rd_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); -- = rd_usedw + rd_fill_32b : IN STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := TO_UVEC(g_fifo_fill, c_word_w); + -- ST sink + snk_out : OUT t_dp_siso; + snk_in : IN t_dp_sosi; + -- ST source + src_in : IN t_dp_siso; + src_out : OUT t_dp_sosi + ); +END dp_fifo_fill_core; + + +ARCHITECTURE rtl OF dp_fifo_fill_core IS + + CONSTANT c_fifo_rl : NATURAL := sel_a_b(g_fifo_fill=0, 1, g_fifo_rl); + CONSTANT c_fifo_fill_margin : NATURAL := g_fifo_af_margin + 2; -- add +2 extra margin, with tb_dp_fifo_fill it follows that +1 is also enough to avoid almost full when fifo is operating near g_fifo_fill level + CONSTANT c_fifo_size : NATURAL := largest(g_fifo_size, g_fifo_fill + c_fifo_fill_margin); + CONSTANT c_fifo_size_w : NATURAL := ceil_log2(c_fifo_size); -- = wr_usedw'LENGTH = rd_usedw'LENGTH + + -- The FIFO filling relies on framed data, so contrary to dp_fifo_sc the sop and eop need to be used. + CONSTANT c_use_ctrl : BOOLEAN := TRUE; + + -- Define t_state as slv to avoid Modelsim warning "Nonresolved signal 'nxt_state' may have multiple sources". Due to that g_fifo_rl = 0 or 1 ar both supported. + --TYPE t_state IS (s_idle, s_fill, s_output, s_xoff); + CONSTANT s_idle : STD_LOGIC_VECTOR(1 DOWNTO 0) := "00"; + CONSTANT s_fill : STD_LOGIC_VECTOR(1 DOWNTO 0) := "01"; + CONSTANT s_output : STD_LOGIC_VECTOR(1 DOWNTO 0) := "10"; + CONSTANT s_xoff : STD_LOGIC_VECTOR(1 DOWNTO 0) := "11"; + + SIGNAL state : STD_LOGIC_VECTOR(1 DOWNTO 0); -- t_state + SIGNAL nxt_state : STD_LOGIC_VECTOR(1 DOWNTO 0); -- t_state + + SIGNAL xon_reg : STD_LOGIC; + SIGNAL nxt_xon_reg : STD_LOGIC; + + SIGNAL rd_siso : t_dp_siso; + SIGNAL rd_sosi : t_dp_sosi := c_dp_sosi_rst; -- initialize default values for unused sosi fields; + + SIGNAL wr_fifo_usedw : STD_LOGIC_VECTOR(c_fifo_size_w-1 DOWNTO 0); -- = wr_usedw'RANGE + SIGNAL rd_fifo_usedw : STD_LOGIC_VECTOR(c_fifo_size_w-1 DOWNTO 0); -- = rd_usedw'RANGE + SIGNAL rd_fill_ctrl : STD_LOGIC_VECTOR(c_fifo_size_w-1 DOWNTO 0); -- used to resize rd_fill_32b to actual maximum width + + SIGNAL i_src_out : t_dp_sosi; + SIGNAL nxt_src_out : t_dp_sosi; + + -- Signals for g_fifo_rl=1 + SIGNAL hold_src_in : t_dp_siso; + SIGNAL pend_src_out : t_dp_sosi; + +BEGIN + + -- Output monitor FIFO filling + wr_usedw <= wr_fifo_usedw; + rd_usedw <= rd_fifo_usedw; + + -- Control FIFO fill level + wr_usedw_32b <= RESIZE_UVEC(wr_fifo_usedw, c_word_w); + rd_usedw_32b <= RESIZE_UVEC(rd_fifo_usedw, c_word_w); + + rd_fill_ctrl <= rd_fill_32b(c_fifo_size_w-1 DOWNTO 0); + + gen_dp_fifo_sc : IF g_use_dual_clock=FALSE GENERATE + u_dp_fifo_sc : ENTITY work.dp_fifo_sc + GENERIC MAP ( + g_technology => g_technology, + g_data_w => g_data_w, + g_bsn_w => g_bsn_w, + g_empty_w => g_empty_w, + g_channel_w => g_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_channel, + g_use_error => g_use_error, + g_use_sync => g_use_sync, + g_use_ctrl => c_use_ctrl, + g_use_complex => g_use_complex, + g_fifo_size => c_fifo_size, + g_fifo_af_margin => g_fifo_af_margin, + g_fifo_rl => c_fifo_rl + ) + PORT MAP ( + rst => rd_rst, + clk => rd_clk, + -- Monitor FIFO filling + wr_ful => wr_ful, + usedw => rd_fifo_usedw, + rd_emp => rd_emp, + -- ST sink + snk_out => snk_out, + snk_in => snk_in, + -- ST source + src_in => rd_siso, -- for RL = 0 rd_siso.ready acts as read acknowledge, for RL = 1 rd_siso.ready acts as read request + src_out => rd_sosi + ); + + wr_fifo_usedw <= rd_fifo_usedw; + END GENERATE; + + gen_dp_fifo_dc : IF g_use_dual_clock=TRUE GENERATE + u_dp_fifo_dc : ENTITY work.dp_fifo_dc + GENERIC MAP ( + g_technology => g_technology, + g_data_w => g_data_w, + g_bsn_w => g_bsn_w, + g_empty_w => g_empty_w, + g_channel_w => g_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_channel, + g_use_error => g_use_error, + g_use_sync => g_use_sync, + g_use_ctrl => c_use_ctrl, + --g_use_complex => g_use_complex, + g_fifo_size => c_fifo_size, + g_fifo_af_margin => g_fifo_af_margin, + g_fifo_rl => c_fifo_rl + ) + PORT MAP ( + wr_rst => wr_rst, + wr_clk => wr_clk, + rd_rst => rd_rst, + rd_clk => rd_clk, + -- Monitor FIFO filling + wr_ful => wr_ful, + wr_usedw => wr_fifo_usedw, + rd_usedw => rd_fifo_usedw, + rd_emp => rd_emp, + -- ST sink + snk_out => snk_out, + snk_in => snk_in, + -- ST source + src_in => rd_siso, -- for RL = 0 rd_siso.ready acts as read acknowledge, -- for RL = 1 rd_siso.ready acts as read request + src_out => rd_sosi + ); + END GENERATE; + + no_fill : IF g_fifo_fill=0 GENERATE + rd_siso <= src_in; -- SISO + src_out <= rd_sosi; -- SOSI + END GENERATE; -- no_fill + + gen_fill : IF g_fifo_fill>0 GENERATE + + src_out <= i_src_out; + + p_rd_clk: PROCESS(rd_clk, rd_rst) + BEGIN + IF rd_rst='1' THEN + xon_reg <= '0'; + state <= s_idle; + i_src_out <= c_dp_sosi_rst; + ELSIF rising_edge(rd_clk) THEN + xon_reg <= nxt_xon_reg; + state <= nxt_state; + i_src_out <= nxt_src_out; + END IF; + END PROCESS; + + nxt_xon_reg <= src_in.xon; -- register xon to easy timing closure + + gen_rl_0 : IF g_fifo_rl=0 GENERATE + p_state : PROCESS(state, rd_sosi, src_in, xon_reg, rd_fifo_usedw, rd_fill_ctrl) + BEGIN + nxt_state <= state; + + rd_siso <= src_in; -- default acknowledge (RL=1) this input when output is ready + + -- The output register stage increase RL=0 to 1, so it matches RL = 1 for src_in.ready + nxt_src_out <= rd_sosi; + nxt_src_out.valid <= '0'; -- default no output + nxt_src_out.sop <= '0'; + nxt_src_out.eop <= '0'; + nxt_src_out.sync <= '0'; + + CASE state IS + WHEN s_idle => + IF xon_reg='0' THEN + nxt_state <= s_xoff; + ELSE + -- read the FIFO until the sop is pending at the output, so discard any valid data between eop and sop + IF rd_sosi.sop='0' THEN + rd_siso <= c_dp_siso_rdy; -- acknowledge (RL=0) this input independent of output ready + ELSE + rd_siso <= c_dp_siso_hold; -- stop the input, hold the rd_sosi.sop at FIFO output (RL=0) + nxt_state <= s_fill; + END IF; + END IF; + WHEN s_fill => + IF xon_reg='0' THEN + nxt_state <= s_xoff; + ELSE + -- stop reading until the FIFO has been filled sufficiently + IF UNSIGNED(rd_fifo_usedw) + -- if the output is ready continue outputting the frame, ignore xon_reg during this frame + IF src_in.ready='1' THEN + nxt_src_out <= rd_sosi; -- output valid + IF rd_sosi.eop='1' THEN + nxt_state <= s_idle; -- output eop, so stop reading the FIFO + END IF; + END IF; + WHEN OTHERS => -- s_xoff + -- Flush the fill FIFO when xon='0' + rd_siso <= c_dp_siso_flush; + IF xon_reg='1' THEN + nxt_state <= s_idle; + END IF; + END CASE; + + -- Pass on frame level flow control + rd_siso.xon <= src_in.xon; + END PROCESS; + END GENERATE; -- gen_rl_0 + + gen_rl_1 : IF g_fifo_rl=1 GENERATE + -- Use dp_hold_input to get equivalent implementation with default RL=1 FIFO. + + -- Hold the sink input for source output + u_snk : ENTITY dp_components_lib.dp_hold_input + PORT MAP ( + rst => rd_rst, + clk => rd_clk, + -- ST sink + snk_out => rd_siso, -- SISO ready + snk_in => rd_sosi, -- SOSI + -- ST source + src_in => hold_src_in, -- SISO ready + next_src_out => OPEN, -- SOSI + pend_src_out => pend_src_out, + src_out_reg => i_src_out + ); + + p_state : PROCESS(state, src_in, xon_reg, pend_src_out, rd_fifo_usedw, rd_fill_ctrl) + BEGIN + nxt_state <= state; + + hold_src_in <= src_in; -- default request (RL=1) new input when output is ready + + -- The output register stage matches RL = 1 for src_in.ready + nxt_src_out <= pend_src_out; + nxt_src_out.valid <= '0'; -- default no output + nxt_src_out.sop <= '0'; + nxt_src_out.eop <= '0'; + nxt_src_out.sync <= '0'; + + CASE state IS + WHEN s_idle => + IF xon_reg='0' THEN + nxt_state <= s_xoff; + ELSE + -- read the FIFO until the sop is pending at the output, so discard any valid data between eop and sop + IF pend_src_out.sop='0' THEN + hold_src_in <= c_dp_siso_rdy; -- request (RL=1) new input independent of output ready + ELSE + hold_src_in <= c_dp_siso_hold; -- stop the input, hold the pend_src_out.sop in dp_hold_input + nxt_state <= s_fill; + END IF; + END IF; + WHEN s_fill => + IF xon_reg='0' THEN + nxt_state <= s_xoff; + ELSE + -- stop reading until the FIFO has been filled sufficiently + IF UNSIGNED(rd_fifo_usedw) + -- if the output is ready continue outputting the input frame, ignore xon_reg during this frame + IF src_in.ready='1' THEN + nxt_src_out <= pend_src_out; -- output valid + IF pend_src_out.eop='1' THEN + nxt_state <= s_idle; -- output eop, so stop reading the FIFO + END IF; + END IF; + WHEN OTHERS => -- s_xon + -- Flush the fill FIFO when xon='0' + hold_src_in <= c_dp_siso_flush; + IF xon_reg='1' THEN + nxt_state <= s_idle; + END IF; + END CASE; + + -- Pass on frame level flow control + hold_src_in.xon <= src_in.xon; + END PROCESS; + END GENERATE; -- gen_rl_1 + + END GENERATE; -- gen_fill +END rtl;
astron_fifo/trunk/dp_fifo_fill_core.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/dp_fifo_fill_sc.vhd =================================================================== --- astron_fifo/trunk/dp_fifo_fill_sc.vhd (nonexistent) +++ astron_fifo/trunk/dp_fifo_fill_sc.vhd (revision 2) @@ -0,0 +1,121 @@ +-------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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: The FIFO output is available until the next eop only after it has +-- been filled with more than g_fifo_fill words. +-- Description: See dp_fifo_fill_core.vhd. + +LIBRARY IEEE, common_pkg_lib, dp_pkg_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_fifo_fill_sc IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_data_w : NATURAL := 16; + g_bsn_w : NATURAL := 1; + g_empty_w : NATURAL := 1; + g_channel_w : NATURAL := 1; + g_error_w : NATURAL := 1; + g_use_bsn : BOOLEAN := FALSE; + g_use_empty : BOOLEAN := FALSE; + g_use_channel : BOOLEAN := FALSE; + g_use_error : BOOLEAN := FALSE; + g_use_sync : BOOLEAN := FALSE; + g_use_complex : BOOLEAN := FALSE; -- TRUE feeds the concatenated complex fields (im & re) through the FIFO instead of the data field. + g_fifo_fill : NATURAL := 0; + g_fifo_size : NATURAL := 256; -- (32+2) * 256 = 1 M9K, g_data_w+2 for sop and eop + g_fifo_af_margin : NATURAL := 4; -- Nof words below max (full) at which fifo is considered almost full + g_fifo_rl : NATURAL := 1 -- use RL=0 for internal show ahead FIFO, default use RL=1 for internal normal FIFO + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + + -- Monitor FIFO filling + wr_ful : OUT STD_LOGIC; + usedw : OUT STD_LOGIC_VECTOR(ceil_log2(largest(g_fifo_size, g_fifo_fill + g_fifo_af_margin + 2))-1 DOWNTO 0); -- = ceil_log2(c_fifo_size)-1 DOWNTO 0 + rd_emp : OUT STD_LOGIC; + + -- MM control FIFO filling (assume 32 bit MM interface) + wr_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); -- = wr_usedw + rd_usedw_32b : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); -- = rd_usedw + rd_fill_32b : IN STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := TO_UVEC(g_fifo_fill, c_word_w); + + -- ST sink + snk_out : OUT t_dp_siso; + snk_in : IN t_dp_sosi; + -- ST source + src_in : IN t_dp_siso; + src_out : OUT t_dp_sosi + ); +END dp_fifo_fill_sc; + + +ARCHITECTURE str OF dp_fifo_fill_sc IS +BEGIN + + u_dp_fifo_fill_core : ENTITY work.dp_fifo_fill_core + GENERIC MAP ( + g_technology => g_technology, + g_use_dual_clock => FALSE, + g_data_w => g_data_w, + g_bsn_w => g_bsn_w, + g_empty_w => g_empty_w, + g_channel_w => g_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_channel, + g_use_error => g_use_error, + g_use_sync => g_use_sync, + g_use_complex => g_use_complex, + g_fifo_fill => g_fifo_fill, + g_fifo_size => g_fifo_size, + g_fifo_af_margin => g_fifo_af_margin, + g_fifo_rl => g_fifo_rl + ) + PORT MAP ( + wr_rst => rst, + wr_clk => clk, + rd_rst => rst, + rd_clk => clk, + -- Monitor FIFO filling + wr_ful => wr_ful, + wr_usedw => OPEN, + rd_usedw => usedw, + rd_emp => rd_emp, + -- MM control FIFO filling (assume 32 bit MM interface) + wr_usedw_32b => wr_usedw_32b, + rd_usedw_32b => rd_usedw_32b, + rd_fill_32b => rd_fill_32b, + -- ST sink + snk_out => snk_out, + snk_in => snk_in, + -- ST source + src_in => src_in, + src_out => src_out + ); + +END str;
astron_fifo/trunk/dp_fifo_fill_sc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/dp_fifo_sc.vhd =================================================================== --- astron_fifo/trunk/dp_fifo_sc.vhd (nonexistent) +++ astron_fifo/trunk/dp_fifo_sc.vhd (revision 2) @@ -0,0 +1,113 @@ +-------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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: DP FIFO for single clock (= sc) domain wr and rd. +-- Description: See dp_fifo_core.vhd. + +LIBRARY IEEE, common_pkg_lib, dp_pkg_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_fifo_sc IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_note_is_ful : BOOLEAN := TRUE; -- when TRUE report NOTE when FIFO goes full, fifo overflow is always reported as FAILURE + g_use_lut : BOOLEAN := FALSE; -- when TRUE then force using LUTs instead of block RAM + g_data_w : NATURAL := 16; -- Should be 2 times the c_complex_w if g_use_complex = TRUE + g_bsn_w : NATURAL := 1; + g_empty_w : NATURAL := 1; + g_channel_w : NATURAL := 1; + g_error_w : NATURAL := 1; + g_use_bsn : BOOLEAN := FALSE; + g_use_empty : BOOLEAN := FALSE; + g_use_channel : BOOLEAN := FALSE; + g_use_error : BOOLEAN := FALSE; + g_use_sync : BOOLEAN := FALSE; + g_use_ctrl : BOOLEAN := TRUE; -- sop & eop + g_use_complex : BOOLEAN := FALSE; -- TRUE feeds the concatenated complex fields (im & re) through the FIFO instead of the data field. + g_fifo_size : NATURAL := 512; -- (16+2) * 512 = 1 M9K, g_data_w+2 for sop and eop + g_fifo_af_margin : NATURAL := 4; -- >=4, Nof words below max (full) at which fifo is considered almost full + g_fifo_rl : NATURAL := 1 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + -- Monitor FIFO filling + wr_ful : OUT STD_LOGIC; + usedw : OUT STD_LOGIC_VECTOR(ceil_log2(g_fifo_size)-1 DOWNTO 0); + rd_emp : OUT STD_LOGIC; + -- ST sink + snk_out : OUT t_dp_siso; + snk_in : IN t_dp_sosi; + -- ST source + src_in : IN t_dp_siso; + src_out : OUT t_dp_sosi + ); +END dp_fifo_sc; + + +ARCHITECTURE str OF dp_fifo_sc IS +BEGIN + + u_dp_fifo_core : ENTITY work.dp_fifo_core + GENERIC MAP ( + g_technology => g_technology, + g_note_is_ful => g_note_is_ful, + g_use_dual_clock => FALSE, + g_use_lut_sc => g_use_lut, + g_data_w => g_data_w, + g_bsn_w => g_bsn_w, + g_empty_w => g_empty_w, + g_channel_w => g_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_channel, + g_use_error => g_use_error, + g_use_sync => g_use_sync, + g_use_ctrl => g_use_ctrl, + g_use_complex => g_use_complex, + g_fifo_size => g_fifo_size, + g_fifo_af_margin => g_fifo_af_margin, + g_fifo_rl => g_fifo_rl + ) + PORT MAP ( + wr_rst => rst, + wr_clk => clk, + rd_rst => rst, + rd_clk => clk, + -- Monitor FIFO filling + wr_ful => wr_ful, + wr_usedw => OPEN, + rd_usedw => usedw, + rd_emp => rd_emp, + -- ST sink + snk_out => snk_out, + snk_in => snk_in, + -- ST source + src_in => src_in, + src_out => src_out + ); + +END str;
astron_fifo/trunk/dp_fifo_sc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/hdllib.cfg =================================================================== --- astron_fifo/trunk/hdllib.cfg (nonexistent) +++ astron_fifo/trunk/hdllib.cfg (revision 2) @@ -0,0 +1,37 @@ +hdl_lib_name = tech_fifo +hdl_library_clause_name = tech_fifo_lib +hdl_lib_uses_synth = technology ip_stratixiv_fifo +hdl_lib_uses_sim = +hdl_lib_technology = +hdl_lib_disclose_library_clause_names = + ip_stratixiv_fifo ip_stratixiv_fifo_lib + +synth_files = + tech_fifo_component_pkg.vhd + tech_fifo_sc.vhd + tech_fifo_dc.vhd + tech_fifo_dc_mixed_widths.vhd + + common_fifo_sc.vhd + common_fifo_dc.vhd + common_rl_decrease.vhd + common_fifo_rd.vhd + + dp_fifo_core.vhd + dp_fifo_dc.vhd + dp_fifo_sc.vhd + dp_fifo_fill_core.vhd + dp_fifo_fill_sc.vhd + dp_fifo_fill.vhd + +test_bench_files = + tb_common_fifo_rd.vhd + +regression_test_vhdl = + # no self checking tb available yet + + +[modelsim_project_file] + + +[quartus_project_file]
astron_fifo/trunk/hdllib.cfg Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/tb_common_fifo_rd.vhd =================================================================== --- astron_fifo/trunk/tb_common_fifo_rd.vhd (nonexistent) +++ astron_fifo/trunk/tb_common_fifo_rd.vhd (revision 2) @@ -0,0 +1,102 @@ +------------------------------------------------------------------------------- +-- +-- 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.common_lfsr_sequences_pkg.ALL; +USE common_pkg_lib.tb_common_pkg.ALL; + + +ENTITY tb_common_fifo_rd IS + GENERIC ( + g_random_control : BOOLEAN := TRUE -- use TRUE for random rd_req control + ); +END tb_common_fifo_rd; + +-- Run -all, observe rd_dat in wave window + +ARCHITECTURE tb OF tb_common_fifo_rd IS + + CONSTANT clk_period : TIME := 10 ns; + CONSTANT c_dat_w : NATURAL := 16; + CONSTANT c_fifo_rl : NATURAL := 1; -- FIFO has RL = 1 + CONSTANT c_read_rl : NATURAL := 0; -- show ahead FIFO has RL = 0 + + SIGNAL rst : STD_LOGIC; + SIGNAL clk : STD_LOGIC := '0'; + SIGNAL tb_end : STD_LOGIC := '0'; + + SIGNAL fifo_req : STD_LOGIC; + SIGNAL fifo_dat : STD_LOGIC_VECTOR(c_dat_w-1 DOWNTO 0); + SIGNAL fifo_val : STD_LOGIC; + + SIGNAL rd_req : STD_LOGIC; + SIGNAL rd_dat : STD_LOGIC_VECTOR(c_dat_w-1 DOWNTO 0); + SIGNAL rd_val : STD_LOGIC; + + SIGNAL enable : STD_LOGIC := '1'; + SIGNAL random : STD_LOGIC_VECTOR(31 DOWNTO 0) := (OTHERS=>'0'); + SIGNAL verify_en : STD_LOGIC := '1'; + SIGNAL prev_rd_req : STD_LOGIC; + SIGNAL prev_rd_dat : STD_LOGIC_VECTOR(c_dat_w-1 DOWNTO 0); + +BEGIN + + rst <= '1', '0' AFTER clk_period*7; + clk <= NOT clk OR tb_end AFTER clk_period/2; + tb_end <= '0', '1' AFTER 20 us; + + verify_en <= '0', '1' AFTER clk_period*35; + + -- Model FIFO output with c_rl = 1 and counter data starting at 0 + proc_common_gen_data(c_fifo_rl, 0, rst, clk, enable, fifo_req, fifo_dat, fifo_val); + + -- Model rd_req + random <= func_common_random(random) WHEN rising_edge(clk); + rd_req <= random(random'HIGH) WHEN g_random_control=TRUE ELSE '1'; + + -- Verify dut output incrementing data + proc_common_verify_data(c_read_rl, clk, verify_en, rd_req, rd_val, rd_dat, prev_rd_dat); + + -- Verify dut output stream ready - valid relation, prev_rd_req is an auxiliary signal needed by the proc + proc_common_verify_valid(c_read_rl, clk, verify_en, rd_req, prev_rd_req, rd_val); + + + u_dut : ENTITY work.common_fifo_rd + GENERIC MAP ( + g_dat_w => c_dat_w + ) + PORT MAP ( + rst => rst, + clk => clk, + -- ST sink: RL = 1 + fifo_req => fifo_req, + fifo_dat => fifo_dat, + fifo_val => fifo_val, + -- ST source: RL = 0 + rd_req => rd_req, + rd_dat => rd_dat, + rd_val => rd_val + ); + +END tb;
astron_fifo/trunk/tb_common_fifo_rd.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/tech_fifo_component_pkg.vhd =================================================================== --- astron_fifo/trunk/tech_fifo_component_pkg.vhd (nonexistent) +++ astron_fifo/trunk/tech_fifo_component_pkg.vhd (revision 2) @@ -0,0 +1,291 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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: IP components declarations for various devices that get wrapped by the tech components + +LIBRARY IEEE, technology_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE technology_lib.technology_pkg.ALL; + +PACKAGE tech_fifo_component_pkg IS + + ----------------------------------------------------------------------------- + -- ip_stratixiv + ----------------------------------------------------------------------------- + + COMPONENT ip_stratixiv_fifo_sc IS + GENERIC ( + g_use_eab : STRING := "ON"; + g_dat_w : NATURAL; + g_nof_words : NATURAL + ); + PORT ( + aclr : IN STD_LOGIC; + clock : IN STD_LOGIC; + data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + rdreq : IN STD_LOGIC; + wrreq : IN STD_LOGIC; + empty : OUT STD_LOGIC; + full : OUT STD_LOGIC; + q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + usedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) + ); + END COMPONENT; + + COMPONENT ip_stratixiv_fifo_dc IS + GENERIC ( + g_dat_w : NATURAL; + g_nof_words : NATURAL + ); + PORT ( + aclr : IN STD_LOGIC := '0'; + data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + rdclk : IN STD_LOGIC; + rdreq : IN STD_LOGIC; + wrclk : IN STD_LOGIC; + wrreq : IN STD_LOGIC; + q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + rdempty : OUT STD_LOGIC; + rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0); + wrfull : OUT STD_LOGIC; + wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) + ); + END COMPONENT; + + COMPONENT ip_stratixiv_fifo_dc_mixed_widths IS + GENERIC ( + g_nof_words : NATURAL; -- FIFO size in nof wr_dat words + g_wrdat_w : NATURAL; + g_rddat_w : NATURAL + ); + PORT ( + aclr : IN STD_LOGIC := '0'; + data : IN STD_LOGIC_VECTOR (g_wrdat_w-1 DOWNTO 0); + rdclk : IN STD_LOGIC; + rdreq : IN STD_LOGIC; + wrclk : IN STD_LOGIC; + wrreq : IN STD_LOGIC; + q : OUT STD_LOGIC_VECTOR (g_rddat_w-1 DOWNTO 0); + rdempty : OUT STD_LOGIC; + rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words*g_wrdat_w/g_rddat_w)-1 DOWNTO 0); + wrfull : OUT STD_LOGIC; + wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) + ); + END COMPONENT; + + +-- ----------------------------------------------------------------------------- +-- -- ip_arria10 +-- ----------------------------------------------------------------------------- +-- +-- COMPONENT ip_arria10_fifo_sc IS +-- GENERIC ( +-- g_use_eab : STRING := "ON"; +-- g_dat_w : NATURAL := 20; +-- g_nof_words : NATURAL := 1024 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC ; +-- clock : IN STD_LOGIC ; +-- data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdreq : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- empty : OUT STD_LOGIC ; +-- full : OUT STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0) ; +-- usedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- COMPONENT ip_arria10_fifo_dc IS +-- GENERIC ( +-- g_use_eab : STRING := "ON"; +-- g_dat_w : NATURAL := 20; +-- g_nof_words : NATURAL := 1024 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC := '0'; +-- data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdclk : IN STD_LOGIC ; +-- rdreq : IN STD_LOGIC ; +-- wrclk : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdempty : OUT STD_LOGIC ; +-- rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0); +-- wrfull : OUT STD_LOGIC ; +-- wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- COMPONENT ip_arria10_fifo_dc_mixed_widths IS +-- GENERIC ( +-- g_nof_words : NATURAL := 1024; -- FIFO size in nof wr_dat words +-- g_wrdat_w : NATURAL := 20; +-- g_rddat_w : NATURAL := 10 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC := '0'; +-- data : IN STD_LOGIC_VECTOR (g_wrdat_w-1 DOWNTO 0); +-- rdclk : IN STD_LOGIC ; +-- rdreq : IN STD_LOGIC ; +-- wrclk : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_rddat_w-1 DOWNTO 0); +-- rdempty : OUT STD_LOGIC ; +-- rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words*g_wrdat_w/g_rddat_w)-1 DOWNTO 0); +-- wrfull : OUT STD_LOGIC ; +-- wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- ----------------------------------------------------------------------------- +-- -- ip_arria10_e3sge3 +-- ----------------------------------------------------------------------------- +-- +-- COMPONENT ip_arria10_e3sge3_fifo_sc IS +-- GENERIC ( +-- g_use_eab : STRING := "ON"; +-- g_dat_w : NATURAL := 20; +-- g_nof_words : NATURAL := 1024 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC ; +-- clock : IN STD_LOGIC ; +-- data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdreq : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- empty : OUT STD_LOGIC ; +-- full : OUT STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0) ; +-- usedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- COMPONENT ip_arria10_e3sge3_fifo_dc IS +-- GENERIC ( +-- g_use_eab : STRING := "ON"; +-- g_dat_w : NATURAL := 20; +-- g_nof_words : NATURAL := 1024 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC := '0'; +-- data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdclk : IN STD_LOGIC ; +-- rdreq : IN STD_LOGIC ; +-- wrclk : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdempty : OUT STD_LOGIC ; +-- rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0); +-- wrfull : OUT STD_LOGIC ; +-- wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- COMPONENT ip_arria10_e3sge3_fifo_dc_mixed_widths IS +-- GENERIC ( +-- g_nof_words : NATURAL := 1024; -- FIFO size in nof wr_dat words +-- g_wrdat_w : NATURAL := 20; +-- g_rddat_w : NATURAL := 10 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC := '0'; +-- data : IN STD_LOGIC_VECTOR (g_wrdat_w-1 DOWNTO 0); +-- rdclk : IN STD_LOGIC ; +-- rdreq : IN STD_LOGIC ; +-- wrclk : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_rddat_w-1 DOWNTO 0); +-- rdempty : OUT STD_LOGIC ; +-- rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words*g_wrdat_w/g_rddat_w)-1 DOWNTO 0); +-- wrfull : OUT STD_LOGIC ; +-- wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- ----------------------------------------------------------------------------- +-- -- ip_arria10_e1sg +-- ----------------------------------------------------------------------------- +-- +-- COMPONENT ip_arria10_e1sg_fifo_sc IS +-- GENERIC ( +-- g_use_eab : STRING := "ON"; +-- g_dat_w : NATURAL := 20; +-- g_nof_words : NATURAL := 1024 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC ; +-- clock : IN STD_LOGIC ; +-- data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdreq : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- empty : OUT STD_LOGIC ; +-- full : OUT STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0) ; +-- usedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- COMPONENT ip_arria10_e1sg_fifo_dc IS +-- GENERIC ( +-- g_use_eab : STRING := "ON"; +-- g_dat_w : NATURAL := 20; +-- g_nof_words : NATURAL := 1024 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC := '0'; +-- data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdclk : IN STD_LOGIC ; +-- rdreq : IN STD_LOGIC ; +-- wrclk : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); +-- rdempty : OUT STD_LOGIC ; +-- rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0); +-- wrfull : OUT STD_LOGIC ; +-- wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; +-- +-- COMPONENT ip_arria10_e1sg_fifo_dc_mixed_widths IS +-- GENERIC ( +-- g_nof_words : NATURAL := 1024; -- FIFO size in nof wr_dat words +-- g_wrdat_w : NATURAL := 20; +-- g_rddat_w : NATURAL := 10 +-- ); +-- PORT ( +-- aclr : IN STD_LOGIC := '0'; +-- data : IN STD_LOGIC_VECTOR (g_wrdat_w-1 DOWNTO 0); +-- rdclk : IN STD_LOGIC ; +-- rdreq : IN STD_LOGIC ; +-- wrclk : IN STD_LOGIC ; +-- wrreq : IN STD_LOGIC ; +-- q : OUT STD_LOGIC_VECTOR (g_rddat_w-1 DOWNTO 0); +-- rdempty : OUT STD_LOGIC ; +-- rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words*g_wrdat_w/g_rddat_w)-1 DOWNTO 0); +-- wrfull : OUT STD_LOGIC ; +-- wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) +-- ); +-- END COMPONENT; + + +END tech_fifo_component_pkg;
astron_fifo/trunk/tech_fifo_component_pkg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/tech_fifo_dc.vhd =================================================================== --- astron_fifo/trunk/tech_fifo_dc.vhd (nonexistent) +++ astron_fifo/trunk/tech_fifo_dc.vhd (revision 2) @@ -0,0 +1,85 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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, technology_lib; +USE ieee.std_logic_1164.all; +USE work.tech_fifo_component_pkg.ALL; +USE technology_lib.technology_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +-- Declare IP libraries to ensure default binding in simulation. The IP library clause is ignored by synthesis. +LIBRARY ip_stratixiv_fifo_lib; +--LIBRARY ip_arria10_fifo_lib; +--LIBRARY ip_arria10_e3sge3_fifo_lib; +--LIBRARY ip_arria10_e1sg_fifo_lib; + +ENTITY tech_fifo_dc IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_use_eab : STRING := "ON"; + g_dat_w : NATURAL; + g_nof_words : NATURAL + ); + PORT ( + aclr : IN STD_LOGIC := '0'; + data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + rdclk : IN STD_LOGIC; + rdreq : IN STD_LOGIC; + wrclk : IN STD_LOGIC; + wrreq : IN STD_LOGIC; + q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + rdempty : OUT STD_LOGIC; + rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0); + wrfull : OUT STD_LOGIC; + wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) + ); +END tech_fifo_dc; + + +ARCHITECTURE str OF tech_fifo_dc IS + +BEGIN + + gen_ip_stratixiv : IF g_technology=c_tech_stratixiv GENERATE + u0 : ip_stratixiv_fifo_dc + GENERIC MAP (g_dat_w, g_nof_words) + PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); + END GENERATE; + +-- gen_ip_arria10 : IF g_technology=c_tech_arria10 GENERATE +-- u0 : ip_arria10_fifo_dc +-- GENERIC MAP (g_use_eab, g_dat_w, g_nof_words) +-- PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); +-- END GENERATE; +-- +-- gen_ip_arria10_e3sge3 : IF g_technology=c_tech_arria10_e3sge3 GENERATE +-- u0 : ip_arria10_e3sge3_fifo_dc +-- GENERIC MAP (g_use_eab, g_dat_w, g_nof_words) +-- PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); +-- END GENERATE; +-- +-- gen_ip_arria10_e1sg : IF g_technology=c_tech_arria10_e1sg GENERATE +-- u0 : ip_arria10_e1sg_fifo_dc +-- GENERIC MAP (g_use_eab, g_dat_w, g_nof_words) +-- PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); +-- END GENERATE; + +END ARCHITECTURE;
astron_fifo/trunk/tech_fifo_dc.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/tech_fifo_dc_mixed_widths.vhd =================================================================== --- astron_fifo/trunk/tech_fifo_dc_mixed_widths.vhd (nonexistent) +++ astron_fifo/trunk/tech_fifo_dc_mixed_widths.vhd (revision 2) @@ -0,0 +1,85 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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, technology_lib; +USE ieee.std_logic_1164.all; +USE work.tech_fifo_component_pkg.ALL; +USE technology_lib.technology_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +-- Declare IP libraries to ensure default binding in simulation. The IP library clause is ignored by synthesis. +LIBRARY ip_stratixiv_fifo_lib; +--LIBRARY ip_arria10_fifo_lib; +--LIBRARY ip_arria10_e3sge3_fifo_lib; +--LIBRARY ip_arria10_e1sg_fifo_lib; + +ENTITY tech_fifo_dc_mixed_widths IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_nof_words : NATURAL; -- FIFO size in nof wr_dat words + g_wrdat_w : NATURAL; + g_rddat_w : NATURAL + ); + PORT ( + aclr : IN STD_LOGIC := '0'; + data : IN STD_LOGIC_VECTOR (g_wrdat_w-1 DOWNTO 0); + rdclk : IN STD_LOGIC; + rdreq : IN STD_LOGIC; + wrclk : IN STD_LOGIC; + wrreq : IN STD_LOGIC; + q : OUT STD_LOGIC_VECTOR (g_rddat_w-1 DOWNTO 0); + rdempty : OUT STD_LOGIC; + rdusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words*g_wrdat_w/g_rddat_w)-1 DOWNTO 0); + wrfull : OUT STD_LOGIC; + wrusedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) + ); +END tech_fifo_dc_mixed_widths; + + +ARCHITECTURE str OF tech_fifo_dc_mixed_widths IS + +BEGIN + + gen_ip_stratixiv : IF g_technology=c_tech_stratixiv GENERATE + u0 : ip_stratixiv_fifo_dc_mixed_widths + GENERIC MAP (g_nof_words, g_wrdat_w, g_rddat_w) + PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); + END GENERATE; + +-- gen_ip_arria10 : IF g_technology=c_tech_arria10 GENERATE +-- u0 : ip_arria10_fifo_dc_mixed_widths +-- GENERIC MAP (g_nof_words, g_wrdat_w, g_rddat_w) +-- PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); +-- END GENERATE; +-- +-- gen_ip_arria10_e3sge3 : IF g_technology=c_tech_arria10_e3sge3 GENERATE +-- u0 : ip_arria10_e3sge3_fifo_dc_mixed_widths +-- GENERIC MAP (g_nof_words, g_wrdat_w, g_rddat_w) +-- PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); +-- END GENERATE; +-- +-- gen_ip_arria10_e1sg : IF g_technology=c_tech_arria10_e1sg GENERATE +-- u0 : ip_arria10_e1sg_fifo_dc_mixed_widths +-- GENERIC MAP (g_nof_words, g_wrdat_w, g_rddat_w) +-- PORT MAP (aclr, data, rdclk, rdreq, wrclk, wrreq, q, rdempty, rdusedw, wrfull, wrusedw); +-- END GENERATE; + +END ARCHITECTURE;
astron_fifo/trunk/tech_fifo_dc_mixed_widths.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: astron_fifo/trunk/tech_fifo_sc.vhd =================================================================== --- astron_fifo/trunk/tech_fifo_sc.vhd (nonexistent) +++ astron_fifo/trunk/tech_fifo_sc.vhd (revision 2) @@ -0,0 +1,83 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2014 +-- 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, technology_lib; +USE ieee.std_logic_1164.all; +USE work.tech_fifo_component_pkg.ALL; +USE technology_lib.technology_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +-- Declare IP libraries to ensure default binding in simulation. The IP library clause is ignored by synthesis. +LIBRARY ip_stratixiv_fifo_lib; +--LIBRARY ip_arria10_fifo_lib; +--LIBRARY ip_arria10_e3sge3_fifo_lib; +--LIBRARY ip_arria10_e1sg_fifo_lib; + +ENTITY tech_fifo_sc IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_use_eab : STRING := "ON"; + g_dat_w : NATURAL; + g_nof_words : NATURAL + ); + PORT ( + aclr : IN STD_LOGIC; + clock : IN STD_LOGIC; + data : IN STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + rdreq : IN STD_LOGIC; + wrreq : IN STD_LOGIC; + empty : OUT STD_LOGIC; + full : OUT STD_LOGIC; + q : OUT STD_LOGIC_VECTOR (g_dat_w-1 DOWNTO 0); + usedw : OUT STD_LOGIC_VECTOR (tech_ceil_log2(g_nof_words)-1 DOWNTO 0) + ); +END tech_fifo_sc; + + +ARCHITECTURE str OF tech_fifo_sc IS + +BEGIN + + gen_ip_stratixiv : IF g_technology=c_tech_stratixiv GENERATE + u0 : ip_stratixiv_fifo_sc + GENERIC MAP (g_use_eab, g_dat_w, g_nof_words) + PORT MAP (aclr, clock, data, rdreq, wrreq, empty, full, q, usedw); + END GENERATE; + +-- gen_ip_arria10 : IF g_technology=c_tech_arria10 GENERATE +-- u0 : ip_arria10_fifo_sc +-- GENERIC MAP (g_use_eab, g_dat_w, g_nof_words) +-- PORT MAP (aclr, clock, data, rdreq, wrreq, empty, full, q, usedw); +-- END GENERATE; +-- +-- gen_ip_arria10_e3sge3 : IF g_technology=c_tech_arria10_e3sge3 GENERATE +-- u0 : ip_arria10_e3sge3_fifo_sc +-- GENERIC MAP (g_use_eab, g_dat_w, g_nof_words) +-- PORT MAP (aclr, clock, data, rdreq, wrreq, empty, full, q, usedw); +-- END GENERATE; +-- +-- gen_ip_arria10_e1sg : IF g_technology=c_tech_arria10_e1sg GENERATE +-- u0 : ip_arria10_e1sg_fifo_sc +-- GENERIC MAP (g_use_eab, g_dat_w, g_nof_words) +-- PORT MAP (aclr, clock, data, rdreq, wrreq, empty, full, q, usedw); +-- END GENERATE; + +END ARCHITECTURE;
astron_fifo/trunk/tech_fifo_sc.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.