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

Subversion Repositories astron_diagnostics

Compare Revisions

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

Rev 1 → Rev 2

/trunk/diag_block_gen.vhd
0,0 → 1,290
-------------------------------------------------------------------------------
--
-- Copyright (C) 2011
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
 
-- Purpose: Block generator repeating a data pattern
-- Description:
-- The data pattern is read via the buf_* MM interface. The output data
-- block is controlled via ctrl of type t_diag_block_gen with fields:
--
-- enable : sl -- block enable immediately
-- enable_sync : sl -- block enable at next en_sync pulse
-- samples_per_packet : slv -- number of valid per block, from sop to eop
-- blocks_per_sync : slv -- number of blocks per sync interval
-- gapsize : slv -- number of clk cycles between blocks, so
-- between last eop and next sop
-- mem_low_adrs : slv -- block start address at MM interface
-- mem_high_adrs : slv -- end address at MM interface
-- bsn_init : slv -- BSN of first output block
--
-- The MM reading starts at mem_low_adrs when the BG is first enabled. If
-- the mem_high_adrs-mem_low_adrs+1 < samples_per_packet then the reading
-- wraps and continues from mem_low_adrs. For every new block the reading
-- continues where it left in the previous block. This MM reading scheme
-- allows using a periodic data pattern that can extends accross blocks and
-- sync intervals, because is continues for as long as the BG remains
-- enabled.
--
-- The input en_sync can be used as trigger to start multiple BG at the same
-- clk cycle. The BG creates a out_sosi.sync at the first sop and the sop of
-- every blocks_per_sync.
--
-- The current block is finished properly after enable gows low, to ensure
-- that all blocks have the same length. A new ctrl is accepted after a
-- current block has finished, to ensure that no fractional blocks will
-- enter the stream.
--
-- The BG supports block flow control via out_siso.xon. The BG also supports
-- sample flow control via out_siso.ready.
--
-- The read data is resized and output as unsigned via:
-- . out_sosi.data(g_buf_dat_w-1:0).
-- The read data is also output as complex data via:
-- . out_sosi.im(g_buf_dat_w -1:g_buf_dat_w/2)
-- . out_sosi.re(g_buf_dat_w/2-1: 0)
 
library IEEE, common_pkg_lib, dp_pkg_lib;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.NUMERIC_STD.ALL;
use common_pkg_lib.common_pkg.ALL;
use work.diag_pkg.ALL;
use dp_pkg_lib.dp_stream_pkg.ALL;
 
entity diag_block_gen is
generic (
g_blk_sync : boolean := false; -- when true use active sync during entire block, else use single clock cycle sync pulse
g_buf_dat_w : natural := 32;
g_buf_addr_w : natural := 7
);
port (
rst : in std_logic;
clk : in std_logic;
buf_addr : out std_logic_vector(g_buf_addr_w-1 downto 0);
buf_rden : out std_logic;
buf_rddat : in std_logic_vector(g_buf_dat_w-1 downto 0);
buf_rdval : in std_logic;
ctrl : in t_diag_block_gen;
en_sync : in std_logic := '1';
out_siso : in t_dp_siso := c_dp_siso_rdy;
out_sosi : out t_dp_sosi
);
end diag_block_gen;
architecture rtl of diag_block_gen is
 
type state_type is (s_idle, s_block, s_gap);
 
type reg_type is record
ctrl_reg : t_diag_block_gen; -- capture ctrl
blk_en : std_logic; -- enable at block level
blk_xon : std_logic; -- siso.xon at block level, the BG continues but the sosi control depend on xon (the BG does not support siso.ready)
blk_sync : std_logic; -- block sync alternative of the pulse sync
pls_sync : std_logic; -- pulse sync
valid : std_logic;
sop : std_logic;
eop : std_logic;
rd_ena : std_logic;
samples_cnt : natural range 0 to 2**c_diag_bg_samples_per_packet_w-1;
blocks_cnt : natural range 0 to 2**c_diag_bg_blocks_per_sync_w-1;
bsn_cnt : std_logic_vector(c_diag_bg_bsn_init_w-1 downto 0); -- = c_dp_stream_bsn_w
mem_cnt : natural range 0 to 2**g_buf_addr_w-1;
state : state_type; -- The state machine.
end record;
 
signal r, rin : reg_type;
signal out_sosi_i : t_dp_sosi := c_dp_sosi_rst; -- Signal used to assign reset values to output
begin
p_comb : process(r, rst, ctrl, en_sync, out_siso)
variable v : reg_type;
variable v_samples_per_packet : natural;
variable v_gapsize : natural;
variable v_blocks_per_sync : natural;
variable v_mem_low_adrs : natural;
variable v_mem_high_adrs : natural;
begin
v_samples_per_packet := TO_UINT(r.ctrl_reg.samples_per_packet);
v_gapsize := TO_UINT(r.ctrl_reg.gapsize);
v_blocks_per_sync := TO_UINT(r.ctrl_reg.blocks_per_sync);
v_mem_low_adrs := TO_UINT(r.ctrl_reg.mem_low_adrs);
v_mem_high_adrs := TO_UINT(r.ctrl_reg.mem_high_adrs);
v := r; -- default hold all r fields
v.pls_sync := '0';
v.valid := '0';
v.sop := '0';
v.eop := '0';
v.rd_ena := '0';
-- Control block generator enable
if ctrl.enable='0' then
v.blk_en := '0'; -- disable immediately
elsif ctrl.enable_sync='0' then
v.blk_en := '1'; -- enable immediately or keep enabled
elsif en_sync='1' then
v.blk_en := '1'; -- enable at input sync pulse or keep enabled
end if;
-- The pulse sync is high at the sop of the first block, the block sync is high during the entire block until the eop
if r.eop='1' then
v.blk_sync := '0';
end if;
-- Increment the block sequence number counter after each block
if r.eop='1' then
v.bsn_cnt := incr_uvec(r.bsn_cnt, 1);
end if;
case r.state is
when s_idle =>
v.ctrl_reg := ctrl; -- accept new control settings
v.blk_xon := out_siso.xon;
v.blk_sync := '0';
v.samples_cnt := 0;
v.blocks_cnt := 0;
v.bsn_cnt := ctrl.bsn_init;
v.mem_cnt := v_mem_low_adrs;
if r.blk_en = '1' then -- Wait until enabled
if out_siso.xon='1' then -- Wait until XON is 1
v.rd_ena := '1';
v.state := s_block;
end if;
end if;
when s_block =>
if out_siso.ready='1' then
v.rd_ena := '1'; -- read next data
if r.samples_cnt = 0 and r.blocks_cnt = 0 then
v.pls_sync := '1'; -- Always start with a pulse sync
v.blk_sync := '1';
v.sop := '1';
v.samples_cnt := v.samples_cnt + 1;
elsif r.samples_cnt = 0 then
v.sop := '1';
v.samples_cnt := v.samples_cnt + 1;
elsif r.samples_cnt >= v_samples_per_packet-1 and v_gapsize = 0 and r.blocks_cnt >= v_blocks_per_sync-1 then
v.eop := '1';
v.ctrl_reg := ctrl; -- accept new control settings at end of block when gapsize=0
v.samples_cnt := 0;
v.blocks_cnt := 0;
elsif r.samples_cnt >= v_samples_per_packet-1 and v_gapsize = 0 then
v.eop := '1';
v.ctrl_reg := ctrl; -- accept new control settings at end of block when gapsize=0
v.samples_cnt := 0;
v.blocks_cnt := r.blocks_cnt + 1;
elsif r.samples_cnt >= v_samples_per_packet-1 then
v.eop := '1';
v.samples_cnt := 0;
v.rd_ena := '0';
v.state := s_gap;
else
v.samples_cnt := r.samples_cnt + 1;
end if;
v.valid := '1'; -- output pending data
if r.mem_cnt >= v_mem_high_adrs then
v.mem_cnt := v_mem_low_adrs;
else
v.mem_cnt := r.mem_cnt + 1;
end if;
if v.eop = '1' and r.blk_en = '0' then
v.state := s_idle; -- accept disable after eop, not during block
end if;
if r.eop = '1' then
v.blk_xon := out_siso.xon; -- accept XOFF after eop, not during block
end if;
end if; -- out_siso.ready='1'
 
when s_gap =>
if r.samples_cnt >= v_gapsize-1 and r.blocks_cnt >= v_blocks_per_sync-1 then
v.ctrl_reg := ctrl; -- accept new control settings at end of gap
v.samples_cnt := 0;
v.blocks_cnt := 0;
v.rd_ena := '1';
v.state := s_block;
elsif r.samples_cnt >= v_gapsize-1 then
v.ctrl_reg := ctrl; -- accept new control settings at end of gap
v.samples_cnt := 0;
v.blocks_cnt := r.blocks_cnt + 1;
v.rd_ena := '1';
v.state := s_block;
else
v.samples_cnt := r.samples_cnt + 1;
end if;
if r.blk_en = '0' then
v.state := s_idle;
end if;
v.blk_xon := out_siso.xon;
when others =>
v.state := s_idle;
 
end case;
if rst = '1' then
v.ctrl_reg := c_diag_block_gen_rst;
v.blk_en := '0';
v.blk_xon := '0';
v.blk_sync := '0';
v.pls_sync := '0';
v.valid := '0';
v.sop := '0';
v.eop := '0';
v.rd_ena := '0';
v.samples_cnt := 0;
v.blocks_cnt := 0;
v.bsn_cnt := (others=>'0');
v.mem_cnt := 0;
v.state := s_idle;
end if;
 
rin <= v;
end process;
p_regs : process(rst, clk)
begin
if rising_edge(clk) then
r <= rin;
end if;
end process;
-- Connect to the outside world
out_sosi_i.sop <= r.sop and r.blk_xon;
out_sosi_i.eop <= r.eop and r.blk_xon;
out_sosi_i.sync <= r.pls_sync and r.blk_xon when g_blk_sync=false else r.blk_sync and r.blk_xon;
out_sosi_i.valid <= r.valid and r.blk_xon;
out_sosi_i.bsn <= r.bsn_cnt;
out_sosi_i.re <= RESIZE_DP_DSP_DATA(buf_rddat(g_buf_dat_w/2-1 downto 0)); -- treat as signed
out_sosi_i.im <= RESIZE_DP_DSP_DATA(buf_rddat(g_buf_dat_w-1 downto g_buf_dat_w/2)); -- treat as signed
out_sosi_i.data <= RESIZE_DP_DATA( buf_rddat(g_buf_dat_w-1 downto 0)); -- treat as unsigned
out_sosi <= out_sosi_i;
buf_addr <= TO_UVEC(r.mem_cnt, g_buf_addr_w);
buf_rden <= r.rd_ena;
end rtl;
trunk/diag_block_gen.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/diag_block_gen_reg.vhd =================================================================== --- trunk/diag_block_gen_reg.vhd (nonexistent) +++ trunk/diag_block_gen_reg.vhd (revision 2) @@ -0,0 +1,166 @@ +----------------------------------------------------------------------------- +-- +-- 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 . +-- +------------------------------------------------------------------------------- + + +library IEEE, common_pkg_lib, common_ram_lib, common_components_lib; +use IEEE.std_logic_1164.ALL; +use IEEE.numeric_std.ALL; +use common_pkg_lib.common_pkg.ALL; +use common_ram_lib.common_ram_pkg.ALL; +use work.diag_pkg.ALL; + +entity diag_block_gen_reg is + generic ( + g_cross_clock_domain : boolean := TRUE; -- use FALSE when mm_clk and st_clk are the same, else use TRUE to cross the clock domain + g_diag_block_gen_rst : t_diag_block_gen := c_diag_block_gen_rst + ); + port ( + mm_rst : in std_logic; -- Clocks and reset + mm_clk : in std_logic; + dp_rst : in std_logic := '0'; + dp_clk : in std_logic; + mm_mosi : in t_mem_mosi; -- Memory Mapped Slave in mm_clk domain + mm_miso : out t_mem_miso := c_mem_miso_rst; + bg_ctrl : out t_diag_block_gen := g_diag_block_gen_rst + ); +end diag_block_gen_reg; + +architecture rtl of diag_block_gen_reg is + + constant c_adrs_width : positive := c_diag_bg_reg_adr_w; + signal mm_bg_ctrl : t_diag_block_gen := g_diag_block_gen_rst; + signal dp_bg_ctrl : t_diag_block_gen := g_diag_block_gen_rst; + +begin + + ------------------------------------------------------------------------------ + -- MM register access in the mm_clk domain + -- . Hardcode the shared MM slave register directly in RTL instead of using + -- the common_reg_r_w instance. Directly using RTL is easier when the large + -- MM register has multiple different fields and with different read and + -- write options per field in one MM register. + ------------------------------------------------------------------------------ + + p_mm_reg : process (mm_rst, mm_clk) + begin + if(mm_rst = '1') then + mm_miso <= c_mem_miso_rst; + mm_bg_ctrl <= g_diag_block_gen_rst; + elsif(rising_edge(mm_clk)) then + -- Read access defaults + mm_miso.rdval <= '0'; + -- Write access: set register value + if(mm_mosi.wr = '1') then + case TO_UINT(mm_mosi.address(c_adrs_width-1 downto 0)) is + when 0 => + mm_bg_ctrl.enable <= mm_mosi.wrdata(0); + mm_bg_ctrl.enable_sync <= mm_mosi.wrdata(1); + when 1 => + mm_bg_ctrl.samples_per_packet <= mm_mosi.wrdata(c_diag_bg_samples_per_packet_w -1 downto 0); + when 2 => + mm_bg_ctrl.blocks_per_sync <= mm_mosi.wrdata(c_diag_bg_blocks_per_sync_w -1 downto 0); + when 3 => + mm_bg_ctrl.gapsize <= mm_mosi.wrdata(c_diag_bg_gapsize_w -1 downto 0); + when 4 => + mm_bg_ctrl.mem_low_adrs <= mm_mosi.wrdata(c_diag_bg_mem_low_adrs_w -1 downto 0); + when 5 => + mm_bg_ctrl.mem_high_adrs <= mm_mosi.wrdata(c_diag_bg_mem_high_adrs_w -1 downto 0); + when 6 => + mm_bg_ctrl.bsn_init(31 downto 0) <= mm_mosi.wrdata(31 downto 0); + when 7 => + mm_bg_ctrl.bsn_init(63 downto 32) <= mm_mosi.wrdata(31 downto 0); + when others => null; -- not used MM addresses + end case; + -- Read access: get register value + elsif mm_mosi.rd = '1' then + mm_miso <= c_mem_miso_rst; -- set unused rddata bits to '0' when read + mm_miso.rdval <= '1'; + case TO_UINT(mm_mosi.address(c_adrs_width-1 downto 0)) is + -- Read Block Sync + when 0 => + mm_miso.rddata(0) <= mm_bg_ctrl.enable; + mm_miso.rddata(1) <= mm_bg_ctrl.enable_sync; + when 1 => + mm_miso.rddata(c_diag_bg_samples_per_packet_w -1 downto 0) <= mm_bg_ctrl.samples_per_packet; + when 2 => + mm_miso.rddata(c_diag_bg_blocks_per_sync_w -1 downto 0) <= mm_bg_ctrl.blocks_per_sync; + when 3 => + mm_miso.rddata(c_diag_bg_gapsize_w -1 downto 0) <= mm_bg_ctrl.gapsize; + when 4 => + mm_miso.rddata(c_diag_bg_mem_low_adrs_w -1 downto 0) <= mm_bg_ctrl.mem_low_adrs; + when 5 => + mm_miso.rddata(c_diag_bg_mem_high_adrs_w -1 downto 0) <= mm_bg_ctrl.mem_high_adrs; + when 6 => + mm_miso.rddata(31 downto 0) <= mm_bg_ctrl.bsn_init(31 downto 0); + when 7 => + mm_miso.rddata(31 downto 0) <= mm_bg_ctrl.bsn_init(63 downto 32); + when others => null; -- not used MM addresses + end case; + end if; + end if; + end process; + + ------------------------------------------------------------------------------ + -- Transfer register value between mm_clk and dp_clk domain. + -- If the function of the register ensures that the value will not be used + -- immediately when it was set, then the transfer between the clock domains + -- can be done by wires only. Otherwise if the change in register value can + -- have an immediate effect then the bit or word value needs to be transfered + -- using: + -- + -- . common_async --> for single-bit level signal + -- . common_spulse --> for single-bit pulse signal + -- . common_reg_cross_domain --> for a multi-bit (a word) signal + -- + -- Typically always use a crossing component for the single bit signals (to + -- be on the save side) and only use a crossing component for the word + -- signals if it is necessary (to avoid using more logic than necessary). + ------------------------------------------------------------------------------ + + no_cross : if g_cross_clock_domain = FALSE generate + dp_bg_ctrl <= mm_bg_ctrl; + end generate; -- no_cross + + gen_crossing : if g_cross_clock_domain = TRUE generate + -- Assume diag BG enable gets written last, so when diag BG enable is transfered properly to the dp_clk domain, then + -- the other diag BG control fields are stable as well + u_bg_enable : entity common_components_lib.common_async + generic map ( + g_rst_level => '0' + ) + port map ( + rst => dp_rst, + clk => dp_clk, + din => mm_bg_ctrl.enable, + dout => dp_bg_ctrl.enable + ); + dp_bg_ctrl.enable_sync <= mm_bg_ctrl.enable_sync; + dp_bg_ctrl.samples_per_packet <= mm_bg_ctrl.samples_per_packet; + dp_bg_ctrl.blocks_per_sync <= mm_bg_ctrl.blocks_per_sync; + dp_bg_ctrl.gapsize <= mm_bg_ctrl.gapsize; + dp_bg_ctrl.mem_low_adrs <= mm_bg_ctrl.mem_low_adrs; + dp_bg_ctrl.mem_high_adrs <= mm_bg_ctrl.mem_high_adrs; + dp_bg_ctrl.bsn_init <= mm_bg_ctrl.bsn_init; + end generate; -- gen_crossing + + bg_ctrl <= dp_bg_ctrl; + +end rtl;
trunk/diag_block_gen_reg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/diag_data_buffer.vhd =================================================================== --- trunk/diag_data_buffer.vhd (nonexistent) +++ trunk/diag_data_buffer.vhd (revision 2) @@ -0,0 +1,266 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2011 +-- 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 : Capture a block of streaming data for analysis via MM access +-- Description : +-- The first g_nof_data valid streaming data input words are stored in the +-- data buffer. Then they can be read via the MM interface. Dependent on +-- g_use_in_sync the nxt block of valid streaming data input words gets +-- stored when a new in_sync occurs or when the last word was read from via +-- the MM interface. +-- Remarks: +-- . The actual RAM usage depends on g_data_w. Unused bits are forced to '0' +-- when read. +-- . The c_mm_factor must be a power of 2 factor. Typically c_mm_factor=1 is +-- sufficient for most purposes. If the application only requires +-- eg. c_mm_factor=3 then it needs to extend the data to c_mm_factor=4. +-- . If c_mm_factor=2 then in_data[g_data_w/2-1:0] will appear at MM address +-- even and in_data[g_data_w-1:g_data_w/2] at address odd. +-- The advantage of splitting at g_data_w/2 instead of at c_word_w=32 is +-- that streaming 36b data can then map on 18b RAM still fit in a single +-- RAM block. Whereas mapping the LS 32b part at even address and the MS 4b +-- part at odd address would require using c_word_w=32b RAM that could +-- require two RAM blocks. For g_data_w=2*c_word_w=64b there is no +-- difference between these 2 schemes. Hence by rising the g_data_w to a +-- power of 2 multiple of 32b the user can enforce using splitting the data +-- a c_word_w parts. + +LIBRARY IEEE, common_pkg_lib, mm_lib, technology_lib, common_ram_lib, common_counter_lib, common_components_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE work.diag_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +ENTITY diag_data_buffer IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + g_data_w : NATURAL := 32; + g_nof_data : NATURAL := 1024; + g_use_in_sync : BOOLEAN := FALSE -- when TRUE start filling the buffer at the in_sync, else after the last word was read + ); + PORT ( + -- Memory-mapped clock domain + mm_rst : IN STD_LOGIC; + mm_clk : IN STD_LOGIC; + + ram_mm_mosi : IN t_mem_mosi; -- read and overwrite access to the data buffer + ram_mm_miso : OUT t_mem_miso; + + reg_mm_mosi : IN t_mem_mosi := c_mem_mosi_rst; + reg_mm_miso : OUT t_mem_miso; + + -- Streaming clock domain + st_rst : IN STD_LOGIC; + st_clk : IN STD_LOGIC; + + in_data : IN STD_LOGIC_VECTOR(g_data_w-1 DOWNTO 0); + in_sync : IN STD_LOGIC := '0'; + in_val : IN STD_LOGIC + ); +END diag_data_buffer; + + +ARCHITECTURE rtl OF diag_data_buffer IS + + CONSTANT c_mm_factor : NATURAL := ceil_div(g_data_w, c_word_w); -- must be a power of 2 multiple + + CONSTANT c_nof_data_mm : NATURAL := g_nof_data*c_mm_factor; + CONSTANT g_data_mm_w : NATURAL := g_data_w/c_mm_factor; + + CONSTANT c_buf_mm : t_c_mem := (latency => 1, + adr_w => ceil_log2(c_nof_data_mm), + dat_w => g_data_mm_w, + nof_dat => c_nof_data_mm, + init_sl => '0'); + + CONSTANT c_buf_st : t_c_mem := (latency => 1, + adr_w => ceil_log2(g_nof_data), + dat_w => g_data_w, + nof_dat => g_nof_data, + init_sl => '0'); + + CONSTANT c_reg : t_c_mem := (latency => 1, + adr_w => c_diag_db_reg_adr_w, + dat_w => c_word_w, -- Use MM bus data width = c_word_w = 32 for all MM registers + nof_dat => c_diag_db_reg_nof_dat, -- 1: word_cnt; 0:sync_cnt + init_sl => '0'); + + SIGNAL i_ram_mm_miso : t_mem_miso := c_mem_miso_rst; -- used to avoid vsim-8684 error "No drivers exist" for the unused fields + + SIGNAL rd_last : STD_LOGIC; + SIGNAL wr_sync : STD_LOGIC; + + SIGNAL wr_done : STD_LOGIC; + SIGNAL nxt_wr_done : STD_LOGIC; + + SIGNAL wr_data : STD_LOGIC_VECTOR(c_buf_st.dat_w-1 DOWNTO 0); + SIGNAL nxt_wr_data : STD_LOGIC_VECTOR(c_buf_st.dat_w-1 DOWNTO 0); + SIGNAL wr_addr : STD_LOGIC_VECTOR(c_buf_st.adr_w-1 DOWNTO 0); + SIGNAL nxt_wr_addr : STD_LOGIC_VECTOR(c_buf_st.adr_w-1 DOWNTO 0); + SIGNAL wr_en : STD_LOGIC; + SIGNAL nxt_wr_en : STD_LOGIC; + + SIGNAL reg_rd_arr : STD_LOGIC_VECTOR(c_reg.nof_dat-1 DOWNTO 0); + SIGNAL reg_slv : STD_LOGIC_VECTOR(c_reg.nof_dat*c_word_w-1 DOWNTO 0); + + SIGNAL sync_cnt_clr : STD_LOGIC := '0'; + SIGNAL sync_cnt : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); -- Nof times buffer has been written + SIGNAL word_cnt : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0) := (OTHERS=>'0'); + +BEGIN + + ASSERT c_mm_factor=2**true_log2(c_mm_factor) REPORT "Only support mixed width data that uses a power of 2 multiple." SEVERITY FAILURE; + + ram_mm_miso <= i_ram_mm_miso; + + rd_last <= '1' WHEN UNSIGNED(ram_mm_mosi.address(c_buf_mm.adr_w-1 DOWNTO 0))=c_nof_data_mm-1 AND ram_mm_mosi.rd='1' ELSE '0'; + + -- Determine the write trigger + use_rd_last : IF g_use_in_sync=FALSE GENERATE + u_wr_sync : ENTITY common_components_lib.common_spulse + GENERIC MAP ( + g_delay_len => c_meta_delay_len + ) + PORT MAP ( + in_rst => mm_rst, + in_clk => mm_clk, + in_pulse => rd_last, + out_rst => st_rst, + out_clk => st_clk, + out_pulse => wr_sync + ); + END GENERATE; + + use_in_sync : IF g_use_in_sync=TRUE GENERATE + sync_cnt_clr <= rd_last; -- clear sync_cnt register on read of last data + wr_sync <= in_sync; + END GENERATE; + + p_st_clk : PROCESS (st_clk, st_rst) + BEGIN + IF st_rst='1' THEN + wr_data <= (OTHERS => '0'); + wr_addr <= (OTHERS => '0'); + wr_en <= '0'; + wr_done <= '0'; + ELSIF rising_edge(st_clk) THEN + wr_data <= nxt_wr_data; + wr_addr <= nxt_wr_addr; + wr_en <= nxt_wr_en; + wr_done <= nxt_wr_done; + END IF; + END PROCESS; + + -- Write access control + nxt_wr_data <= in_data; + nxt_wr_en <= in_val AND NOT nxt_wr_done; + + p_wr_addr : PROCESS (wr_done, wr_addr, wr_sync, wr_en) + BEGIN + nxt_wr_done <= wr_done; + nxt_wr_addr <= wr_addr; + IF wr_sync='1' THEN + nxt_wr_done <= '0'; + nxt_wr_addr <= (OTHERS => '0'); + ELSIF wr_en='1' THEN + IF UNSIGNED(wr_addr)=g_nof_data-1 THEN + nxt_wr_done <= '1'; -- keep wr_addr, do not allow wr_addr increment >= g_nof_data to avoid RAM address out-of-bound warning in Modelsim in case c_buf.nof_dat < 2**c_buf.adr_w + ELSE + nxt_wr_addr <= INCR_UVEC(wr_addr, 1); + END IF; + END IF; + END PROCESS; + + u_buf : ENTITY common_ram_lib.common_ram_crw_crw_ratio + GENERIC MAP ( + g_technology => g_technology, + g_ram_a => c_buf_mm, + g_ram_b => c_buf_st, + g_init_file => "UNUSED" + ) + PORT MAP ( + -- MM read/write port clock domain + rst_a => mm_rst, + clk_a => mm_clk, + wr_en_a => ram_mm_mosi.wr, + wr_dat_a => ram_mm_mosi.wrdata(c_buf_mm.dat_w-1 DOWNTO 0), + adr_a => ram_mm_mosi.address(c_buf_mm.adr_w-1 DOWNTO 0), + rd_en_a => ram_mm_mosi.rd, + rd_dat_a => i_ram_mm_miso.rddata(c_buf_mm.dat_w-1 DOWNTO 0), + rd_val_a => i_ram_mm_miso.rdval, + + -- ST write only port clock domain + rst_b => st_rst, + clk_b => st_clk, + wr_en_b => wr_en, + wr_dat_b => wr_data, + adr_b => wr_addr, + rd_en_b => '0', + rd_dat_b => OPEN, + rd_val_b => OPEN + ); + + u_reg : ENTITY mm_lib.common_reg_r_w_dc + GENERIC MAP ( + g_reg => c_reg + ) + PORT MAP ( + -- Clocks and reset + mm_rst => mm_rst, + mm_clk => mm_clk, + st_rst => st_rst, + st_clk => st_clk, + + -- Memory Mapped Slave in mm_clk domain + sla_in => reg_mm_mosi, + sla_out => reg_mm_miso, + + -- MM registers in st_clk domain + reg_wr_arr => OPEN, + reg_rd_arr => reg_rd_arr, + in_reg => reg_slv, + out_reg => OPEN + ); + + reg_slv <= word_cnt & sync_cnt; + + u_word_cnt : ENTITY common_counter_lib.common_counter + PORT MAP ( + rst => st_rst, + clk => st_clk, + cnt_en => wr_en, + cnt_clr => wr_sync, + count => word_cnt + ); + + u_sync_cnt : ENTITY common_counter_lib.common_counter + PORT MAP ( + rst => st_rst, + clk => st_clk, + cnt_en => wr_sync, + cnt_clr => sync_cnt_clr, + count => sync_cnt + ); + +END rtl; +
trunk/diag_data_buffer.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/diag_pkg.vhd =================================================================== --- trunk/diag_pkg.vhd (nonexistent) +++ trunk/diag_pkg.vhd (revision 2) @@ -0,0 +1,213 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2011 +-- 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.MATH_REAL.ALL; +USE common_pkg_lib.common_pkg.ALL; + +PACKAGE diag_pkg IS + + ----------------------------------------------------------------------------- + -- PHY interface tests (e.g. for ethernet, transceivers, lvds, memory) + ----------------------------------------------------------------------------- + + CONSTANT c_diag_test_mode_no_tst : NATURAL := 0; -- no test, the PHY interface runs in normal user mode + CONSTANT c_diag_test_mode_loop_local : NATURAL := 1; -- loop back via PHY chip + CONSTANT c_diag_test_mode_loop_remote : NATURAL := 2; -- loop back via loopback cable or plug in the connector + CONSTANT c_diag_test_mode_tx : NATURAL := 4; -- transmit only + CONSTANT c_diag_test_mode_rx : NATURAL := 5; -- receive only + CONSTANT c_diag_test_mode_tx_rx : NATURAL := 6; -- transmit and receive + + CONSTANT c_diag_test_data_lfsr : NATURAL := 0; -- use pseudo random data + CONSTANT c_diag_test_data_incr : NATURAL := 1; -- use incrementing counter data + + CONSTANT c_diag_test_duration_quick : NATURAL := 0; -- end Rx test after 1 data frame or word, end Tx test after correspondingly sufficient data frames or words transmitted, or all memory lines + CONSTANT c_diag_test_duration_normal : NATURAL := 1; -- idem for e.g. 100 data frames or words, or full memory + CONSTANT c_diag_test_duration_extra : NATURAL := 2; -- idem for e.g. 100000 data frames or words + + CONSTANT c_diag_test_result_ok : NATURAL := 0; -- test went OK + CONSTANT c_diag_test_result_none : NATURAL := 1; -- test did not run, default + CONSTANT c_diag_test_result_timeout : NATURAL := 2; -- test started but no valid data was received + CONSTANT c_diag_test_result_error : NATURAL := 3; -- test received valid data, but the value was wrong for one or more + CONSTANT c_diag_test_result_illegal : NATURAL := 4; -- exception, condition that can not occur in the logic + + + ----------------------------------------------------------------------------- + -- Waveform Generator + ----------------------------------------------------------------------------- + + -- control register + CONSTANT c_diag_wg_mode_w : NATURAL := 8; + CONSTANT c_diag_wg_nofsamples_w : NATURAL := 16; -- >~ minimum data path block size + CONSTANT c_diag_wg_phase_w : NATURAL := 16; -- = c_diag_wg_nofsamples_w + CONSTANT c_diag_wg_freq_w : NATURAL := 31; -- >> c_diag_wg_nofsamples_w, determines the minimum frequency = Fs / 2**c_diag_wg_freq_w + CONSTANT c_diag_wg_ampl_w : NATURAL := 17; -- Typically fit DSP multiply 18x18 element so use <= 17, to fit unsigned in 18 bit signed, + -- = waveform data width-1 (sign bit) to be able to make a 1 LSBit amplitude sinus + + CONSTANT c_diag_wg_mode_off : NATURAL := 0; + CONSTANT c_diag_wg_mode_calc : NATURAL := 1; + CONSTANT c_diag_wg_mode_repeat : NATURAL := 2; + CONSTANT c_diag_wg_mode_single : NATURAL := 3; + + TYPE t_diag_wg IS RECORD + mode : STD_LOGIC_VECTOR(c_diag_wg_mode_w -1 DOWNTO 0); + nof_samples : STD_LOGIC_VECTOR(c_diag_wg_nofsamples_w -1 DOWNTO 0); -- unsigned value + phase : STD_LOGIC_VECTOR(c_diag_wg_phase_w -1 DOWNTO 0); -- unsigned value + freq : STD_LOGIC_VECTOR(c_diag_wg_freq_w -1 DOWNTO 0); -- unsigned value + ampl : STD_LOGIC_VECTOR(c_diag_wg_ampl_w -1 DOWNTO 0); -- unsigned value, range [0:2**c_diag_wg_ampl_w> normalized to range [0 c_diag_wg_gain> + END RECORD; + + CONSTANT c_diag_wg_ampl_norm : REAL := 1.0; -- Use this default amplitude norm = 1.0 when WG data width = WG waveform buffer data width, + -- else use extra amplitude unit scaling by (WG data max)/(WG data max + 1) + CONSTANT c_diag_wg_gain_w : NATURAL := 1; -- Normalized range [0 1> maps to fixed point range [0:2**c_diag_wg_ampl_w> + -- . use gain 2**0 = 1 to have fulle scale without clipping + -- . use gain 2**g_calc_gain_w > 1 to cause clipping + CONSTANT c_diag_wg_ampl_unit : REAL := 2**REAL(c_diag_wg_ampl_w-c_diag_wg_gain_w)*c_diag_wg_ampl_norm; -- ^= Full Scale range [-c_wg_full_scale +c_wg_full_scale] without clipping + CONSTANT c_diag_wg_freq_unit : REAL := 2**REAL(c_diag_wg_freq_w); -- ^= c_clk_freq = Fs (sample frequency), assuming one sinus waveform in the buffer + CONSTANT c_diag_wg_phase_unit : REAL := 2**REAL(c_diag_wg_phase_w)/ 360.0; -- ^= 1 degree + + CONSTANT c_diag_wg_rst : t_diag_wg := (TO_UVEC(c_diag_wg_mode_off, c_diag_wg_mode_w), + TO_UVEC( 1024, c_diag_wg_nofsamples_w), + TO_UVEC( 0, c_diag_wg_phase_w), + TO_UVEC( 0, c_diag_wg_freq_w), + TO_UVEC( 0, c_diag_wg_ampl_w)); + + TYPE t_diag_wg_arr IS ARRAY (INTEGER RANGE <>) OF t_diag_wg; + + ----------------------------------------------------------------------------- + -- Block Generator + ----------------------------------------------------------------------------- + + -- control register + CONSTANT c_diag_bg_reg_nof_dat : NATURAL := 8; + CONSTANT c_diag_bg_reg_adr_w : NATURAL := ceil_log2(c_diag_bg_reg_nof_dat); + + CONSTANT c_diag_bg_mode_w : NATURAL := 8; + CONSTANT c_diag_bg_samples_per_packet_w : NATURAL := 24; + CONSTANT c_diag_bg_blocks_per_sync_w : NATURAL := 24; + CONSTANT c_diag_bg_gapsize_w : NATURAL := 24; + CONSTANT c_diag_bg_mem_adrs_w : NATURAL := 24; + CONSTANT c_diag_bg_mem_low_adrs_w : NATURAL := c_diag_bg_mem_adrs_w; + CONSTANT c_diag_bg_mem_high_adrs_w : NATURAL := c_diag_bg_mem_adrs_w; + CONSTANT c_diag_bg_bsn_init_w : NATURAL := 64; + + TYPE t_diag_block_gen IS RECORD + enable : STD_LOGIC; -- block enable + enable_sync : STD_LOGIC; -- block enable on sync pulse + samples_per_packet : STD_LOGIC_VECTOR(c_diag_bg_samples_per_packet_w -1 DOWNTO 0); + blocks_per_sync : STD_LOGIC_VECTOR(c_diag_bg_blocks_per_sync_w -1 DOWNTO 0); + gapsize : STD_LOGIC_VECTOR(c_diag_bg_gapsize_w -1 DOWNTO 0); + mem_low_adrs : STD_LOGIC_VECTOR(c_diag_bg_mem_low_adrs_w -1 DOWNTO 0); + mem_high_adrs : STD_LOGIC_VECTOR(c_diag_bg_mem_high_adrs_w -1 DOWNTO 0); + bsn_init : STD_LOGIC_VECTOR(c_diag_bg_bsn_init_w -1 DOWNTO 0); + END RECORD; + + CONSTANT c_diag_block_gen_rst : t_diag_block_gen := ( '0', + '0', + TO_UVEC( 256, c_diag_bg_samples_per_packet_w), + TO_UVEC( 10, c_diag_bg_blocks_per_sync_w), + TO_UVEC( 128, c_diag_bg_gapsize_w), + TO_UVEC( 0, c_diag_bg_mem_low_adrs_w), + TO_UVEC( 1, c_diag_bg_mem_high_adrs_w), + TO_UVEC( 0, c_diag_bg_bsn_init_w)); + + CONSTANT c_diag_block_gen_enabled : t_diag_block_gen := ( '1', + '0', + TO_UVEC( 50, c_diag_bg_samples_per_packet_w), + TO_UVEC( 10, c_diag_bg_blocks_per_sync_w), + TO_UVEC( 7, c_diag_bg_gapsize_w), + TO_UVEC( 0, c_diag_bg_mem_low_adrs_w), + TO_UVEC( 15, c_diag_bg_mem_high_adrs_w), -- fits any BG buffer that has address width >= 4 + TO_UVEC( 0, c_diag_bg_bsn_init_w)); + + TYPE t_diag_block_gen_arr IS ARRAY (INTEGER RANGE <>) OF t_diag_block_gen; + + -- Overloaded sel_a_b (from common_pkg) for t_diag_block_gen + FUNCTION sel_a_b(sel : BOOLEAN; a, b : t_diag_block_gen) RETURN t_diag_block_gen; + + ----------------------------------------------------------------------------- + -- Data buffer + ----------------------------------------------------------------------------- + CONSTANT c_diag_db_reg_nof_dat : NATURAL := 2; + CONSTANT c_diag_db_reg_adr_w : NATURAL := ceil_log2(c_diag_db_reg_nof_dat); + + CONSTANT c_diag_db_max_data_w : NATURAL := 32; + + TYPE t_diag_data_type_enum IS ( + e_data, + e_complex, -- im & re + e_real, + e_imag + ); + + ----------------------------------------------------------------------------- + -- Data buffer dev + ----------------------------------------------------------------------------- + CONSTANT c_diag_db_dev_reg_nof_dat : NATURAL := 8; -- Create headroom of 4 registers. + CONSTANT c_diag_db_dev_reg_adr_w : NATURAL := ceil_log2(c_diag_db_dev_reg_nof_dat); + + ----------------------------------------------------------------------------- + -- CNTR / PSRG sequence test data + ----------------------------------------------------------------------------- + + CONSTANT c_diag_seq_tx_reg_nof_dat : NATURAL := 4; + CONSTANT c_diag_seq_tx_reg_adr_w : NATURAL := ceil_log2(c_diag_seq_tx_reg_nof_dat); + CONSTANT c_diag_seq_rx_reg_nof_steps_wi : NATURAL := 4; + CONSTANT c_diag_seq_rx_reg_nof_steps : NATURAL := 4; + CONSTANT c_diag_seq_rx_reg_nof_dat : NATURAL := c_diag_seq_rx_reg_nof_steps_wi + c_diag_seq_rx_reg_nof_steps; + CONSTANT c_diag_seq_rx_reg_adr_w : NATURAL := ceil_log2(c_diag_seq_rx_reg_nof_dat); + + -- Record with all diag seq MM register fields + TYPE t_diag_seq_mm_reg IS RECORD + -- readback control + tx_init : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + tx_mod : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + tx_ctrl : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + rx_ctrl : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + rx_steps : t_integer_arr(c_diag_seq_rx_reg_nof_steps-1 DOWNTO 0); + -- read only status + tx_cnt : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + rx_cnt : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + rx_stat : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + rx_sample : STD_LOGIC_VECTOR(c_word_w -1 DOWNTO 0); + END RECORD; + + CONSTANT c_diag_seq_tx_reg_dis : NATURAL := 0; + CONSTANT c_diag_seq_tx_reg_en_psrg : NATURAL := 1; + CONSTANT c_diag_seq_tx_reg_en_cntr : NATURAL := 3; + + TYPE t_diag_seq_mm_reg_arr IS ARRAY (INTEGER RANGE <>) OF t_diag_seq_mm_reg; + +END diag_pkg; + +PACKAGE BODY diag_pkg IS + + FUNCTION sel_a_b(sel : BOOLEAN; a, b : t_diag_block_gen) RETURN t_diag_block_gen IS + BEGIN + IF sel = TRUE THEN + RETURN a; + ELSE + RETURN b; + END IF; + END; + +END diag_pkg;
trunk/diag_pkg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/diag_rx_seq.vhd =================================================================== --- trunk/diag_rx_seq.vhd (nonexistent) +++ trunk/diag_rx_seq.vhd (revision 2) @@ -0,0 +1,437 @@ +-------------------------------------------------------------------------------- +-- +-- Copyright (C) 2009 +-- 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: Verify received continuous test sequence data. +-- Description: +-- The diag_rx_seq can operate in one of two modes that depend on g_use_steps: +-- +-- . g_use_steps = FALSE +-- The test data can be PRSG or COUNTER dependent on diag_sel. +-- The Rx is enabled by diag_en. Typically the Tx should already be running, +-- but it is also allowed to first enable the Rx. +-- The Rx is always ready to accept data, therefore it has no in_ready output. +-- Inititally when diag_en is low then diag_res = -1, when diag_en is high +-- then diag_res becomes valid, indicated by diag_res_val, after two test +-- data words have been received. The diag_res verifies per input dat bit, +-- when an in_dat bit goes wrong then the corresponding bit in diag_res goes +-- high and remains high until the Rx is restarted again. This is useful if +-- the test data bits go via separate physical lines (e.g. an LVDS bus). +-- When the Rx is disabled then diag_res = -1. Typically the g_diag_res_w > +-- g_dat_w: +-- . diag_res(g_diag_res_w-1:g_dat_w) => NOT diag_res_val +-- . diag_res( g_dat_w-1:0 ) => aggregated diff of in_dat during +-- diag_en +-- It is possible to use g_diag_res_w=g_dat_w, but then it is not possible to +-- distinguish between whether the test has ran at all or whether all bits +-- got errors. +-- The diag_sample keeps the last valid in_dat value. When diag_en='0' it is +-- reset to 0. Reading diag_sample via MM gives an impression of the valid +-- in_dat activity. The diag_sample_diff shows the difference of the last and +-- the previous in_dat value. The diag_sample_diff can be useful to determine +-- or debug the values that are needed for diag_steps_arr. +-- +-- . g_use_steps = TRUE +-- The test data is fixed to COUNTER and diag_sel is ignored. The rx_seq can +-- verify counter data that increments in steps that are specified via +-- diag_steps_arr[3:0]. Up to g_nof_steps <= c_diag_seq_rx_reg_nof_steps = 4 +-- step sizes are supported. If all steps are set to 1 then there is no +-- difference compared using the COUNTER in g_use_steps = FALSE. Constant +-- value data can be verified by setting alls step to 0. Usinf different +-- steps is useful when the data is generated in linear incrementing order, +-- but received in a different order. Eg. like after a transpose operation +-- where blocks of data are written in row and and read in colums: +-- +-- tx: 0 1 2 3 4 5 6 7 8 9 10 11 +-- transpose: 0 1 4 5 8 9 2 3 6 7 10 11 +-- rx steps: +1 +1 +1 +1 +1 +1 +-- -11 +3 +3 -7 +3 +3 +-- +-- The step size value range is set by the 32 bit range of the VHDL integer. +-- Therefore typically g_dat_w should be <= 32 b. For a transpose that +-- contains more than 2**32 data words this means that the COUNTER data +-- wraps within the transpose. This is acceptable, because it use g_dat_w +-- <= 32 then still provides sufficient coverage to detect all errors. +-- +-- Data errors that match a step size cannot be detected. However if such +-- an error occurs then typically the next increment will cause a mismatch. +-- +-- Remarks: +-- . The feature of being able to detect errors per bit as with g_use_steps= +-- FALSE is not supported when g_use_steps=TRUE. Therefore the +-- diag_res[g_dat_w-1:0] = -1 (all '1') when a difference occurs that is no +-- in diag_steps_arr. +-- . The common_lfsr_nxt_seq() that is used when g_use_steps=FALSE uses the +-- in_dat_reg as initialization value for the reference sequence. All +-- subsequent values are derived when in_val_reg='1'. This is possible +-- because given a first value all subsequent values for PSRG or COUNTER +-- with +1 increment are known. For g_use_steps=TRUE the sequence is not +-- known in advance because different increment steps can occur at +-- arbitrary instants. Therefore then the in_dat_reg input is also used +-- during the sequence, to determine all g_nof_steps next values are correct +-- in case they occur. + +LIBRARY IEEE, common_pkg_lib, common_components_lib, common_counter_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 work.diag_pkg.ALL; + +ENTITY diag_rx_seq IS + GENERIC ( + g_input_reg : BOOLEAN := FALSE; -- Use unregistered input to save logic, use registered input to ease achieving timing constrains. + g_use_steps : BOOLEAN := FALSE; + g_nof_steps : NATURAL := c_diag_seq_rx_reg_nof_steps; + g_sel : STD_LOGIC := '1'; -- '0' = PRSG, '1' = COUNTER + g_cnt_incr : INTEGER := 1; + g_cnt_w : NATURAL := c_word_w; + g_dat_w : NATURAL := 12; + g_diag_res_w : NATURAL := 16 + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + + -- Static control input (connect via MM or leave open to use default) + diag_en : IN STD_LOGIC; -- '0' = init and disable, '1' = enable + diag_sel : IN STD_LOGIC := g_sel; + diag_steps_arr : t_integer_arr(g_nof_steps-1 DOWNTO 0) := (OTHERS=>1); + diag_res : OUT STD_LOGIC_VECTOR(g_diag_res_w-1 DOWNTO 0); -- diag_res valid indication bits & aggregate diff of in_dat during diag_en + diag_res_val : OUT STD_LOGIC; + diag_sample : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); -- monitor last valid in_dat + diag_sample_diff : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); -- monitor difference between last valid in_dat and previous valid in_dat + diag_sample_val : OUT STD_LOGIC; + + -- ST input + in_cnt : OUT STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0); -- count valid input test sequence data + in_dat : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); -- input test sequence data + in_val : IN STD_LOGIC -- gaps are allowed, however diag_res requires at least 2 valid in_dat to report a valid result + ); +END diag_rx_seq; + + +ARCHITECTURE rtl OF diag_rx_seq IS + + CONSTANT c_lfsr_nr : NATURAL := g_dat_w - c_common_lfsr_first; + + CONSTANT c_diag_res_latency : NATURAL := 3; + + -- Used special value to signal invalid diag_res, unique assuming g_diag_res_w > g_dat_w + CONSTANT c_diag_res_invalid : STD_LOGIC_VECTOR(diag_res'RANGE) := (OTHERS=>'1'); + + SIGNAL in_val_reg : STD_LOGIC; + SIGNAL in_dat_reg : STD_LOGIC_VECTOR(in_dat'RANGE); + + SIGNAL in_dat_dly1 : STD_LOGIC_VECTOR(in_dat'RANGE); -- latency common_lfsr_nxt_seq + SIGNAL in_dat_dly2 : STD_LOGIC_VECTOR(in_dat'RANGE); -- latency ref_dat + SIGNAL in_val_dly1 : STD_LOGIC; -- latency common_lfsr_nxt_seq + SIGNAL in_val_dly2 : STD_LOGIC; -- latency ref_dat + + SIGNAL prsg : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL nxt_prsg : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL cntr : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL nxt_cntr : STD_LOGIC_VECTOR(in_dat'RANGE); + + SIGNAL diag_dis : STD_LOGIC; + SIGNAL ref_en : STD_LOGIC; + SIGNAL diff_dis : STD_LOGIC; + SIGNAL diag_res_en : STD_LOGIC; + SIGNAL nxt_diag_res_en : STD_LOGIC; + SIGNAL nxt_diag_res_val: STD_LOGIC; + + SIGNAL in_val_1 : STD_LOGIC; + SIGNAL in_val_act : STD_LOGIC; + SIGNAL in_val_2 : STD_LOGIC; + SIGNAL in_val_2_dly : STD_LOGIC_VECTOR(0 TO c_diag_res_latency-1) := (OTHERS=>'0'); + SIGNAL in_val_2_act : STD_LOGIC; + + SIGNAL ref_dat : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL nxt_ref_dat : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL diff_dat : STD_LOGIC_VECTOR(in_dat'RANGE) := (OTHERS=>'0'); + SIGNAL nxt_diff_dat : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL diff_res : STD_LOGIC_VECTOR(in_dat'RANGE); + SIGNAL nxt_diag_res : STD_LOGIC_VECTOR(diag_res'RANGE); + + SIGNAL diag_res_int : STD_LOGIC_VECTOR(diag_res'RANGE) := c_diag_res_invalid; + + SIGNAL i_diag_sample : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL nxt_diag_sample : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL i_diag_sample_diff : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL nxt_diag_sample_diff : STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + SIGNAL nxt_diag_sample_val : STD_LOGIC; + + TYPE t_dat_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); + + SIGNAL ref_dat_arr : t_dat_arr(g_nof_steps-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); + SIGNAL nxt_ref_dat_arr : t_dat_arr(g_nof_steps-1 DOWNTO 0); + SIGNAL diff_arr : STD_LOGIC_VECTOR(g_nof_steps-1 DOWNTO 0) := (OTHERS=>'0'); + SIGNAL nxt_diff_arr : STD_LOGIC_VECTOR(g_nof_steps-1 DOWNTO 0); + SIGNAL diff_detect : STD_LOGIC := '0'; + SIGNAL nxt_diff_detect : STD_LOGIC; + SIGNAL diff_hold : STD_LOGIC; + +BEGIN + + diag_dis <= NOT diag_en; + diag_sample <= i_diag_sample; + diag_sample_diff <= i_diag_sample_diff; + + gen_input_reg : IF g_input_reg=TRUE GENERATE + p_reg : PROCESS (clk) + BEGIN + IF rising_edge(clk) THEN + IF clken='1' THEN + in_val_reg <= in_val; + in_dat_reg <= in_dat; + END IF; + END IF; + END PROCESS; + END GENERATE; + no_input_reg : IF g_input_reg=FALSE GENERATE + in_val_reg <= in_val; + in_dat_reg <= in_dat; + END GENERATE; + + -- Use initialisation to set initial diag_res to invalid + diag_res <= diag_res_int; -- use initialisation of internal signal diag_res_int rather than initialisation of entity output diag_res + +-- -- Use rst to set initial diag_res to invalid +-- p_rst_clk : PROCESS (rst, clk) +-- BEGIN +-- IF rst='1' THEN +-- diag_res <= c_diag_res_invalid; +-- ELSIF rising_edge(clk) THEN +-- IF clken='1' THEN +-- -- Internal. +-- diag_res <= nxt_diag_res; +-- -- Outputs. +-- END IF; +-- END IF; +-- END PROCESS; + + p_clk : PROCESS (clk) + BEGIN + IF rising_edge(clk) THEN + IF clken='1' THEN + -- Inputs. + in_dat_dly1 <= in_dat_reg; + in_dat_dly2 <= in_dat_dly1; + in_val_dly1 <= in_val_reg; + in_val_dly2 <= in_val_dly1; + -- Internal. + in_val_2_dly <= in_val_2 & in_val_2_dly(0 TO c_diag_res_latency-2); + diag_res_int <= nxt_diag_res; + diag_res_en <= nxt_diag_res_en; + diag_res_val <= nxt_diag_res_val; + -- . g_use_steps=FALSE + prsg <= nxt_prsg; + cntr <= nxt_cntr; + ref_dat <= nxt_ref_dat; + diff_dat <= nxt_diff_dat; + -- . g_use_steps=TRUE + ref_dat_arr <= nxt_ref_dat_arr; + diff_arr <= nxt_diff_arr; + diff_detect <= nxt_diff_detect; + -- Outputs. + i_diag_sample <= nxt_diag_sample; + i_diag_sample_diff <= nxt_diag_sample_diff; + diag_sample_val <= nxt_diag_sample_val; + END IF; + END IF; + END PROCESS; + + ------------------------------------------------------------------------------ + -- Keep last valid in_dat value for MM monitoring + ------------------------------------------------------------------------------ + nxt_diag_sample <= (OTHERS=>'0') WHEN diag_en='0' ELSE in_dat_reg WHEN in_val_reg='1' ELSE i_diag_sample; + nxt_diag_sample_diff <= (OTHERS=>'0') WHEN diag_en='0' ELSE SUB_UVEC(in_dat_reg, i_diag_sample) WHEN in_val_reg='1' ELSE i_diag_sample_diff; + nxt_diag_sample_val <= '0' WHEN diag_en='0' ELSE in_val_reg; + + ------------------------------------------------------------------------------ + -- Detect that there has been valid input data for at least two clock cycles + ------------------------------------------------------------------------------ + + u_in_val_1 : ENTITY common_components_lib.common_switch + PORT MAP( + clk => clk, + rst => rst, + switch_high => in_val_reg, + switch_low => diag_dis, + out_level => in_val_1 -- first in_val has been detected, but this one was used as seed for common_lfsr_nxt_seq + ); + + in_val_act <= in_val_1 AND in_val_reg; -- Signal the second valid in_dat after diag_en='1' + + u_in_val_2 : ENTITY common_components_lib.common_switch + PORT MAP( + clk => clk, + rst => rst, + switch_high => in_val_act, + switch_low => diag_dis, + out_level => in_val_2 -- second in_val has been detected, representing a true next sequence value + ); + + -- Use in_val_2_act instead of in_val_2 to have stable start in case diag_dis takes just a pulse and in_val is continue high + in_val_2_act <= vector_and(in_val_2 & in_val_2_dly); + + -- Use the first valid in_dat after diag_en='1' to initialize the reference data sequence + ref_en <= in_val_1; + + -- Use the detection of second valid in_dat after diag_en='1' to start detection of differences + diff_dis <= NOT in_val_2_act; + + no_steps : IF g_use_steps=FALSE GENERATE + -- Determine next reference dat based on current input dat + common_lfsr_nxt_seq(c_lfsr_nr, -- IN + g_cnt_incr, -- IN + ref_en, -- IN + in_val_reg, -- IN, use in_val_reg to allow gaps in the input data valid stream + in_dat_reg, -- IN, used only to init nxt_prsg and nxt_cntr when ref_en='0' + prsg, -- IN + cntr, -- IN + nxt_prsg, -- OUT + nxt_cntr); -- OUT + + nxt_ref_dat <= prsg WHEN diag_sel='0' ELSE cntr; + + -- Detect difference per bit. The ref_dat has latency 2 compared to the in_dat, because of the register stage in psrg/cntr and the register stage in ref_dat. + p_diff_dat : PROCESS (diff_dat, ref_dat, in_val_dly2, in_dat_dly2) + BEGIN + nxt_diff_dat <= diff_dat; + IF in_val_dly2='1' THEN + FOR I IN in_dat'RANGE LOOP + nxt_diff_dat(I) <= ref_dat(I) XOR in_dat_dly2(I); + END LOOP; + END IF; + END PROCESS; + + gen_verify_dat : FOR I IN in_dat'RANGE GENERATE + -- Detect and report undefined diff input 'X', which in simulation leaves diff_res at OK, because switch_high only acts on '1' + p_sim_only : PROCESS(clk) + BEGIN + IF rising_edge(clk) THEN + IF diff_dat(I)/='0' AND diff_dat(I)/='1' THEN + REPORT "diag_rx_seq : undefined input" SEVERITY FAILURE; + END IF; + END IF; + END PROCESS; + + -- Hold any difference on the in_dat bus lines + u_dat : ENTITY common_components_lib.common_switch + PORT MAP( + clk => clk, + rst => rst, + switch_high => diff_dat(I), + switch_low => diff_dis, + out_level => diff_res(I) + ); + END GENERATE; + END GENERATE; + + use_steps : IF g_use_steps=TRUE GENERATE + -- Determine next reference data for all steps increments of current input dat + p_ref_dat_arr : PROCESS(in_dat_reg, in_val_reg, ref_dat_arr) + BEGIN + nxt_ref_dat_arr <= ref_dat_arr; + IF in_val_reg='1' THEN + FOR I IN g_nof_steps-1 DOWNTO 0 LOOP + nxt_ref_dat_arr(I) <= INCR_UVEC(in_dat_reg, diag_steps_arr(I)); + END LOOP; + END IF; + END PROCESS; + + -- Detect difference for each allowed reference data. + p_diff_arr : PROCESS(diff_arr, in_val_reg, in_dat_reg, ref_dat_arr) + BEGIN + nxt_diff_arr <= diff_arr; + IF in_val_reg='1' THEN + nxt_diff_arr <= (OTHERS=>'1'); + FOR I IN g_nof_steps-1 DOWNTO 0 LOOP + IF UNSIGNED(ref_dat_arr(I))=UNSIGNED(in_dat_reg) THEN + nxt_diff_arr(I) <= '0'; + END IF; + END LOOP; + END IF; + END PROCESS; + + -- detect diff when none of the step counter value matches + p_diff_detect : PROCESS(diff_detect, diff_arr, in_val_dly1) + BEGIN + nxt_diff_detect <= diff_detect; + IF in_val_dly1='1' THEN + nxt_diff_detect <= '0'; + IF vector_and(diff_arr)='1' THEN + nxt_diff_detect <= '1'; + END IF; + END IF; + END PROCESS; + + -- hold detected diff detect + u_dat : ENTITY common_components_lib.common_switch + PORT MAP( + clk => clk, + rst => rst, + switch_high => diff_detect, + switch_low => diff_dis, + out_level => diff_hold + ); + + diff_res <= (OTHERS=> diff_hold); -- convert diff_hold to diff_res slv format as used for g_use_steps=FALSE + END GENERATE; + + + ------------------------------------------------------------------------------ + -- Report valid diag_res + ------------------------------------------------------------------------------ + + nxt_diag_res_en <= diag_en AND in_val_2_act; + nxt_diag_res_val <= diag_res_en; + + p_diag_res : PROCESS (diff_res, diag_res_en) + BEGIN + nxt_diag_res <= c_diag_res_invalid; + IF diag_res_en='1' THEN + -- The test runs AND there have been valid input samples to verify + nxt_diag_res <= (OTHERS=>'0'); -- MSBits of valid diag_res are 0 + nxt_diag_res(diff_res'RANGE) <= diff_res; -- diff_res of dat[] + END IF; + END PROCESS; + + + ------------------------------------------------------------------------------ + -- Count number of valid input data + ------------------------------------------------------------------------------ + u_common_counter : ENTITY common_counter_lib.common_counter + GENERIC MAP ( + g_latency => 1, -- default 1 for registered count output, use 0 for immediate combinatorial count output + g_width => g_cnt_w + ) + PORT MAP ( + rst => rst, + clk => clk, + clken => clken, + cnt_clr => diag_dis, -- synchronous cnt_clr is only interpreted when clken is active + cnt_en => in_val, + count => in_cnt + ); +END rtl;
trunk/diag_rx_seq.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/diag_tx_seq.vhd =================================================================== --- trunk/diag_tx_seq.vhd (nonexistent) +++ trunk/diag_tx_seq.vhd (revision 2) @@ -0,0 +1,153 @@ +-------------------------------------------------------------------------------- +-- +-- 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, common_counter_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; + +-- Purpose: Transmit continuous PRSG or COUNTER test sequence data. +-- Description: +-- The Tx test data can sequence data or constant value data dependent on +-- diag_dc. +-- The Tx test sequence data can be PRSG or COUNTER dependent on diag_sel. +-- The Tx is enabled by diag_en. When the Tx is disabled then the sequence +-- data gets initialised with diag_init. +-- The out_ready acts as a data request. When the generator is enabled then +-- output is valid for every active out_ready, to support streaming flow +-- control. With g_latency=1 the out_val is active one cycle after diag_req, +-- by using g_latency=0 outval is active in the same cycle as diag_req. +-- Use diag_mod=0 for default binary wrap at 2**g_dat_w. For diag_rx_seq +-- choose diag_step = 2**g_seq_dat_w - diag_mod + g_cnt_incr to verify ok. + +ENTITY diag_tx_seq IS + GENERIC ( + g_latency : NATURAL := 1; -- default 1 for registered out_cnt/dat/val output, use 0 for immediate combinatorial out_cnt/dat/val output + g_sel : STD_LOGIC := '1'; -- '0' = PRSG, '1' = COUNTER + g_init : NATURAL := 0; -- init value for out_dat when diag_en = '0' + g_cnt_incr : INTEGER := 1; + g_cnt_w : NATURAL := c_word_w; + g_dat_w : NATURAL -- >= 1, test data width + ); + PORT ( + rst : IN STD_LOGIC; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + -- Static control input (connect via MM or leave open to use default) + diag_en : IN STD_LOGIC; -- '0' = init and disable output sequence, '1' = enable output sequence + diag_sel : IN STD_LOGIC := g_sel; -- '0' = PRSG sequence data, '1' = COUNTER sequence data + diag_dc : IN STD_LOGIC := '0'; -- '0' = output diag_sel sequence data, '1' = output constant diag_init data + diag_init : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0) := TO_UVEC(g_init, g_dat_w); -- init value for out_dat when diag_en = '0' + diag_mod : IN STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0) := TO_UVEC(0, g_dat_w); -- default 0 to wrap modulo 2*g_dat_w + -- ST output + diag_req : IN STD_LOGIC := '1'; -- '1' = request output, '0' = halt output + out_cnt : OUT STD_LOGIC_VECTOR(g_cnt_w-1 DOWNTO 0); -- count valid output test sequence data + out_dat : OUT STD_LOGIC_VECTOR(g_dat_w-1 DOWNTO 0); -- output test sequence data + out_val : OUT STD_LOGIC -- '1' when out_dat is valid + ); +END diag_tx_seq; + + +ARCHITECTURE rtl OF diag_tx_seq IS + + CONSTANT c_lfsr_nr : NATURAL := g_dat_w - c_common_lfsr_first; + + SIGNAL diag_dis : STD_LOGIC; + + SIGNAL prsg : STD_LOGIC_VECTOR(out_dat'RANGE); + SIGNAL nxt_prsg : STD_LOGIC_VECTOR(out_dat'RANGE); + SIGNAL cntr : STD_LOGIC_VECTOR(out_dat'RANGE) := (OTHERS=>'0'); -- init to avoid Warning: "NUMERIC_STD."<": metavalue detected" with UNSIGNED() + SIGNAL next_cntr : STD_LOGIC_VECTOR(out_dat'RANGE) := (OTHERS=>'0'); -- init to avoid Warning: "NUMERIC_STD."<": metavalue detected" with UNSIGNED() + SIGNAL nxt_cntr : STD_LOGIC_VECTOR(out_dat'RANGE); + + SIGNAL nxt_out_dat : STD_LOGIC_VECTOR(out_dat'RANGE); + SIGNAL nxt_out_val : STD_LOGIC; + +BEGIN + + diag_dis <= NOT diag_en; + + p_clk : PROCESS (rst, clk) + BEGIN + IF rst='1' THEN + prsg <= (OTHERS=>'0'); + cntr <= (OTHERS=>'0'); + ELSIF rising_edge(clk) THEN + IF clken='1' THEN + prsg <= nxt_prsg; + cntr <= nxt_cntr; + END IF; + END IF; + END PROCESS; + + gen_latency : IF g_latency/=0 GENERATE + p_clk : PROCESS (rst, clk) + BEGIN + IF rst='1' THEN + out_dat <= (OTHERS=>'0'); + out_val <= '0'; + ELSIF rising_edge(clk) THEN + IF clken='1' THEN + out_dat <= nxt_out_dat; + out_val <= nxt_out_val; + END IF; + END IF; + END PROCESS; + END GENERATE; + + no_latency : IF g_latency=0 GENERATE + out_dat <= nxt_out_dat; + out_val <= nxt_out_val; + END GENERATE; + + common_lfsr_nxt_seq(c_lfsr_nr, -- IN + g_cnt_incr, -- IN + diag_en, -- IN + diag_req, -- IN + diag_init, -- IN + prsg, -- IN + cntr, -- IN + nxt_prsg, -- OUT + next_cntr); -- OUT + + nxt_cntr <= next_cntr WHEN UNSIGNED(next_cntr) < UNSIGNED(diag_mod) ELSE SUB_UVEC(next_cntr, diag_mod); + + nxt_out_dat <= diag_init WHEN diag_dc='1' ELSE prsg WHEN diag_sel='0' ELSE cntr; + nxt_out_val <= diag_en AND diag_req; -- 'en' for entire test on/off, 'req' for dynamic invalid gaps in the stream + + -- Count number of valid output data + u_common_counter : ENTITY common_counter_lib.common_counter + GENERIC MAP ( + g_latency => g_latency, -- default 1 for registered count output, use 0 for immediate combinatorial count output + g_width => g_cnt_w + ) + PORT MAP ( + rst => rst, + clk => clk, + clken => clken, + cnt_clr => diag_dis, -- synchronous cnt_clr is only interpreted when clken is active + cnt_en => nxt_out_val, + count => out_cnt + ); + +END rtl;
trunk/diag_tx_seq.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/hdllib.cfg =================================================================== --- trunk/hdllib.cfg (nonexistent) +++ trunk/hdllib.cfg (revision 2) @@ -0,0 +1,68 @@ +hdl_lib_name = diag +hdl_library_clause_name = diag_lib +hdl_lib_uses_synth = common_pkg dp_pkg dp_components common_components common_ram common_counter common_ram dp_mux technology mm dp_pipeline #common_mult +hdl_lib_uses_sim = +hdl_lib_technology = + +synth_files = + diag_pkg.vhd +# src/vhdl/diag_bypass.vhd + +# src/vhdl/diag_tx_frm.vhd + diag_rx_seq.vhd +# src/vhdl/diag_frm_generator.vhd +# src/vhdl/diag_frm_monitor.vhd + + mms_diag_rx_seq.vhd +# src/vhdl/diag_wg.vhd +# src/vhdl/diag_wg_wideband.vhd +# src/vhdl/diag_wg_wideband_reg.vhd +# src/vhdl/mms_diag_wg_wideband.vhd + diag_data_buffer.vhd +# src/vhdl/diag_data_buffer_dev.vhd + mms_diag_data_buffer.vhd +# src/vhdl/mms_diag_data_buffer_dev.vhd + diag_tx_seq.vhd + diag_block_gen.vhd + diag_block_gen_reg.vhd + mms_diag_tx_seq.vhd + mms_diag_block_gen.vhd + +test_bench_files = +# tb/vhdl/tb_diag_pkg.vhd +# tb/vhdl/tb_diag_wg.vhd +# tb/vhdl/tb_diag_wg_wideband.vhd +# tb/vhdl/tb_diag_tx_seq.vhd +# tb/vhdl/tb_diag_rx_seq.vhd +# tb/vhdl/tb_tb_diag_rx_seq.vhd +# tb/vhdl/tb_diag_tx_frm.vhd +# tb/vhdl/tb_diag_frm_generator.vhd +# tb/vhdl/tb_diag_frm_monitor.vhd +# tb/vhdl/tb_diag_data_buffer_dev.vhd +# tb/vhdl/tb_mms_diag_seq.vhd +# tb/vhdl/tb_tb_mms_diag_seq.vhd +# tb/vhdl/tb_diag_block_gen.vhd +# tb/vhdl/tb_tb_diag_block_gen.vhd +# tb/vhdl/tb_mms_diag_block_gen.vhd +# tb/vhdl/tb_tb_mms_diag_block_gen.vhd +# tb/vhdl/tb_diag_regression.vhd + +regression_test_vhdl = +# tb/vhdl/tb_diag_wg.vhd +# tb/vhdl/tb_diag_wg_wideband.vhd +# tb/vhdl/tb_diag_frm_generator.vhd +# tb/vhdl/tb_diag_frm_monitor.vhd +# tb/vhdl/tb_tb_diag_block_gen.vhd +# tb/vhdl/tb_tb_diag_rx_seq.vhd +# tb/vhdl/tb_tb_mms_diag_seq.vhd +# tb/vhdl/tb_tb_mms_diag_block_gen.vhd + + +[modelsim_project_file] +modelsim_copy_files = + src/data data + + +[quartus_project_file] + +
trunk/hdllib.cfg Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mms_diag_block_gen.vhd =================================================================== --- trunk/mms_diag_block_gen.vhd (nonexistent) +++ trunk/mms_diag_block_gen.vhd (revision 2) @@ -0,0 +1,402 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2011 +-- 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: Block generator for multiple parallel SOSI streams +-- Description: +-- . The mms_diag_block_gen provides a MM slave interface to an array of +-- g_nof_streams diag_block_gen instances. +-- . The waveform data is stored in RAM and can be pre-load with data from a +-- file g_file_name_prefix. The stream index to the select the actual file +-- is default I, but can be set via g_file_index_arr(I). The g_file_index_arr +-- makes the relation between the instance index and file index flexible. + +-- . g_use_usr_input and g_use_bg +-- When g_use_usr_input=FALSE the BG works standalone. +-- When g_use_bg=FALSE then only the user input is used. +-- When both g_use_usr_input=TRUE and g_use_bg=TRUE then default the user +-- input is passed on when the BG is disabled. The dynamic selection between +-- user input an BG output is done between blocks by the dp_mux using xon. +-- +-- . g_use_bg_buffer_ram +-- When g_use_bg_buffer_ram=TRUE then each stream has a BG buffer RAM that +-- can be accessed via the ram_bg_data MM port. Else when +-- g_use_bg_buffer_ram= FALSE then the RAM is not implemented (to save +-- RAM resources) and instead the RAM read address is used as data in the +-- generated data block. Hence the data will then depend on mem_low_adrs, +-- mem_high_adrs and samples_per_packet, so typically it will output the +-- counter data (0:samples_per_packet-1) and the samedata foreach block. +-- +-- . g_use_tx_seq +-- When g_use_tx_seq=TRUE then the diag_mms_tx_seq is instantiated. If the +-- tx_seq is enabled then the data field is overwitten with tx seq counter +-- or pseudo random data. The tx seq uses the valid as request for tx seq +-- data, so it preserves the output valid, sop, eop framing. For more info +-- on the tx_seq see mms_diag_tx_seq. If g_use_usr_input=FALSE and g_use_bg +-- =FALSE and g_use_tx_seq=TRUE then only the tx_seq is instantiated and +-- without input (c_use_tx_seq_input). +-- +-- Block diagram: +-- +-- g_use_bg +-- g_use_bg_buffer_ram +-- . +-- . g_use_usr_input g_use_tx_seq +-- . . g_usr_bypass_xonoff . +-- . . . . +-- . . . . +-- . . . . +-- . . ___ __ dp_mux . +-- . . |dp | | \ . +-- . usr----|xon|-->|0 \ . +-- . |off| | \ . +-- . |___| | |----------------->|\ +-- . | / | | |---> out +-- BG ctrl----------->|1 / \--> TX seq -->|/ +-- BG data |__/ | +-- || | +-- || | +-- MM ==================================================== +-- +-- The dp_mux is only there if both the usr input and the BG are used. +-- +-- Remark: +-- . The diag_block_gen does not support back pressure, but it does support +-- XON/XOFF flow control at block level via out_siso.xon. +-- . Default input *_mosi = c_mem_mosi_rst to support using the BG with default +-- control and memory settings and no MM interface +-- . The BG does support xon flow control. +-- . If the user input already supports xon then g_usr_bypass_xonoff can be +-- set to TRUE. However if g_usr_bypass_xonoff=FALSE then this is fine to +-- because an extra dp_xonoff stage merely causes the stream to resume one +-- block later when xon goes active (see test bench tb_dp_xonoff). The +-- diag_block_gen BG does already support xon. +-- . A nice new feature would be to support BG data width > 32b, similar as in +-- the DB mms_diag_data_buffer.vhd. +-- . A nice new feature would be to support a BG burst of N blocks. + + +LIBRARY IEEE, common_pkg_lib, common_ram_lib, technology_lib, dp_pkg_lib, dp_components_lib, dp_mux_lib, mm_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE IEEE.NUMERIC_STD.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; +USE work.diag_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +ENTITY mms_diag_block_gen IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + -- Generate configurations + g_use_usr_input : BOOLEAN := FALSE; + g_use_bg : BOOLEAN := TRUE; + g_use_tx_seq : BOOLEAN := FALSE; + -- General + g_nof_streams : POSITIVE := 1; + -- BG settings + g_use_bg_buffer_ram : BOOLEAN := TRUE; + g_buf_dat_w : POSITIVE := 32; + g_buf_addr_w : POSITIVE := 7; -- Waveform buffer size 2**g_buf_addr_w nof samples + g_file_index_arr : t_nat_natural_arr := array_init(0, 128, 1); -- default use the instance index as file index 0, 1, 2, 3, 4 ... + g_file_name_prefix : STRING := "data/bf_in_data"; -- Path to the hex files that contain the initial data for the memories. The sequence number and ".hex" are added within the entity. + g_diag_block_gen_rst : t_diag_block_gen := c_diag_block_gen_rst; + -- User input multiplexer option + g_usr_bypass_xonoff : BOOLEAN := FALSE; + -- Tx_seq + g_seq_dat_w : NATURAL := 32; -- >= 1, test sequence data width. Choose g_seq_dat_w <= g_buf_dat_w + -- LOFAR Lofar style block sync that is active from SOP to EOP + g_blk_sync : BOOLEAN := FALSE + ); + PORT ( + -- System + mm_rst : IN STD_LOGIC; -- reset synchronous with mm_clk + mm_clk : IN STD_LOGIC; -- memory-mapped bus clock + dp_rst : IN STD_LOGIC; -- reset synchronous with st_clk + dp_clk : IN STD_LOGIC; -- streaming clock domain clock + en_sync : IN STD_LOGIC := '1'; -- block generator enable sync pulse in ST dp_clk domain + -- MM interface + reg_bg_ctrl_mosi : IN t_mem_mosi := c_mem_mosi_rst; -- BG control register (one for all streams) + reg_bg_ctrl_miso : OUT t_mem_miso; + ram_bg_data_mosi : IN t_mem_mosi := c_mem_mosi_rst; -- BG buffer RAM (one per stream) + ram_bg_data_miso : OUT t_mem_miso; + reg_tx_seq_mosi : IN t_mem_mosi := c_mem_mosi_rst; -- Tx seq control (one per stream because c_reg_tx_seq_broadcast=FALSE) + reg_tx_seq_miso : OUT t_mem_miso; + -- ST interface + usr_siso_arr : OUT t_dp_siso_arr(g_nof_streams-1 DOWNTO 0); -- connect when g_use_usr_input=TRUE, else leave not connected + usr_sosi_arr : IN t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>c_dp_sosi_rst); + out_siso_arr : IN t_dp_siso_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>c_dp_siso_rdy); -- Default xon='1' + out_sosi_arr : OUT t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) -- Output SOSI that contains the waveform data + ); +END mms_diag_block_gen; + +ARCHITECTURE rtl OF mms_diag_block_gen IS + + CONSTANT c_buf : t_c_mem := (latency => 1, + adr_w => g_buf_addr_w, + dat_w => g_buf_dat_w, + nof_dat => 2**g_buf_addr_w, + init_sl => '0'); + + CONSTANT c_post_buf_file : STRING := ".hex"; + + CONSTANT c_use_mux : BOOLEAN := g_use_usr_input AND g_use_bg; + CONSTANT c_use_tx_seq_input : BOOLEAN := g_use_usr_input OR g_use_bg; + CONSTANT c_mux_nof_input : NATURAL := 2; -- fixed + + CONSTANT c_reg_tx_seq_broadcast : BOOLEAN := FALSE; -- fixed use dedicated MM register per stream + + TYPE t_buf_dat_arr IS ARRAY (NATURAL RANGE <>) OF STD_LOGIC_VECTOR(g_buf_dat_w -1 DOWNTO 0); + TYPE t_buf_adr_arr IS ARRAY (NATURAL RANGE <>) OF STD_LOGIC_VECTOR(g_buf_addr_w-1 DOWNTO 0); + + SIGNAL st_addr_arr : t_buf_adr_arr(g_nof_streams -1 DOWNTO 0); + SIGNAL st_rd_arr : STD_LOGIC_VECTOR(g_nof_streams -1 DOWNTO 0); + SIGNAL st_rdval_arr : STD_LOGIC_VECTOR(g_nof_streams -1 DOWNTO 0); + SIGNAL st_rddata_arr : t_buf_dat_arr(g_nof_streams -1 DOWNTO 0); + SIGNAL ram_bg_data_mosi_arr : t_mem_mosi_arr(g_nof_streams -1 DOWNTO 0); + SIGNAL ram_bg_data_miso_arr : t_mem_miso_arr(g_nof_streams -1 DOWNTO 0); + SIGNAL bg_ctrl : t_diag_block_gen; + + SIGNAL mux_ctrl : NATURAL RANGE 0 TO c_mux_nof_input-1; + SIGNAL mux_snk_out_2arr_2 : t_dp_siso_2arr_2(g_nof_streams-1 DOWNTO 0); -- [g_nof_streams-1:0][c_mux_nof_input-1:0] = [1:0] + SIGNAL mux_snk_in_2arr_2 : t_dp_sosi_2arr_2(g_nof_streams-1 DOWNTO 0); -- [g_nof_streams-1:0][c_mux_nof_input-1:0] = [1:0] + + SIGNAL usr_xflow_src_in_arr : t_dp_siso_arr(g_nof_streams-1 DOWNTO 0); -- optionally use dp_xonoff to add siso.xon flow control to use input when g_usr_bypass_xonoff=FALSE + SIGNAL usr_xflow_src_out_arr : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0); + + SIGNAL bg_src_in_arr : t_dp_siso_arr(g_nof_streams-1 DOWNTO 0); -- BG has siso.xon flow control but no siso.ready flow control + SIGNAL bg_src_out_arr : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0); + + SIGNAL mux_src_in_arr : t_dp_siso_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL mux_src_out_arr : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0); + +BEGIN + + ----------------------------------------------------------------------------- + -- BG + ----------------------------------------------------------------------------- + + no_bg : IF g_use_bg=FALSE GENERATE + reg_bg_ctrl_miso <= c_mem_miso_rst; + ram_bg_data_miso <= c_mem_miso_rst; + + bg_src_out_arr <= (OTHERS=>c_dp_sosi_rst); + END GENERATE; + + gen_bg : IF g_use_bg=TRUE GENERATE + mux_ctrl <= 0 WHEN bg_ctrl.enable='0' ELSE 1; + + u_bg_ctrl : ENTITY work.diag_block_gen_reg + GENERIC MAP( + g_cross_clock_domain => TRUE, -- use FALSE when mm_clk and st_clk are the same, else use TRUE to cross the clock domain + g_diag_block_gen_rst => g_diag_block_gen_rst + ) + PORT MAP ( + mm_rst => mm_rst, -- Clocks and reset + mm_clk => mm_clk, + dp_rst => dp_rst, + dp_clk => dp_clk, + mm_mosi => reg_bg_ctrl_mosi, + mm_miso => reg_bg_ctrl_miso, + bg_ctrl => bg_ctrl + ); + + -- Combine the internal array of mm interfaces for the bg_data to one array that is connected to the port of the MM bus + u_mem_mux_bg_data : ENTITY mm_lib.common_mem_mux + GENERIC MAP ( + g_nof_mosi => g_nof_streams, + g_mult_addr_w => g_buf_addr_w + ) + PORT MAP ( + mosi => ram_bg_data_mosi, + miso => ram_bg_data_miso, + mosi_arr => ram_bg_data_mosi_arr, + miso_arr => ram_bg_data_miso_arr + ); + + gen_streams : FOR I IN 0 TO g_nof_streams-1 GENERATE + no_buffer_ram : IF g_use_bg_buffer_ram=FALSE GENERATE + ram_bg_data_miso_arr(I) <= c_mem_miso_rst; + + -- Use read address as read data with read latency 1 similar as for u_buffer_ram + st_rdval_arr(I) <= st_rd_arr(I) WHEN rising_edge(dp_clk); + st_rddata_arr(I) <= RESIZE_UVEC(st_addr_arr(I), g_buf_dat_w) WHEN rising_edge(dp_clk); + END GENERATE; + + gen_buffer_ram : IF g_use_bg_buffer_ram=TRUE GENERATE + u_buffer_ram : ENTITY common_ram_lib.common_ram_crw_crw + GENERIC MAP ( + g_technology => g_technology, + g_ram => c_buf, + -- Sequence number and ".hex" extension are added to the relative path in case a ram file is provided. + g_init_file => sel_a_b(g_file_name_prefix = "UNUSED", g_file_name_prefix, g_file_name_prefix & "_" & NATURAL'IMAGE(g_file_index_arr(I)) & c_post_buf_file) + ) + PORT MAP ( + -- MM side + rst_a => mm_rst, + clk_a => mm_clk, + wr_en_a => ram_bg_data_mosi_arr(I).wr, + wr_dat_a => ram_bg_data_mosi_arr(I).wrdata(c_buf.dat_w -1 DOWNTO 0), + adr_a => ram_bg_data_mosi_arr(I).address(c_buf.adr_w-1 DOWNTO 0), + rd_en_a => ram_bg_data_mosi_arr(I).rd, + rd_dat_a => ram_bg_data_miso_arr(I).rddata(c_buf.dat_w -1 DOWNTO 0), + rd_val_a => ram_bg_data_miso_arr(I).rdval, + -- Waveform side + rst_b => dp_rst, + clk_b => dp_clk, + wr_en_b => '0', + wr_dat_b => (OTHERS =>'0'), + adr_b => st_addr_arr(I), + rd_en_b => st_rd_arr(I), + rd_dat_b => st_rddata_arr(I), + rd_val_b => st_rdval_arr(I) + ); + END GENERATE; + + u_diag_block_gen : ENTITY work.diag_block_gen + GENERIC MAP ( + g_blk_sync => g_blk_sync, + g_buf_dat_w => g_buf_dat_w, + g_buf_addr_w => g_buf_addr_w + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + buf_addr => st_addr_arr(I), + buf_rden => st_rd_arr(I), + buf_rddat => st_rddata_arr(I), + buf_rdval => st_rdval_arr(I), + ctrl => bg_ctrl, + en_sync => en_sync, + out_siso => bg_src_in_arr(I), + out_sosi => bg_src_out_arr(I) + ); + END GENERATE; + END GENERATE; + + + --------------------------------------------------------------------------- + -- No multiplexer, so only one input or no input at all + --------------------------------------------------------------------------- + no_dp_mux : IF c_use_mux=FALSE GENERATE -- so g_use_usr_input and g_use_bg are not both TRUE + -- default pass on flow control + usr_siso_arr <= mux_src_in_arr; + bg_src_in_arr <= mux_src_in_arr; + + -- User input only, BG only or no input + mux_src_out_arr <= usr_sosi_arr WHEN g_use_usr_input=TRUE ELSE + bg_src_out_arr WHEN g_use_bg=TRUE ELSE + (OTHERS=>c_dp_sosi_rst); + END GENERATE; + + + ----------------------------------------------------------------------------- + -- Multiplex user input and BG + ----------------------------------------------------------------------------- + gen_dp_mux : IF c_use_mux=TRUE GENERATE -- so g_use_usr_input and g_use_bg are both TRUE + gen_streams : FOR I IN 0 TO g_nof_streams-1 GENERATE + -- Add user xon flow control if the user input does not already support it + u_dp_xonoff : ENTITY dp_components_lib.dp_xonoff + GENERIC MAP ( + g_bypass => g_usr_bypass_xonoff -- if the user input already has xon flow control then bypass using g_usr_bypass_xonoff=TRUE + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + -- Frame in + in_siso => usr_siso_arr(I), + in_sosi => usr_sosi_arr(I), + -- Frame out + out_siso => usr_xflow_src_in_arr(I), -- flush control via out_siso.xon + out_sosi => usr_xflow_src_out_arr(I) + ); + + -- Multiplex the inputs: + -- . [0] = usr input + -- . [1] = BG + usr_xflow_src_in_arr(I) <= mux_snk_out_2arr_2(I)(0); + bg_src_in_arr(I) <= mux_snk_out_2arr_2(I)(1); + + mux_snk_in_2arr_2(I)(0) <= usr_xflow_src_out_arr(I); + mux_snk_in_2arr_2(I)(1) <= bg_src_out_arr(I); + + u_dp_mux : ENTITY dp_mux_lib.dp_mux + GENERIC MAP ( + g_technology => g_technology, + -- MUX + g_mode => 4, -- g_mode=4 for framed input select via sel_ctrl + g_nof_input => c_mux_nof_input, -- >= 1 + g_append_channel_lo => FALSE, + g_sel_ctrl_invert => TRUE, -- Use default FALSE when stream array IO are indexed (0 TO g_nof_input-1), else use TRUE when indexed (g_nof_input-1 DOWNTO 0) + -- Input FIFO + g_use_fifo => FALSE, + g_fifo_size => array_init(1024, c_mux_nof_input), -- must match g_nof_input, even when g_use_fifo=FALSE + g_fifo_fill => array_init( 0, c_mux_nof_input) -- must match g_nof_input, even when g_use_fifo=FALSE + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + -- Control + sel_ctrl => mux_ctrl, -- 0 = usr, 1 = BG + -- ST sinks + snk_out_arr => mux_snk_out_2arr_2(I), -- [c_mux_nof_input-1:0] + snk_in_arr => mux_snk_in_2arr_2(I), -- [c_mux_nof_input-1:0] + -- ST source + src_in => mux_src_in_arr(I), + src_out => mux_src_out_arr(I) + ); + END GENERATE; + END GENERATE; + + no_tx_seq : IF g_use_tx_seq=FALSE GENERATE + reg_tx_seq_miso <= c_mem_miso_rst; + + mux_src_in_arr <= out_siso_arr; + out_sosi_arr <= mux_src_out_arr; + END GENERATE; + + gen_tx_seq : IF g_use_tx_seq=TRUE GENERATE + u_mms_diag_tx_seq : ENTITY work.mms_diag_tx_seq + GENERIC MAP ( + g_use_usr_input => c_use_tx_seq_input, + g_mm_broadcast => c_reg_tx_seq_broadcast, + g_nof_streams => g_nof_streams, + g_seq_dat_w => g_seq_dat_w + ) + PORT MAP ( + -- Clocks and reset + mm_rst => mm_rst, + mm_clk => mm_clk, + dp_rst => dp_rst, + dp_clk => dp_clk, + + -- MM interface + reg_mosi => reg_tx_seq_mosi, + reg_miso => reg_tx_seq_miso, + + -- DP streaming interface + usr_snk_out_arr => mux_src_in_arr, -- connect when g_use_usr_input=TRUE, else leave not connected + usr_snk_in_arr => mux_src_out_arr, + tx_src_out_arr => out_sosi_arr, + tx_src_in_arr => out_siso_arr + ); + END GENERATE; + +END rtl;
trunk/mms_diag_block_gen.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mms_diag_data_buffer.vhd =================================================================== --- trunk/mms_diag_data_buffer.vhd (nonexistent) +++ trunk/mms_diag_data_buffer.vhd (revision 2) @@ -0,0 +1,224 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2011 +-- 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: MM data buffer and Rx seq for multiple parallel SOSI streams +-- Description: +-- . g_use_db +-- The mms_diag_data_buffer can capture data from an input stream in a data +-- buffer when g_use_db=TRUE. Dependend on g_buf_use_sync the data buffer +-- is rewritten after each in_sync or when the last word was read via MM. +-- . g_use_rx_seq +-- The mms_diag_data_buffer can continously verify a input Rx data sequence +-- when g_use_rx_seq=TRUE. The expected sequence data is typically generated +-- by an remote upstream tx_seq source. +-- . The advantage of the rx_seq is that is can continously verify the +-- correctness of all rx data in hardware, whereas the DB can only take a +-- snapshot that then needs to be examined via MM. The advandage of the DB +-- is that it can take a snapshot of the values of the received data. The +-- DB requires RAM resources and the rx_seq does not. +-- +-- Block diagram: +-- +-- g_use_db +-- g_buf_use_sync +-- . +-- . g_use_tx_seq +-- . . +-- . . +-- /-------------> Rx seq +-- | . | +-- in_sosi_arr -----*---> DB RAM | +-- in_sync -------------> DB reg | +-- || | +-- || | +-- MM ================================ +-- +-- Remark: +-- . A nice new feature would be to continuously write the DB and to stop +-- writting it on a trigger. This trigger can then eg. be when the rx_seq +-- detects an error. By delaying the trigger somewhat it the DB can then +-- capture some data before and after the trigger event. + +LIBRARY IEEE, common_pkg_lib, technology_lib, dp_pkg_lib, common_ram_lib, mm_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE IEEE.NUMERIC_STD.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; +USE work.diag_pkg.ALL; +USE technology_lib.technology_select_pkg.ALL; + +ENTITY mms_diag_data_buffer IS + GENERIC ( + g_technology : NATURAL := c_tech_select_default; + -- Generate configurations + g_use_db : BOOLEAN := TRUE; + g_use_rx_seq : BOOLEAN := FALSE; + -- General + g_nof_streams : POSITIVE := 16; -- each stream gets an data buffer + -- DB settings + g_data_type : t_diag_data_type_enum := e_data; -- define the sosi field that gets stored: e_data=data, e_complex=im&re, e_real=re, e_imag=im + g_data_w : NATURAL := 32; -- the g_data_w is the width of the data, re, im values or of the combined im&re value + g_buf_nof_data : NATURAL := 1024; -- nof words per data buffer + g_buf_use_sync : BOOLEAN := FALSE; -- when TRUE start filling the buffer at the in_sync, else after the last word was read + -- Rx_seq + g_use_steps : BOOLEAN := FALSE; + g_nof_steps : NATURAL := c_diag_seq_rx_reg_nof_steps; + g_seq_dat_w : NATURAL := 32 -- >= 1, test sequence data width. Choose g_seq_dat_w <= g_data_w + ); + PORT ( + -- System + mm_rst : IN STD_LOGIC; + mm_clk : IN STD_LOGIC; + dp_rst : IN STD_LOGIC; + dp_clk : IN STD_LOGIC; + -- MM interface + reg_data_buf_mosi : IN t_mem_mosi := c_mem_mosi_rst; -- DB control register (one per stream) + reg_data_buf_miso : OUT t_mem_miso; + + ram_data_buf_mosi : IN t_mem_mosi := c_mem_mosi_rst; -- DB buffer RAM (one per streams) + ram_data_buf_miso : OUT t_mem_miso; + + reg_rx_seq_mosi : IN t_mem_mosi := c_mem_mosi_rst; -- Rx seq control register (one per streams) + reg_rx_seq_miso : OUT t_mem_miso; + + -- ST interface + in_sync : IN STD_LOGIC := '0'; -- input sync pulse in ST dp_clk domain that starts data buffer when g_use_in_sync = TRUE + in_sosi_arr : IN t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) + ); +END mms_diag_data_buffer; + +ARCHITECTURE str OF mms_diag_data_buffer IS + + CONSTANT c_buf_mm_factor : NATURAL := ceil_div(g_data_w, c_word_w); + CONSTANT c_buf_nof_data_mm : NATURAL := g_buf_nof_data*c_buf_mm_factor; + + CONSTANT c_buf_adr_w : NATURAL := ceil_log2(c_buf_nof_data_mm); + CONSTANT c_reg_adr_w : NATURAL := c_diag_db_reg_adr_w; + + TYPE t_data_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_data_w-1 DOWNTO 0); + + SIGNAL in_data_arr : t_data_arr(g_nof_streams-1 DOWNTO 0); + + SIGNAL ram_data_buf_mosi_arr : t_mem_mosi_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL ram_data_buf_miso_arr : t_mem_miso_arr(g_nof_streams-1 DOWNTO 0); + + SIGNAL reg_data_buf_mosi_arr : t_mem_mosi_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL reg_data_buf_miso_arr : t_mem_miso_arr(g_nof_streams-1 DOWNTO 0); + +BEGIN + + no_db : IF g_use_db=FALSE GENERATE + ram_data_buf_miso <= c_mem_miso_rst; + reg_data_buf_miso <= c_mem_miso_rst; + END GENERATE; + + gen_db : IF g_use_db=TRUE GENERATE + -- Combine the internal array of mm interfaces for the data_buf to one array that is connected to the port of the MM bus + u_mem_mux_data_buf : ENTITY mm_lib.common_mem_mux + GENERIC MAP ( + g_nof_mosi => g_nof_streams, + g_mult_addr_w => c_buf_adr_w + ) + PORT MAP ( + mosi => ram_data_buf_mosi, + miso => ram_data_buf_miso, + mosi_arr => ram_data_buf_mosi_arr, + miso_arr => ram_data_buf_miso_arr + ); + + u_mem_mux_reg : ENTITY mm_lib.common_mem_mux + GENERIC MAP ( + g_nof_mosi => g_nof_streams, + g_mult_addr_w => c_reg_adr_w + ) + PORT MAP ( + mosi => reg_data_buf_mosi, + miso => reg_data_buf_miso, + mosi_arr => reg_data_buf_mosi_arr, + miso_arr => reg_data_buf_miso_arr + ); + + gen_stream : FOR I IN 0 TO g_nof_streams-1 GENERATE + in_data_arr(I) <= in_sosi_arr(I).im(g_data_w/2-1 DOWNTO 0) & in_sosi_arr(I).re(g_data_w/2-1 DOWNTO 0) WHEN g_data_type=e_complex ELSE + in_sosi_arr(I).re(g_data_w-1 DOWNTO 0) WHEN g_data_type=e_real ELSE + in_sosi_arr(I).im(g_data_w-1 DOWNTO 0) WHEN g_data_type=e_imag ELSE + in_sosi_arr(I).data(g_data_w-1 DOWNTO 0); -- g_data_type=e_data is default + + u_diag_data_buffer : ENTITY work.diag_data_buffer + GENERIC MAP ( + g_technology => g_technology, + g_data_w => g_data_w, + g_nof_data => g_buf_nof_data, + g_use_in_sync => g_buf_use_sync -- when TRUE start filling the buffer at the in_sync, else after the last word was read + ) + PORT MAP ( + -- Memory-mapped clock domain + mm_rst => mm_rst, + mm_clk => mm_clk, + + ram_mm_mosi => ram_data_buf_mosi_arr(I), + ram_mm_miso => ram_data_buf_miso_arr(I), + + reg_mm_mosi => reg_data_buf_mosi_arr(I), + reg_mm_miso => reg_data_buf_miso_arr(I), + + -- Streaming clock domain + st_rst => dp_rst, + st_clk => dp_clk, + + in_data => in_data_arr(I), + in_sync => in_sync, + in_val => in_sosi_arr(I).valid + ); + END GENERATE; + END GENERATE; + + no_rx_seq : IF g_use_rx_seq=FALSE GENERATE + reg_rx_seq_miso <= c_mem_miso_rst; + END GENERATE; + + gen_rx_seq : IF g_use_rx_seq=TRUE GENERATE + u_mms_diag_rx_seq : ENTITY work.mms_diag_rx_seq + GENERIC MAP ( + g_nof_streams => g_nof_streams, + g_use_steps => g_use_steps, + g_nof_steps => g_nof_steps, + g_seq_dat_w => g_seq_dat_w, -- >= 1, test sequence data width + g_data_w => g_data_w -- >= g_seq_dat_w, user data width + ) + PORT MAP ( + -- Clocks and reset + mm_rst => mm_rst, + mm_clk => mm_clk, + dp_rst => dp_rst, + dp_clk => dp_clk, + + -- Memory Mapped Slave + reg_mosi => reg_rx_seq_mosi, -- multiplexed port for g_nof_streams MM control/status registers + reg_miso => reg_rx_seq_miso, + + -- Streaming interface + rx_snk_in_arr => in_sosi_arr + ); + END GENERATE; + +END str;
trunk/mms_diag_data_buffer.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mms_diag_rx_seq.vhd =================================================================== --- trunk/mms_diag_rx_seq.vhd (nonexistent) +++ trunk/mms_diag_rx_seq.vhd (revision 2) @@ -0,0 +1,323 @@ + ------------------------------------------------------------------------------- +-- +-- Copyright (C) 2015 +-- 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: Provide MM access via slave register to diag_rx_seq +-- Description: +-- +-- Each DP stream has its own diag_rx_seq and its own MM control register. +-- The MM control registers are accessible via a single MM port thanks to +-- the common_mem_mux. Each single MM control register is defined as: +-- +-- 31 24 23 16 15 8 7 0 wi +-- |-----------------|-----------------|-----------------|-----------------| +-- | diag_sel = [1], diag_en = [0] | 0 RW +-- |-----------------------------------------------------------------------| +-- | res_val_n = [1], res_ok_n = [0] | 1 RO +-- |-----------------------------------------------------------------------| +-- | rx_cnt[31:0] | 2 RO +-- |-----------------------------------------------------------------------| +-- | rx_sample[g_seq_dat_w-1:0] | 3 RO +-- |-----------------------------------------------------------------------| +-- | diag_steps_arr[0][g_seq_dat_w-1:0] | 4 RW +-- |-----------------------------------------------------------------------| +-- | diag_steps_arr[1][g_seq_dat_w-1:0] | 5 RW +-- |-----------------------------------------------------------------------| +-- | diag_steps_arr[2][g_seq_dat_w-1:0] | 6 RW +-- |-----------------------------------------------------------------------| +-- | diag_steps_arr[3][g_seq_dat_w-1:0] | 7 RW +-- |-----------------------------------------------------------------------| +-- +-- . g_nof_streams +-- The MM control register for stream I in 0:g_nof_streams-1 starts at word +-- index wi = I * 2**c_mm_reg.adr_w. +-- +-- . diag_en +-- '0' = stop and reset input sequence verification +-- '1' = enable input sequence verification +-- +-- . diag_sel +-- '0' = verify PSRG data +-- '1' = verify CNTR data +-- +-- . Results +-- When res_val_n = '1' then no valid data is being received. When +-- res_val_n = '0' then at least two valid data have been received so the +-- diag_rx_seq can detect whether the subsequent data is ok. When res_ok_n +-- = '0' then indeed all data that has been received so far is correct. +-- When res_ok_n = '1' then at least 1 data word was received with errors. +-- Once res_ok_n goes high it remains high. +-- +-- . g_data_w and g_seq_dat_w +-- The DP streaming data field is c_dp_stream_data_w bits wide but only +-- g_data_w bits are used. The g_seq_dat_w must be >= 1 and <= g_data_w. +-- If g_seq_dat_w < g_data_w then the data carries replicated copies of +-- the g_seq_dat_w. The maximum g_seq_dat_w depends on the pseudo random +-- data width of the LFSR sequeces in common_lfsr_sequences_pkg and on +-- whether timing closure can still be achieved for wider g_seq_dat_w. +-- Thanks to the replication a smaller g_seq_dat_w can be used to provide +-- CNTR or LFSR data for the DP data. If the higher bits do notmatch the +-- sequence in the lower bits, then the rx data is forced to -1, and that +-- will then be detected and reported by u_diag_rx_seq as a sequence error. +-- +-- . rx_cnt +-- Counts the number of valid input data that was received since diag_en +-- went active. An incrementing rx_cnt shows that data is being received. +-- +-- . rx_sample +-- The rx_sample keeps the last valid in_dat value. When diag_en='0' it is +-- reset to 0. Reading rx_sample via MM gives an impression of the valid +-- in_dat activity. +-- +-- . g_use_steps +-- When g_use_steps=FALSE then diag_sel selects whether PSRG or COUNTER +-- data with increment +1 is used to verify the input data. +-- When g_use_steps=TRUE then the g_nof_steps = +-- c_diag_seq_rx_reg_nof_steps = 4 MM step registers define the allowed +-- COUNTER increment values. + +LIBRARY IEEE, common_pkg_lib, dp_pkg_lib, mm_lib, common_ram_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE mm_lib.common_field_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; +USE work.diag_pkg.ALL; + +ENTITY mms_diag_rx_seq IS + GENERIC ( + g_nof_streams : NATURAL := 1; + g_use_steps : BOOLEAN := FALSE; + g_nof_steps : NATURAL := c_diag_seq_rx_reg_nof_steps; + g_seq_dat_w : NATURAL := c_word_w; -- >= 1, test sequence data width + g_data_w : NATURAL := c_word_w -- >= g_seq_dat_w, user data width + ); + PORT ( + -- Clocks and reset + mm_rst : IN STD_LOGIC; -- reset synchronous with mm_clk + mm_clk : IN STD_LOGIC; -- MM bus clock + dp_rst : IN STD_LOGIC; -- reset synchronous with dp_clk + dp_clk : IN STD_LOGIC; -- DP streaming bus clock + + -- Memory Mapped Slave + reg_mosi : IN t_mem_mosi; -- multiplexed port for g_nof_streams MM control/status registers + reg_miso : OUT t_mem_miso; + + -- Streaming interface + rx_snk_in_arr : IN t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) + ); +END mms_diag_rx_seq; + + +ARCHITECTURE str OF mms_diag_rx_seq IS + + -- Define MM slave register size + CONSTANT c_mm_reg : t_c_mem := (latency => 1, + adr_w => c_diag_seq_rx_reg_adr_w, + dat_w => c_word_w, -- Use MM bus data width = c_word_w = 32 for all MM registers + nof_dat => c_diag_seq_rx_reg_nof_dat, + init_sl => '0'); + + -- Define MM slave register fields for Python peripheral using pi_common.py (specify MM register access per word, not per individual bit because mm_fields assumes 1 field per MM word) + CONSTANT c_mm_reg_field_arr : t_common_field_arr(c_mm_reg.nof_dat-1 DOWNTO 0) := ( ( field_name_pad("step_3"), "RW", c_word_w, field_default(0) ), -- [7] = diag_steps_arr[3], c_diag_seq_rx_reg_nof_steps = 4 + ( field_name_pad("step_2"), "RW", c_word_w, field_default(0) ), -- [6] = diag_steps_arr[2] + ( field_name_pad("step_1"), "RW", c_word_w, field_default(0) ), -- [5] = diag_steps_arr[1] + ( field_name_pad("step_0"), "RW", c_word_w, field_default(0) ), -- [4] = diag_steps_arr[0] + ( field_name_pad("rx_sample"), "RO", c_word_w, field_default(0) ), -- [3] + ( field_name_pad("rx_cnt"), "RO", c_word_w, field_default(0) ), -- [2] + ( field_name_pad("result"), "RO", 2, field_default(0) ), -- [1] = result[1:0] = res_val_n & res_ok_n + ( field_name_pad("control"), "RW", 2, field_default(0) )); -- [0] = control[1:0] = diag_sel & diag_en + + CONSTANT c_reg_slv_w : NATURAL := c_mm_reg.nof_dat*c_mm_reg.dat_w; + CONSTANT c_reg_dat_w : NATURAL := smallest(c_word_w, g_seq_dat_w); + + CONSTANT c_nof_steps_wi : NATURAL := c_diag_seq_rx_reg_nof_steps_wi; + + TYPE t_reg_slv_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_reg_slv_w-1 DOWNTO 0); + TYPE t_seq_dat_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_seq_dat_w-1 DOWNTO 0); + TYPE t_data_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_data_w-1 DOWNTO 0); + TYPE t_steps_2arr IS ARRAY (INTEGER RANGE <>) OF t_integer_arr(g_nof_steps-1 DOWNTO 0); + + SIGNAL reg_mosi_arr : t_mem_mosi_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL reg_miso_arr : t_mem_miso_arr(g_nof_streams-1 DOWNTO 0); + + -- Registers in dp_clk domain + SIGNAL ctrl_reg_arr : t_reg_slv_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); + SIGNAL stat_reg_arr : t_reg_slv_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); + + SIGNAL diag_en_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL diag_sel_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL diag_steps_2arr : t_steps_2arr(g_nof_streams-1 DOWNTO 0); + + SIGNAL rx_cnt_arr : t_slv_32_arr(g_nof_streams-1 DOWNTO 0); -- can use t_slv_32_arr because c_mm_reg.dat_w = c_word_w = 32 fixed + SIGNAL rx_sample_arr : t_seq_dat_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL rx_sample_diff_arr : t_seq_dat_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL rx_sample_val_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL rx_seq_arr : t_seq_dat_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL rx_seq_val_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL rx_data_arr : t_data_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL rx_data_val_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + + SIGNAL diag_res_arr : t_seq_dat_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL diag_res_val_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + + SIGNAL stat_res_ok_n_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL stat_res_val_n_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + +BEGIN + + ASSERT g_data_w >= g_seq_dat_w REPORT "mms_diag_rx_seq: g_data_w < g_seq_dat_w is not allowed." SEVERITY FAILURE; + + gen_nof_streams: FOR I IN 0 to g_nof_streams-1 GENERATE + + -- no unreplicate needed + gen_one : IF g_data_w = g_seq_dat_w GENERATE + rx_seq_arr(I) <= rx_snk_in_arr(i).data(g_seq_dat_w-1 DOWNTO 0); + rx_seq_val_arr(I) <= rx_snk_in_arr(i).valid; + END GENERATE; + + -- unreplicate needed + gen_unreplicate : IF g_data_w > g_seq_dat_w GENERATE + -- keep sequence in low bits and set high bits to '1' if they mismatch the corresponding bit in the sequence + rx_data_arr(I) <= UNREPLICATE_DP_DATA(rx_snk_in_arr(i).data(g_data_w-1 DOWNTO 0), g_seq_dat_w); + rx_data_val_arr(I) <= rx_snk_in_arr(i).valid; + + -- keep sequence in low bits if the high bits match otherwise force low bits value to -1 to indicate the mismatch + p_rx_seq : PROCESS(dp_clk) + BEGIN + IF rising_edge(dp_clk) THEN -- register to ease timing closure + IF UNSIGNED(rx_data_arr(I)(g_data_w-1 DOWNTO g_seq_dat_w))=0 THEN + rx_seq_arr(I) <= rx_data_arr(I)(g_seq_dat_w-1 DOWNTO 0); + ELSE + rx_seq_arr(I) <= TO_SVEC(-1, g_seq_dat_w); + END IF; + rx_seq_val_arr(I) <= rx_data_val_arr(I); + END IF; + END PROCESS; + END GENERATE; + + -- detect rx sequence errors + u_diag_rx_seq: ENTITY WORK.diag_rx_seq + GENERIC MAP ( + g_use_steps => g_use_steps, + g_nof_steps => g_nof_steps, + g_cnt_w => c_word_w, + g_dat_w => g_seq_dat_w, + g_diag_res_w => g_seq_dat_w -- do not use g_seq_dat_w+1 to include NOT diag_res_val in MSbit, instead use diag_res_val output + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + + -- Write and read back registers: + diag_en => diag_en_arr(I), + diag_sel => diag_sel_arr(I), + diag_steps_arr => diag_steps_2arr(I), + + -- Read only registers: + diag_res => diag_res_arr(I), + diag_res_val => diag_res_val_arr(I), + diag_sample => rx_sample_arr(I), + diag_sample_diff => rx_sample_diff_arr(I), + diag_sample_val => rx_sample_val_arr(I), + + -- Streaming + in_cnt => rx_cnt_arr(I), + in_dat => rx_seq_arr(I), + in_val => rx_seq_val_arr(I) + ); + + -- Map diag_res to single bit and register it to ease timing closure + stat_res_ok_n_arr(I) <= orv(diag_res_arr(I)) WHEN rising_edge(dp_clk); + stat_res_val_n_arr(I) <= NOT diag_res_val_arr(I) WHEN rising_edge(dp_clk); + + -- Register mapping + -- . write ctrl_reg_arr + diag_en_arr(I) <= ctrl_reg_arr(I)(0); -- address 0, data bit [0] + diag_sel_arr(I) <= ctrl_reg_arr(I)(1); -- address 0, data bit [1] + + gen_diag_steps_2arr : FOR J IN 0 TO g_nof_steps-1 GENERATE + diag_steps_2arr(I)(J) <= TO_SINT(ctrl_reg_arr(I)(c_reg_dat_w-1 + (c_nof_steps_wi+J)*c_word_w DOWNTO (c_nof_steps_wi+J)*c_word_w)); -- address 4, 5, 6, 7 + END GENERATE; + + -- . read stat_reg_arr + p_stat_reg_arr : PROCESS(ctrl_reg_arr, stat_res_ok_n_arr, stat_res_val_n_arr, rx_cnt_arr, rx_sample_arr) + BEGIN + -- Default write / readback: + stat_reg_arr(I) <= ctrl_reg_arr(I); -- default control read back + -- Status read only: + stat_reg_arr(I)( 0+1*c_word_w) <= stat_res_ok_n_arr(I); -- address 1, data bit [0] + stat_reg_arr(I)( 1+1*c_word_w) <= stat_res_val_n_arr(I); -- address 1, data bit [1] + stat_reg_arr(I)(3*c_word_w-1 DOWNTO 2*c_word_w) <= rx_cnt_arr(I); -- address 2: read rx_cnt per stream + stat_reg_arr(I)(4*c_word_w-1 DOWNTO 3*c_word_w) <= RESIZE_UVEC(rx_sample_arr(I), c_word_w); -- address 3: read valid sample per stream + END PROCESS; + + u_reg : ENTITY mm_lib.common_reg_r_w_dc + GENERIC MAP ( + g_cross_clock_domain => TRUE, + g_readback => FALSE, -- must use FALSE for write/read or read only register when g_cross_clock_domain=TRUE + g_reg => c_mm_reg + ) + PORT MAP ( + -- Clocks and reset + mm_rst => mm_rst, + mm_clk => mm_clk, + st_rst => dp_rst, + st_clk => dp_clk, + + -- Memory Mapped Slave in mm_clk domain + sla_in => reg_mosi_arr(I), + sla_out => reg_miso_arr(I), + + -- MM registers in dp_clk domain + in_reg => stat_reg_arr(I), + out_reg => ctrl_reg_arr(I) + ); + END GENERATE; + + -- Combine the internal array of mm interfaces for the bg_data to one array that is connected to the port of the MM bus + u_mem_mux : ENTITY mm_lib.common_mem_mux + GENERIC MAP ( + g_nof_mosi => g_nof_streams, + g_mult_addr_w => c_mm_reg.adr_w + ) + PORT MAP ( + mosi => reg_mosi, + miso => reg_miso, + mosi_arr => reg_mosi_arr, + miso_arr => reg_miso_arr + ); + +END str; + + + + + + + + + + + + +
trunk/mms_diag_rx_seq.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mms_diag_tx_seq.vhd =================================================================== --- trunk/mms_diag_tx_seq.vhd (nonexistent) +++ trunk/mms_diag_tx_seq.vhd (revision 2) @@ -0,0 +1,401 @@ + ------------------------------------------------------------------------------- +-- +-- Copyright (C) 2015 +-- 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: Provide MM access via slave register to diag_tx_seq +-- Description: +-- +-- Each DP stream has its own diag_tx_seq, because each stream can have its +-- own flow control. Each DP stream also has its own MM control register to +-- support reading tx_cnt per stream. +-- +-- 31 24 23 16 15 8 7 0 wi +-- |-----------------|-----------------|-----------------|-----------------| +-- | diag_dc = [2], diag_sel = [1], diag_en = [0] | 0 RW +-- |-----------------------------------------------------------------------| +-- | diag_init[31:0] | 1 RW +-- |-----------------------------------------------------------------------| +-- | tx_cnt[31:0] | 2 RO +-- |-----------------------------------------------------------------------| +-- | diag_mod[31:0] | 3 RW +-- |-----------------------------------------------------------------------| +-- +-- . g_use_usr_input +-- When diag_en='0' then the usr_sosi_arr input is passed on. +-- When diag_en='1' then the the tx_seq data overrules the usr_sosi_arr. Dependent on g_use_usr_input +-- the overule differs: +-- +-- 1) When g_use_usr_input=TRUE then usr_sosi_arr().valid sets the pace else +-- 2) when g_use_usr_input=FALSE then tx_src_in_arr().ready sets the pace of the valid output data. +-- +-- This scheme allows filling user data with Tx seq data using the user valid or to completely +-- overrule the user by deriving the Tx seq valid directly from the ready. +-- +-- g_use_usr_input=FALSE : +-- +-- g_nof_streams +-- c_latency=1 +-- . +-- . +-- usr_snk_out_arr <-------------------/------------------------------ tx_src_in_arr +-- usr_snk_in_arr --------------------|---------------->|\ +-- . | |0| +-- ______ | | |---------> tx_src_out_arr +-- | | |.ready | | +-- |diag |<----/ |1| +-- |tx_seq|---------------------->|/ +-- |______| . | +-- __|___ . | +-- |u_reg | tx_seq_src_in_arr | +-- |______| tx_seq_src_out_arr | +-- __|___ | +-- | mux | diag_en_arr +-- |______| +-- | +-- MM ================= +-- +-- +-- g_use_usr_input=TRUE : +-- g_nof_streams +-- c_latency=0 +-- . +-- . ____ +-- usr_snk_out_arr ------------------------------------------------| |<-- tx_src_in_arr +-- usr_snk_in_arr -----------------------\------------>|\ |dp | +-- . | |0| |pipe| +-- ______ valid | | |------->|line|--> tx_src_out_arr +-- |diag |<-------/ |1| . |arr | +-- |tx_seq|--------------------->|/ . |____| +-- |______| . | . +-- __|___ . | mux_seq_src_in_arr +-- |u_reg | tx_seq_src_in_arr | mux_seq_src_out_arr +-- |______| tx_seq_src_out_arr | +-- __|___ | +-- | mux | diag_en_arr +-- |______| +-- | +-- MM ================= +-- +-- +-- . g_nof_streams +-- The MM control register for stream I in 0:g_nof_streams-1 starts at word +-- index wi = I * 2**c_mm_reg.adr_w. +-- +-- . g_mm_broadcast +-- Use default g_mm_broadcast=FALSE for multiplexed individual MM access to +-- each reg_mosi_arr/reg_miso_arr MM port. When g_mm_broadcast=TRUE then a +-- write access to MM port [0] is passed on to all ports and a read access +-- is done from MM port [0]. The other MM array ports cannot be read then. +-- +-- . g_seq_dat_w +-- The g_seq_dat_w must be >= 1. The DP streaming data field is +-- c_dp_stream_data_w bits wide and the REPLICATE_DP_DATA() is used to wire +-- the g_seq_dat_w from the u_diag_tx_seq to fill the entire DP data width. +-- The maximum g_seq_dat_w depends on the pseudo random data width of the +-- LFSR sequeces in common_lfsr_sequences_pkg and on whether timing closure +-- can still be achieved for wider g_seq_dat_w. Thanks to the replication a +-- smaller g_seq_dat_w can be used to provide CNTR or LFSR data for the DP +-- data. +-- +-- . diag_en +-- '0' = init and disable output sequence +-- '1' = enable output sequence +-- +-- . diag_sel +-- '0' = generate PSRG data +-- '1' = generate CNTR data +-- +-- . diag_dc +-- '0' = Output sequence data (as selected by diag_sel) +-- '1' = Output constant data (value as set by diag_init) +-- +-- . diag_init +-- Note that MM diag_init has c_word_w=32 bits, so if g_seq_dat_w is wider +-- then the MSbits are 0 and if it is smaller, then the MSbits are ignored. +-- +-- . tx_cnt +-- Counts the number of valid output data that was transmitted on stream 0 +-- since diag_en went active. An incrementing tx_cnt shows that data is +-- being transmitted. +-- +-- . diag_mod +-- CNTR counts modulo diag_mod, so diag_mod becomes 0. Use diag_mod = 0 +-- for default binary wrap at 2**g_seq_dat_w. For diag_rx_seq choose +-- diag_step = 2**g_seq_dat_w - diag_mod + g_cnt_incr to verify ok as +-- simulated with tb_tb_diag_rx_seq. In this mms_diag_tx_seq g_cnt_incr=1 +-- fixed for diag_tx_seq. +-- The default diag_mod=0 is equivalent to diag_mod=2**g_seq_dat_w. +-- Using diag_mod < 2**g_seq_dat_w can be useful to generate tx seq CNTR +-- data that is written to a memory that is larger than 2**g_seq_dat_w +-- addresses. The CNTR values then differ from the memory address values, +-- which can be useful to ensure that reading e.g. address 2**g_seq_dat_w +-- yields a different CNTR value than reading 2**(g_seq_dat_w+1). + + +LIBRARY IEEE, common_pkg_lib, dp_pkg_lib, dp_pipeline_lib, common_ram_lib, mm_lib; -- init value for out_dat when diag_en = '0' +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE mm_lib.common_field_pkg.ALL; +USE dp_pkg_lib.dp_stream_pkg.ALL; +USE work.diag_pkg.ALL; + +ENTITY mms_diag_tx_seq IS + GENERIC ( + g_use_usr_input : BOOLEAN := FALSE; + g_mm_broadcast : BOOLEAN := FALSE; + g_nof_streams : NATURAL := 1; + g_seq_dat_w : NATURAL := c_word_w -- >= 1, test sequence data width + ); + PORT ( + -- Clocks and reset + mm_rst : IN STD_LOGIC; -- reset synchronous with mm_clk + mm_clk : IN STD_LOGIC; -- MM bus clock + dp_rst : IN STD_LOGIC; -- reset synchronous with dp_clk + dp_clk : IN STD_LOGIC; -- DP streaming bus clock + + -- MM interface + reg_mosi : IN t_mem_mosi; -- single MM control register applied to all g_nof_streams + reg_miso : OUT t_mem_miso; + + -- DP streaming interface + usr_snk_out_arr : OUT t_dp_siso_arr(g_nof_streams-1 DOWNTO 0); + usr_snk_in_arr : IN t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>c_dp_sosi_rst); + tx_src_out_arr : OUT t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0); + tx_src_in_arr : IN t_dp_siso_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>c_dp_siso_rdy) -- Default xon='1'; + ); +END mms_diag_tx_seq; + + +ARCHITECTURE str OF mms_diag_tx_seq IS + + -- Define MM slave register size + CONSTANT c_mm_reg : t_c_mem := (latency => 1, + adr_w => c_diag_seq_tx_reg_adr_w, + dat_w => c_word_w, -- Use MM bus data width = c_word_w = 32 for all MM registers + nof_dat => c_diag_seq_tx_reg_nof_dat, + init_sl => '0'); + + -- Define MM slave register fields for Python peripheral using pi_common.py (specify MM register access per word, not per individual bit because mm_fields assumes 1 field per MM word) + CONSTANT c_mm_reg_field_arr : t_common_field_arr(c_mm_reg.nof_dat-1 DOWNTO 0) := ( ( field_name_pad("modulo"), "RW", c_word_w, field_default(0) ), + ( field_name_pad("tx_cnt"), "RO", c_word_w, field_default(0) ), + ( field_name_pad("init"), "RW", c_word_w, field_default(0) ), + ( field_name_pad("control"), "RW", 3, field_default(0) )); -- control[2:0] = diag_dc & diag_sel & diag_en + + CONSTANT c_reg_slv_w : NATURAL := c_mm_reg.nof_dat*c_mm_reg.dat_w; + + CONSTANT c_latency : NATURAL := sel_a_b(g_use_usr_input, 0, 1); -- default 1 for registered diag_tx_seq out_cnt/dat/val output, use 0 for immediate combinatorial diag_tx_seq out_cnt/dat/val output + + TYPE t_reg_slv_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_reg_slv_w-1 DOWNTO 0); + TYPE t_seq_dat_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(g_seq_dat_w-1 DOWNTO 0); + TYPE t_replicate_arr IS ARRAY (INTEGER RANGE <>) OF STD_LOGIC_VECTOR(c_dp_stream_data_w-1 DOWNTO 0); + + SIGNAL reg_mosi_arr : t_mem_mosi_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL reg_miso_arr : t_mem_miso_arr(g_nof_streams-1 DOWNTO 0); + + -- Registers in dp_clk domain + SIGNAL ctrl_reg_arr : t_reg_slv_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); + SIGNAL stat_reg_arr : t_reg_slv_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); + + SIGNAL diag_en_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL diag_sel_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL diag_dc_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + + SIGNAL diag_init_mm_arr : t_slv_32_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); -- can use t_slv_32_arr because c_mm_reg.dat_w = c_word_w = 32 fixed + SIGNAL diag_init_arr : t_seq_dat_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); + + SIGNAL diag_mod_mm_arr : t_slv_32_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); -- can use t_slv_32_arr because c -- init value for out_dat when diag_en = '0'_mm_reg.dat_w = c_word_w = 32 fixed + SIGNAL diag_mod_arr : t_seq_dat_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>(OTHERS=>'0')); + + SIGNAL tx_cnt_arr : t_slv_32_arr(g_nof_streams-1 DOWNTO 0); -- can use t_slv_32_arr because c_mm_reg.dat_w = c_word_w = 32 fixed + SIGNAL tx_dat_arr : t_seq_dat_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL tx_val_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + SIGNAL tx_req_arr : STD_LOGIC_VECTOR(g_nof_streams-1 DOWNTO 0); + + SIGNAL tx_replicate_dat_arr : t_dp_data_slv_arr(g_nof_streams-1 DOWNTO 0); + + SIGNAL tx_seq_src_in_arr : t_dp_siso_arr(g_nof_streams-1 DOWNTO 0); + SIGNAL tx_seq_src_out_arr : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0) := (OTHERS=>c_dp_sosi_rst); -- default set all other fields then data and valid to inactive. + + -- Use user input or self generate + SIGNAL mux_seq_src_in_arr : t_dp_siso_arr(g_nof_streams-1 DOWNTO 0); -- multiplex user sosi control with tx_seq data + SIGNAL mux_seq_src_out_arr : t_dp_sosi_arr(g_nof_streams-1 DOWNTO 0); + +BEGIN + + gen_nof_streams: FOR I IN 0 to g_nof_streams-1 GENERATE + u_diag_tx_seq: ENTITY WORK.diag_tx_seq + GENERIC MAP ( + g_latency => c_latency, + g_cnt_w => c_word_w, + g_dat_w => g_seq_dat_w + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + + -- Write and read back registers: + diag_en => diag_en_arr(I), + diag_sel => diag_sel_arr(I), + diag_dc => diag_dc_arr(I), + diag_init => diag_init_arr(I), + diag_mod => diag_mod_arr(I), + + -- Streaming + diag_req => tx_req_arr(I), + out_cnt => tx_cnt_arr(I), + out_dat => tx_dat_arr(I), + out_val => tx_val_arr(I) + ); + + tx_req_arr(I) <= tx_seq_src_in_arr(I).ready; + + tx_replicate_dat_arr(I) <= REPLICATE_DP_DATA(tx_dat_arr(I)); + + -- for some reason the intermediate tx_replicate_dat_arr() signal is needed, otherwise the assignment to the tx_seq_src_out_arr().data field remains void in the Wave window + tx_seq_src_out_arr(I).data <= tx_replicate_dat_arr(I); + tx_seq_src_out_arr(I).valid <= tx_val_arr(I); + + -- Register mapping + diag_en_arr(I) <= ctrl_reg_arr(I)( 0); -- address 0, data bit [0] + diag_sel_arr(I) <= ctrl_reg_arr(I)( 1); -- address 0, data bit [1] + diag_dc_arr(I) <= ctrl_reg_arr(I)( 2); -- address 0, data bit [2] + diag_init_mm_arr(I) <= ctrl_reg_arr(I)(2*c_word_w-1 DOWNTO c_word_w); -- address 1, data bits [31:0] + diag_mod_mm_arr(I) <= ctrl_reg_arr(I)(4*c_word_w-1 DOWNTO 3*c_word_w); -- address 3, data bits [31:0] + + diag_init_arr(I) <= RESIZE_UVEC(diag_init_mm_arr(I), g_seq_dat_w); + diag_mod_arr(I) <= RESIZE_UVEC(diag_mod_mm_arr(I), g_seq_dat_w); + + p_stat_reg : PROCESS(ctrl_reg_arr(I), tx_cnt_arr) + BEGIN + -- Default write / readback: + stat_reg_arr(I) <= ctrl_reg_arr(I); -- address 0, 1: control read back + -- Status read only: + stat_reg_arr(I)(3*c_word_w-1 DOWNTO 2*c_word_w) <= tx_cnt_arr(I); -- address 2: read tx_cnt + END PROCESS; + + u_reg : ENTITY mm_lib.common_reg_r_w_dc + GENERIC MAP ( + g_cross_clock_domain => TRUE, + g_readback => FALSE, -- must use FALSE for write/read or read only register when g_cross_clock_domain=TRUE + g_reg => c_mm_reg + ) + PORT MAP ( + -- Clocks and reset + mm_rst => mm_rst, + mm_clk => mm_clk, + st_rst => dp_rst, + st_clk => dp_clk, + + -- Memory Mapped Slave in mm_clk domain + sla_in => reg_mosi_arr(I), + sla_out => reg_miso_arr(I), + + -- MM registers in dp_clk domain + in_reg => stat_reg_arr(I), -- connect out_reg to in_reg for write and readback register + out_reg => ctrl_reg_arr(I) + ); + END GENERATE; + + -- Combine the internal array of mm interfaces for the bg_data to one array that is connected to the port of the MM bus + u_mem_mux : ENTITY mm_lib.common_mem_mux + GENERIC MAP ( + g_broadcast => g_mm_broadcast, + g_nof_mosi => g_nof_streams, + g_mult_addr_w => c_mm_reg.adr_w + ) + PORT MAP ( + mosi => reg_mosi, + miso => reg_miso, + mosi_arr => reg_mosi_arr, + miso_arr => reg_miso_arr + ); + + ignore_usr_input : IF g_use_usr_input=FALSE GENERATE + -- flow control + usr_snk_out_arr <= tx_src_in_arr; + tx_seq_src_in_arr <= tx_src_in_arr; + + -- data + p_tx_src_out_arr : PROCESS (usr_snk_in_arr, tx_seq_src_out_arr, diag_en_arr) + BEGIN + tx_src_out_arr <= usr_snk_in_arr; -- Default pass on the usr data + FOR I IN 0 TO g_nof_streams-1 LOOP + IF diag_en_arr(I)='1' THEN + tx_src_out_arr(I) <= tx_seq_src_out_arr(I); -- When diag is enabled then pass on the Tx seq data + END IF; + END LOOP; + END PROCESS; + END GENERATE; + + use_usr_input : IF g_use_usr_input=TRUE GENERATE + -- Request tx_seq data at user data valid rate + p_tx_seq_src_in_arr : PROCESS(usr_snk_in_arr) + BEGIN + FOR I IN 0 TO g_nof_streams-1 LOOP + tx_seq_src_in_arr(I).ready <= usr_snk_in_arr(I).valid; + END LOOP; + END PROCESS; + + -- Default output the user input or BG data, else when tx_seq is enabled overrule output with tx_seq data + usr_snk_out_arr <= mux_seq_src_in_arr; + + p_mux_seq_src_out_arr : PROCESS (usr_snk_in_arr, tx_seq_src_out_arr, diag_en_arr) + BEGIN + mux_seq_src_out_arr <= usr_snk_in_arr; + FOR I IN 0 TO g_nof_streams-1 LOOP + IF diag_en_arr(I)='1' THEN + mux_seq_src_out_arr(I).data <= tx_seq_src_out_arr(I).data; + END IF; + END LOOP; + END PROCESS; + + -- Pipeline the streams by 1 to register the mux_seq_src_out_arr data to ease timing closure given that c_tx_seq_latency=0 + u_dp_pipeline_arr : ENTITY dp_pipeline_lib.dp_pipeline_arr + GENERIC MAP ( + g_nof_streams => g_nof_streams + ) + PORT MAP ( + rst => dp_rst, + clk => dp_clk, + -- ST sink + snk_out_arr => mux_seq_src_in_arr, + snk_in_arr => mux_seq_src_out_arr, + -- ST source + src_in_arr => tx_src_in_arr, + src_out_arr => tx_src_out_arr + ); + END GENERATE; + +END str; + + + + + + + + + + + + +
trunk/mms_diag_tx_seq.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.