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

Subversion Repositories astron_mm

Compare Revisions

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

Rev 1 → Rev 2

/trunk/common_field_pkg.vhd
0,0 → 1,343
-------------------------------------------------------------------------------
--
-- Copyright (C) 2013
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU General Public License for more details.
--
-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
--
-------------------------------------------------------------------------------
 
LIBRARY IEEE, common_pkg_lib;
USE IEEE.STD_LOGIC_1164.ALL;
USE IEEE.NUMERIC_STD.ALL;
USE common_pkg_lib.common_pkg.ALL;
USE common_pkg_lib.common_str_pkg.ALL;
 
-- Purpose:
-- . Dynamically map record-like field structures onto SLVs.
-- Description:
-- . The MM register is defined by mm_fields.vhd.
-- . The MM register consists of "RO" = input fields (status) and "RW" = output fields (control) in
-- arbitrary order. The entire register is kept in a word_arr slv. The functions can extract the
-- "RO" fields into a slv_in and the "RW" fields into a slv_out. Hence the slv_in'LENGTH +
-- slv_out'LENGTH = word_arr'LENGTH.
--
-- . Advantages:
-- . Replaces non-generic (dedicated) records;
-- . Field widths are variable
-- Remarks:
 
 
PACKAGE common_field_pkg IS
 
CONSTANT c_common_field_name_len : NATURAL := 64;
CONSTANT c_common_field_default_len : NATURAL := 256;
TYPE t_common_field IS RECORD
name : STRING(1 TO c_common_field_name_len);
mode : STRING(1 TO 2);
size : POSITIVE;
default : STD_LOGIC_VECTOR(c_common_field_default_len-1 DOWNTO 0);
END RECORD;
TYPE t_common_field_arr IS ARRAY(INTEGER RANGE <>) OF t_common_field;
 
FUNCTION field_name_pad(name: STRING) RETURN STRING;
FUNCTION field_default(slv_in: STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR;
FUNCTION field_default(nat_in: NATURAL) RETURN STD_LOGIC_VECTOR;
 
FUNCTION field_map_defaults(field_arr : t_common_field_arr) RETURN STD_LOGIC_VECTOR; -- returns slv_out
 
FUNCTION field_mode (field_arr : t_common_field_arr; name: STRING ) RETURN STRING;
FUNCTION field_size (field_arr : t_common_field_arr; name: STRING ) RETURN NATURAL;
FUNCTION field_hi (field_arr : t_common_field_arr; name: STRING ) RETURN INTEGER;
FUNCTION field_hi (field_arr : t_common_field_arr; index: NATURAL ) RETURN NATURAL;
FUNCTION field_lo (field_arr : t_common_field_arr; name: STRING ) RETURN NATURAL;
FUNCTION field_lo (field_arr : t_common_field_arr; index: NATURAL ) RETURN NATURAL;
FUNCTION field_slv_len (field_arr : t_common_field_arr ) RETURN NATURAL;
FUNCTION field_slv_in_len (field_arr : t_common_field_arr ) RETURN NATURAL;
FUNCTION field_slv_out_len (field_arr : t_common_field_arr ) RETURN NATURAL;
FUNCTION field_nof_words (field_arr : t_common_field_arr; word_w : NATURAL ) RETURN NATURAL;
FUNCTION field_map_in (field_arr : t_common_field_arr; slv : STD_LOGIC_VECTOR; word_w : NATURAL ; mode : STRING) RETURN STD_LOGIC_VECTOR; -- returns word_arr
FUNCTION field_map_out (field_arr : t_common_field_arr; word_arr : STD_LOGIC_VECTOR; word_w : NATURAL ) RETURN STD_LOGIC_VECTOR; -- returns slv_out
FUNCTION field_map (field_arr : t_common_field_arr; word_arr_in: STD_LOGIC_VECTOR; word_arr_out: STD_LOGIC_VECTOR; word_w : NATURAL) RETURN STD_LOGIC_VECTOR; -- returns word_arr
 
FUNCTION field_ovr_arr(field_arr : t_common_field_arr; ovr_init: STD_LOGIC_VECTOR) RETURN t_common_field_arr;
 
FUNCTION field_exists(field_arr : t_common_field_arr; name: STRING) RETURN BOOLEAN;
 
FUNCTION field_arr_set_mode(field_arr : t_common_field_arr; mode : STRING) RETURN t_common_field_arr;
 
FUNCTION sel_a_b(sel : BOOLEAN; a, b : t_common_field_arr ) RETURN t_common_field_arr;
 
END common_field_pkg;
 
 
PACKAGE BODY common_field_pkg IS
 
FUNCTION field_name_pad(name: STRING) RETURN STRING IS
BEGIN
RETURN pad(name, c_common_field_name_len, ' ');
END field_name_pad;
 
FUNCTION field_default(slv_in: STD_LOGIC_VECTOR) RETURN STD_LOGIC_VECTOR IS
BEGIN
RETURN RESIZE_UVEC(slv_in, c_common_field_default_len);
END field_default;
 
FUNCTION field_default(nat_in: NATURAL) RETURN STD_LOGIC_VECTOR IS
BEGIN
RETURN TO_UVEC(nat_in, c_common_field_default_len);
END field_default;
 
FUNCTION field_map_defaults(field_arr : t_common_field_arr) RETURN STD_LOGIC_VECTOR IS
VARIABLE v_slv_out : STD_LOGIC_VECTOR(field_slv_out_len(field_arr)-1 DOWNTO 0);
BEGIN
FOR f IN 0 TO field_arr'HIGH LOOP
IF field_arr(f).mode="RW" THEN
v_slv_out( field_hi(field_arr, field_arr(f).name) DOWNTO field_lo(field_arr, field_arr(f).name)) := field_arr(f).default(field_arr(f).size-1 DOWNTO 0);
END IF;
END LOOP;
RETURN v_slv_out;
END field_map_defaults;
 
FUNCTION field_mode(field_arr : t_common_field_arr; name: STRING) RETURN STRING IS
-- Returns the mode string of the passed (via name) field
BEGIN
IF field_exists(field_arr, name) THEN
FOR i IN 0 TO field_arr'HIGH LOOP
IF field_arr(i).name=field_name_pad(name) THEN
RETURN field_arr(i).mode;
END IF;
END LOOP;
ELSE
RETURN "-1";
END IF;
END field_mode;
 
FUNCTION field_size(field_arr : t_common_field_arr; name: STRING) RETURN NATURAL IS
-- Returns the size of the passed (via name) field
BEGIN
FOR i IN 0 TO field_arr'HIGH LOOP
IF field_arr(i).name=field_name_pad(name) THEN
RETURN field_arr(i).size;
END IF;
END LOOP;
END field_size;
 
FUNCTION field_hi(field_arr : t_common_field_arr; name: STRING) RETURN INTEGER IS
-- Returns the high (=left) bit range index of the field within the field_arr interpreted as concatenated IN or OUT SLV
VARIABLE v_acc_hi : NATURAL := 0;
BEGIN
IF field_exists(field_arr, name) THEN
FOR i IN 0 TO field_arr'HIGH LOOP
IF field_arr(i).mode=field_mode(field_arr, name) THEN -- increment index only for the "RO" = IN or the "RW" = OUT
v_acc_hi := v_acc_hi + field_arr(i).size;
IF field_arr(i).name = field_name_pad(name) THEN
RETURN v_acc_hi-1;
END IF;
END IF;
END LOOP;
ELSE --field does not exist; return -1 which results in null array
RETURN -1;
END IF;
END field_hi;
 
FUNCTION field_hi(field_arr : t_common_field_arr; index : NATURAL) RETURN NATURAL IS
-- Returns the high (=left) bit range index of the field within the field_arr interpreted as concatenated SLV
VARIABLE v_acc_hi : NATURAL := 0;
BEGIN
FOR i IN 0 TO index LOOP
v_acc_hi := v_acc_hi + field_arr(i).size;
IF i = index THEN
RETURN v_acc_hi-1;
END IF;
END LOOP;
END field_hi;
 
FUNCTION field_lo(field_arr : t_common_field_arr; name: STRING) RETURN NATURAL IS
-- Returns the low (=right) bit range index of the field within the field_arr interpreted as concatenated IN or OUT SLV
VARIABLE v_acc_hi : NATURAL := 0;
BEGIN
IF field_exists(field_arr, name) THEN
FOR i IN 0 TO field_arr'HIGH LOOP
IF field_arr(i).mode=field_mode(field_arr, name) THEN -- increment index only for the "RO" = IN or the "RW" = OUT
v_acc_hi := v_acc_hi + field_arr(i).size;
IF field_arr(i).name = field_name_pad(name) THEN
RETURN v_acc_hi-field_arr(i).size;
END IF;
END IF;
END LOOP;
ELSE
RETURN 0;
END IF;
END field_lo;
 
FUNCTION field_lo(field_arr : t_common_field_arr; index : NATURAL) RETURN NATURAL IS
-- Returns the low (=right) bit range index of the field within the field_arr interpreted as concatenated SLV
VARIABLE v_acc_hi : NATURAL := 0;
BEGIN
FOR i IN 0 TO index LOOP
v_acc_hi := v_acc_hi + field_arr(i).size;
IF i = index THEN
RETURN v_acc_hi-field_arr(i).size;
END IF;
END LOOP;
END field_lo;
 
FUNCTION field_slv_len(field_arr : t_common_field_arr) RETURN NATURAL IS
-- Return the total length of all fields in field_arr
VARIABLE v_len : NATURAL := 0;
BEGIN
FOR i IN 0 TO field_arr'HIGH LOOP
v_len := v_len + field_arr(i).size;
END LOOP;
RETURN v_len;
END field_slv_len;
 
FUNCTION field_slv_in_len(field_arr : t_common_field_arr) RETURN NATURAL IS
-- Return the total length of the input fields in field_arr (= all "RO")
VARIABLE v_len : NATURAL := 0;
BEGIN
FOR f IN 0 TO field_arr'HIGH LOOP
IF field_arr(f).mode="RO" THEN
v_len := v_len + field_arr(f).size;
END IF;
END LOOP;
RETURN v_len;
END field_slv_in_len;
 
FUNCTION field_slv_out_len(field_arr : t_common_field_arr) RETURN NATURAL IS
-- Return the total length of the output fields in field_arr (= all "RW")
VARIABLE v_len : NATURAL := 0;
BEGIN
FOR f IN 0 TO field_arr'HIGH LOOP
IF field_arr(f).mode="RW" THEN
v_len := v_len + field_arr(f).size;
END IF;
END LOOP;
RETURN v_len;
END field_slv_out_len;
 
FUNCTION field_nof_words(field_arr : t_common_field_arr; word_w : NATURAL) RETURN NATURAL IS
-- Return the number of words (of width word_w) required to hold field_arr
VARIABLE v_word_cnt : NATURAL := 0;
VARIABLE v_nof_reg_words : NATURAL;
BEGIN
FOR f IN 0 TO field_arr'HIGH LOOP
-- Get the number of register words this field spans
v_nof_reg_words := ceil_div(field_arr(f).size, word_w);
FOR w IN 0 TO v_nof_reg_words-1 LOOP
v_word_cnt := v_word_cnt +1;
END LOOP;
END LOOP;
RETURN v_word_cnt;
END field_nof_words;
 
FUNCTION field_map_in(field_arr : t_common_field_arr; slv: STD_LOGIC_VECTOR; word_w : NATURAL; mode : STRING) RETURN STD_LOGIC_VECTOR IS
-- Re-map a field SLV into a larger SLV, support mapping both the slv_in or the slv_out that dependents on mode; each field starting at a word boundary (word_w)
VARIABLE v_word_arr : STD_LOGIC_VECTOR(field_nof_words(field_arr, word_w)*word_w-1 DOWNTO 0) := (OTHERS=>'0');
VARIABLE v_word_cnt : NATURAL := 0;
BEGIN
FOR f IN 0 TO field_arr'HIGH LOOP
-- Only extract the fields that are inputs
IF field_arr(f).mode=mode THEN -- if mode="RO" then slv = slv_in, else if mode="RW" then slv = slv_out
-- Extract the field
v_word_arr( v_word_cnt*word_w+field_arr(f).size-1 DOWNTO v_word_cnt*word_w) := slv( field_hi(field_arr, field_arr(f).name) DOWNTO field_lo(field_arr, field_arr(f).name) );
END IF;
-- Calculate the correct word offset for the next field
v_word_cnt := v_word_cnt + ceil_div(field_arr(f).size, word_w);
END LOOP;
RETURN v_word_arr;
END field_map_in;
 
FUNCTION field_map_out(field_arr : t_common_field_arr; word_arr: STD_LOGIC_VECTOR; word_w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-- Reverse of field_map_in
VARIABLE v_slv_out : STD_LOGIC_VECTOR(field_slv_out_len(field_arr)-1 DOWNTO 0) := (OTHERS=>'0');
VARIABLE v_word_cnt : NATURAL := 0;
BEGIN
FOR f IN 0 TO field_arr'HIGH LOOP
-- Only extract the fields that are outputs
IF field_arr(f).mode="RW" THEN
-- Extract the field
v_slv_out( field_hi(field_arr, field_arr(f).name) DOWNTO field_lo(field_arr, field_arr(f).name)) := word_arr( v_word_cnt*word_w+field_arr(f).size-1 DOWNTO v_word_cnt*word_w);
END IF;
-- Calculate the correct word offset for the next field
v_word_cnt := v_word_cnt + ceil_div(field_arr(f).size, word_w);
END LOOP;
RETURN v_slv_out;
END field_map_out;
 
FUNCTION field_map(field_arr : t_common_field_arr; word_arr_in: STD_LOGIC_VECTOR; word_arr_out: STD_LOGIC_VECTOR; word_w : NATURAL) RETURN STD_LOGIC_VECTOR IS
-- Create one SLV consisting of both read-only and output-readback fields, e.g. as input to an MM reg
VARIABLE v_word_arr : STD_LOGIC_VECTOR(field_nof_words(field_arr, word_w)*word_w-1 DOWNTO 0);
VARIABLE v_word_cnt : NATURAL := 0;
BEGIN
-- Wire the entire SLV to the input SLV by default
v_word_arr := word_arr_in;
-- Now re-assign the words that need to be read back from word_arr_out
FOR f IN 0 TO field_arr'HIGH LOOP
IF field_arr(f).mode="RW" THEN
v_word_arr( v_word_cnt*word_w+field_arr(f).size-1 DOWNTO v_word_cnt*word_w):= word_arr_out( v_word_cnt*word_w+field_arr(f).size-1 DOWNTO v_word_cnt*word_w);
END IF;
-- Calculate the correct word offset for the next field
v_word_cnt := v_word_cnt + ceil_div(field_arr(f).size, word_w);
END LOOP;
RETURN v_word_arr;
END field_map;
 
FUNCTION field_ovr_arr(field_arr : t_common_field_arr; ovr_init: STD_LOGIC_VECTOR) RETURN t_common_field_arr IS
-- Copy field_arr but change widths to 1 to create a 1-bit override field for each field in field_arr.
VARIABLE v_ovr_field_arr : t_common_field_arr(field_arr'RANGE);
BEGIN
v_ovr_field_arr:= field_arr;
FOR i IN field_arr'RANGE LOOP
v_ovr_field_arr(i).size := 1;
v_ovr_field_arr(i).default := field_default(slv(ovr_init(i)));
END LOOP;
RETURN v_ovr_field_arr;
END field_ovr_arr;
 
FUNCTION field_exists(field_arr : t_common_field_arr; name: STRING) RETURN BOOLEAN IS
BEGIN
FOR i IN field_arr'RANGE LOOP
IF field_arr(i).name=field_name_pad(name) THEN
RETURN TRUE;
END IF;
END LOOP;
RETURN FALSE;
END field_exists;
 
FUNCTION field_arr_set_mode(field_arr : t_common_field_arr; mode : STRING) RETURN t_common_field_arr IS
VARIABLE v_field_arr : t_common_field_arr(field_arr'RANGE);
BEGIN
v_field_arr := field_arr;
FOR i IN field_arr'RANGE LOOP
v_field_arr(i).mode := mode;
END LOOP;
RETURN v_field_arr;
END field_arr_set_mode;
 
FUNCTION sel_a_b(sel :BOOLEAN; a, b : t_common_field_arr) RETURN t_common_field_arr IS
BEGIN
IF sel = TRUE THEN
RETURN a;
ELSE
RETURN b;
END IF;
END;
 
END common_field_pkg;
trunk/common_field_pkg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/common_mem_mux.vhd =================================================================== --- trunk/common_mem_mux.vhd (nonexistent) +++ trunk/common_mem_mux.vhd (revision 2) @@ -0,0 +1,143 @@ +------------------------------------------------------------------------------- +-- +-- 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: Combines an array of MM interfaces into a single MM interface. +-- Description: +-- The common_mem_mux unit combines an array of mosi's and miso's to one +-- single set of mosi and miso. Should be used to decrease the amount of +-- slave memory interfaces to the MM bus. +-- +-- g_rd_latency +-- ______________ +-- strip index: | | +-- mosi.address[h:w] ---+-->| delay line |--\ +-- | |____________| | +-- | | +-- selected v | +-- mosi -------> mosi_arr.wr[ ]-----------------------------> mosi_arr +-- rd | +-- selected v +-- miso <-------------------------------miso_arr[ ]<--------- miso_arr +-- +-- . not selected mosi_arr get mosi but with wr='0', rd='0' +-- . not selected miso_arr are ignored +-- +-- Use default g_broadcast=FALSE for multiplexed individual MM access to +-- each mosi_arr/miso_arr MM port. When g_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 ports cannot be read. +-- +-- Remarks: +-- . In simulation selecting an unused element address will cause a simulation +-- failure. Therefore the element index is only accepted when it is in the +-- g_nof_mosi-1 DOWNTO 0 range. +-- . In case multiple common_mem_mux would be used in series, then only the +-- top one needs to account for g_rd_latency>0, the rest can use 0. +-- +------------------------------------------------------------------------------- + + +LIBRARY IEEE, common_pkg_lib, common_ram_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; + +ENTITY common_mem_mux IS + GENERIC ( + g_broadcast : BOOLEAN := FALSE; + g_nof_mosi : POSITIVE := 256; -- Number of memory interfaces in the array. + g_mult_addr_w : POSITIVE := 8; -- Address width of each memory-interface element in the muliplexed array. + g_rd_latency : NATURAL := 0 + ); + PORT ( + clk : IN STD_LOGIC := '0'; -- only used when g_rd_latency > 0 + mosi : IN t_mem_mosi; + miso : OUT t_mem_miso; + mosi_arr : OUT t_mem_mosi_arr(g_nof_mosi - 1 DOWNTO 0); + miso_arr : IN t_mem_miso_arr(g_nof_mosi - 1 DOWNTO 0) := (OTHERS=>c_mem_miso_rst) + ); +END common_mem_mux; + +ARCHITECTURE rtl OF common_mem_mux IS + + CONSTANT c_index_w : NATURAL := ceil_log2(g_nof_mosi); + CONSTANT c_total_addr_w : NATURAL := c_index_w + g_mult_addr_w; + + SIGNAL index_arr : t_natural_arr(0 TO g_rd_latency); + SIGNAL index_rw : NATURAL; -- read or write access + SIGNAL index_rd : NATURAL; -- read response + +BEGIN + + gen_single : IF g_broadcast=FALSE AND g_nof_mosi=1 GENERATE + mosi_arr(0) <= mosi; + miso <= miso_arr(0); + END GENERATE; + + gen_multiple : IF g_broadcast=FALSE AND g_nof_mosi>1 GENERATE + -- The activated element of the array is detected here + index_arr(0) <= TO_UINT(mosi.address(c_total_addr_w-1 DOWNTO g_mult_addr_w)); + + -- Pipeline the index of the activated element to account for the read latency + p_clk : PROCESS(clk) + BEGIN + IF rising_edge(clk) THEN + index_arr(1 TO g_rd_latency) <= index_arr(0 TO g_rd_latency-1); + END IF; + END PROCESS; + + index_rw <= index_arr(0); + index_rd <= index_arr(g_rd_latency); + + -- Master access, can be write or read + p_mosi_arr : PROCESS(mosi, index_rw) + BEGIN + FOR I IN 0 TO g_nof_mosi-1 LOOP + mosi_arr(I) <= mosi; + mosi_arr(I).rd <= '0'; + mosi_arr(I).wr <= '0'; + IF I = index_rw THEN + mosi_arr(I).rd <= mosi.rd; + mosi_arr(I).wr <= mosi.wr; + END IF; + END LOOP; + END PROCESS; + + -- Slave response to read access after g_rd_latency clk cycles + p_miso : PROCESS(miso_arr, index_rd) + BEGIN + miso <= c_mem_miso_rst; + FOR I IN 0 TO g_nof_mosi-1 LOOP + IF I = index_rd THEN + miso <= miso_arr(I); + END IF; + END LOOP; + END PROCESS; + END GENERATE; + + gen_broadcast : IF g_broadcast=TRUE GENERATE + mosi_arr <= (OTHERS=>mosi); -- broadcast write to all [g_nof_mosi-1:0] MM ports + miso <= miso_arr(0); -- broadcast read only from MM port [0] + END GENERATE; + +END rtl;
trunk/common_mem_mux.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/common_reg_cross_domain.vhd =================================================================== --- trunk/common_reg_cross_domain.vhd (nonexistent) +++ trunk/common_reg_cross_domain.vhd (revision 2) @@ -0,0 +1,200 @@ +------------------------------------------------------------------------------- +-- +-- 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_components_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; + +-- Purpose: Get in_dat from in_clk to out_clk domain when in_new is asserted. +-- Remarks: +-- . If in_new is a pulse, then new in_dat is available after g_in_new_latency. +-- . It is also allowed to hold in_new high, then out_new will pulse once for +-- every 24 out_clk cycles. +-- . Use in_done to be sure that in_dat due to in_new has crossed the clock +-- domain, in case of multiple in_new pulses in a row the in_done will only +-- pulse when this state remains s_idle, so after the last in_new. +-- . If the in_dat remains unchanged during the crossing of in_new to out_en +-- then g_input_buf=FALSE may be used to save some flipflops + +ENTITY common_reg_cross_domain IS + GENERIC ( + g_input_buf : BOOLEAN := TRUE; + g_in_new_latency : NATURAL := 0; -- >= 0 + g_out_dat_init : STD_LOGIC_VECTOR(c_mem_reg_init_w-1 DOWNTO 0) := (OTHERS => '0') + ); + PORT ( + in_rst : IN STD_LOGIC; + in_clk : IN STD_LOGIC; + in_new : IN STD_LOGIC := '1'; -- when '1' then new in_dat is available after g_in_new_latency + in_dat : IN STD_LOGIC_VECTOR; + in_done : OUT STD_LOGIC; -- pulses when no more pending in_new + out_rst : IN STD_LOGIC; + out_clk : IN STD_LOGIC; + out_dat : OUT STD_LOGIC_VECTOR; + out_new : OUT STD_LOGIC -- when '1' then the out_dat was updated with in_dat due to in_new + ); +END common_reg_cross_domain; + + +ARCHITECTURE rtl OF common_reg_cross_domain IS + + CONSTANT c_dat : STD_LOGIC_VECTOR(in_dat'RANGE) := g_out_dat_init(in_dat'RANGE); + + ------------------------------------------------------------------------------ + -- in_clk domain + ------------------------------------------------------------------------------ + SIGNAL reg_new : STD_LOGIC_VECTOR(0 TO g_in_new_latency) := (OTHERS=>'0'); + SIGNAL nxt_reg_new : STD_LOGIC_VECTOR(reg_new'RANGE); + + SIGNAL in_buf : STD_LOGIC_VECTOR(c_dat'RANGE) := c_dat; + SIGNAL in_buf_reg : STD_LOGIC_VECTOR(c_dat'RANGE) := c_dat; + SIGNAL nxt_in_buf_reg : STD_LOGIC_VECTOR(c_dat'RANGE); + + -- Register access clock domain crossing + TYPE t_state_enum IS (s_idle, s_busy); + + SIGNAL cross_req : STD_LOGIC; + SIGNAL cross_busy : STD_LOGIC; + SIGNAL nxt_in_done : STD_LOGIC; + SIGNAL state : t_state_enum; + SIGNAL nxt_state : t_state_enum; + SIGNAL prev_state : t_state_enum; + SIGNAL in_new_hold : STD_LOGIC; + SIGNAL nxt_in_new_hold : STD_LOGIC; + + ------------------------------------------------------------------------------ + -- out_clk domain + ------------------------------------------------------------------------------ + SIGNAL out_en : STD_LOGIC; + SIGNAL i_out_dat : STD_LOGIC_VECTOR(c_dat'RANGE) := c_dat; -- register init without physical reset + SIGNAL nxt_out_dat : STD_LOGIC_VECTOR(c_dat'RANGE); + +BEGIN + + out_dat <= i_out_dat; + + ------------------------------------------------------------------------------ + -- in_clk domain + ------------------------------------------------------------------------------ + + reg_new(0) <= in_new; + + gen_latency : IF g_in_new_latency>0 GENERATE + p_reg_new : PROCESS(in_rst, in_clk) + BEGIN + IF in_rst='1' THEN + reg_new(1 TO g_in_new_latency) <= (OTHERS=>'0'); + ELSIF rising_edge(in_clk) THEN + reg_new(1 TO g_in_new_latency) <= nxt_reg_new(1 TO g_in_new_latency); + END IF; + END PROCESS; + + nxt_reg_new(1 TO g_in_new_latency) <= reg_new(0 TO g_in_new_latency-1); + END GENERATE; + + p_in_clk : PROCESS(in_rst, in_clk) + BEGIN + IF in_rst='1' THEN + in_new_hold <= '0'; + in_done <= '0'; + state <= s_idle; + prev_state <= s_idle; + ELSIF rising_edge(in_clk) THEN + in_buf_reg <= nxt_in_buf_reg; + in_new_hold <= nxt_in_new_hold; + in_done <= nxt_in_done; + state <= nxt_state; + prev_state <= state; + END IF; + END PROCESS; + + -- capture the new register data + no_in_buf : IF g_input_buf=FALSE GENERATE + in_buf <= in_dat; -- assumes that in_dat remains unchanged during the crossing of in_new to out_en + END GENERATE; + + gen_in_buf : IF g_input_buf=TRUE GENERATE + nxt_in_buf_reg <= in_dat WHEN cross_req='1' ELSE in_buf_reg; + in_buf <= in_buf_reg; + END GENERATE; + + + -- handshake control of the clock domain crossing by u_cross_req + -- hold any subsequent in_new during cross domain busy to ensure that the out_dat will get the latest value of in_dat + p_state : PROCESS(state, prev_state, reg_new, in_new_hold, cross_busy) + BEGIN + cross_req <= '0'; + nxt_in_done <= '0'; + nxt_in_new_hold <= in_new_hold; + nxt_state <= state; + CASE state IS + WHEN s_idle => + nxt_in_new_hold <= '0'; + IF reg_new(g_in_new_latency)='1' OR in_new_hold='1' THEN + cross_req <= '1'; + nxt_state <= s_busy; + ELSIF UNSIGNED(reg_new)=0 AND prev_state=s_busy THEN + nxt_in_done <= '1'; -- no pending in_new at input or in shift register and just left s_busy, so signal in_done + END IF; + WHEN OTHERS => -- s_busy + IF reg_new(g_in_new_latency)='1' THEN + nxt_in_new_hold <= '1'; + END IF; + IF cross_busy='0' THEN + nxt_state <= s_idle; + END IF; + END CASE; + END PROCESS; + + ------------------------------------------------------------------------------ + -- cross clock domain + ------------------------------------------------------------------------------ + u_cross_req : ENTITY common_components_lib.common_spulse + PORT MAP ( + in_rst => in_rst, + in_clk => in_clk, + in_pulse => cross_req, + in_busy => cross_busy, + out_rst => out_rst, + out_clk => out_clk, + out_pulse => out_en + ); + + ------------------------------------------------------------------------------ + -- out_clk domain + ------------------------------------------------------------------------------ + p_out_clk : PROCESS(out_rst, out_clk) + BEGIN + IF out_rst='1' THEN + out_new <= '0'; + ELSIF rising_edge(out_clk) THEN + i_out_dat <= nxt_out_dat; + out_new <= out_en; + END IF; + END PROCESS; + + -- some clock cycles after the cross_req the in_buf data is stable for sure + nxt_out_dat <= in_buf WHEN out_en='1' ELSE i_out_dat; + +END rtl;
trunk/common_reg_cross_domain.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/common_reg_r_w.vhd =================================================================== --- trunk/common_reg_r_w.vhd (nonexistent) +++ trunk/common_reg_r_w.vhd (revision 2) @@ -0,0 +1,176 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2009 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, common_components_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; + +-- Derived from LOFAR cfg_single_reg + +-- Purpose: Provide a MM interface to a register vector +-- +-- Description: +-- The register has g_reg.nof_dat words and each word is g_reg.dat_w bits +-- wide. At the control side the register is accessed per word using the +-- address input wr_adr or rd_adr as index. At the data side the whole +-- register of g_reg.dat_w*g_reg.nof_dat bits is available at once. This is +-- the key difference with using a RAM. +-- E.g. for g_reg.nof_dat = 3 and g_reg.dat_w = 32 the addressing accesses +-- the register bits as follows: +-- wr_adr[1:0], rd_adr[1:0] = 0 --> reg[31:0] +-- wr_adr[1:0], rd_adr[1:0] = 1 --> reg[63:32] +-- wr_adr[1:0], rd_adr[1:0] = 2 --> reg[95:64] +-- E.g. for wr_adr = 0 and wr_en = '1': out_reg[31:0] = wr_dat[31:0] +-- E.g. for rd_adr = 0 and rd_en = '1': rd_dat[31:0] = in_reg[31:0] +-- +-- The word in the register that got accessed is reported via reg_wr_arr +-- or via reg_rd_arr depended on whether it was a write access or an read +-- access. +-- +-- Usage: +-- 1) Connect out_reg to in_reg for write and readback register. +-- 2) Do not connect out_reg to in_reg for seperate write only register and +-- read only register at the same address. +-- 3) Leave out_reg OPEN for read only register. +-- 4) Connect wr_adr and rd_adr to have a shared address bus register. + +ENTITY common_reg_r_w IS + GENERIC ( + g_reg : t_c_mem := c_mem_reg; + g_init_reg : STD_LOGIC_VECTOR(c_mem_reg_init_w-1 DOWNTO 0) := (OTHERS => '0') + ); + PORT ( + rst : IN STD_LOGIC := '0'; + clk : IN STD_LOGIC; + clken : IN STD_LOGIC := '1'; + -- control side + wr_en : IN STD_LOGIC; + wr_adr : IN STD_LOGIC_VECTOR(g_reg.adr_w-1 DOWNTO 0); + wr_dat : IN STD_LOGIC_VECTOR(g_reg.dat_w-1 DOWNTO 0); + rd_en : IN STD_LOGIC; + rd_adr : IN STD_LOGIC_VECTOR(g_reg.adr_w-1 DOWNTO 0); + rd_dat : OUT STD_LOGIC_VECTOR(g_reg.dat_w-1 DOWNTO 0); + rd_val : OUT STD_LOGIC; + -- data side + reg_wr_arr : OUT STD_LOGIC_VECTOR( g_reg.nof_dat-1 DOWNTO 0); + reg_rd_arr : OUT STD_LOGIC_VECTOR( g_reg.nof_dat-1 DOWNTO 0); + out_reg : OUT STD_LOGIC_VECTOR(g_reg.dat_w*g_reg.nof_dat-1 DOWNTO 0); + in_reg : IN STD_LOGIC_VECTOR(g_reg.dat_w*g_reg.nof_dat-1 DOWNTO 0) + ); +END common_reg_r_w; + + +ARCHITECTURE rtl OF common_reg_r_w IS + + CONSTANT c_rd_latency : NATURAL := 1; + CONSTANT c_pipeline : NATURAL := g_reg.latency - c_rd_latency; + CONSTANT c_pipe_dat_w : NATURAL := 1 + g_reg.dat_w; -- pipeline rd_val & rd_dat together + + SIGNAL pipe_dat_in : STD_LOGIC_VECTOR(c_pipe_dat_w-1 DOWNTO 0); + SIGNAL pipe_dat_out : STD_LOGIC_VECTOR(c_pipe_dat_w-1 DOWNTO 0); + + SIGNAL nxt_reg_wr_arr : STD_LOGIC_VECTOR(reg_wr_arr'RANGE); + SIGNAL nxt_reg_rd_arr : STD_LOGIC_VECTOR(reg_rd_arr'RANGE); + + SIGNAL i_out_reg : STD_LOGIC_VECTOR(out_reg'RANGE); + SIGNAL nxt_out_reg : STD_LOGIC_VECTOR(out_reg'RANGE); + + SIGNAL int_rd_dat : STD_LOGIC_VECTOR(rd_dat'RANGE); + SIGNAL int_rd_val : STD_LOGIC; + SIGNAL nxt_rd_dat : STD_LOGIC_VECTOR(rd_dat'RANGE); + SIGNAL nxt_rd_val : STD_LOGIC; + +BEGIN + + out_reg <= i_out_reg; + + -- Pipeline to support read data latency > 1 + u_pipe_rd : ENTITY common_components_lib.common_pipeline + GENERIC MAP ( + g_pipeline => c_pipeline, + g_in_dat_w => c_pipe_dat_w, + g_out_dat_w => c_pipe_dat_w + ) + PORT MAP ( + clk => clk, + clken => clken, + in_dat => pipe_dat_in, + out_dat => pipe_dat_out + ); + + pipe_dat_in <= int_rd_val & int_rd_dat; + + rd_dat <= pipe_dat_out(pipe_dat_out'HIGH-1 DOWNTO 0); + rd_val <= pipe_dat_out(pipe_dat_out'HIGH); + + + p_reg : PROCESS (rst, clk) + BEGIN + IF rst = '1' THEN + -- Output signals. + reg_wr_arr <= (OTHERS => '0'); + reg_rd_arr <= (OTHERS => '0'); + int_rd_val <= '0'; + int_rd_dat <= (OTHERS => '0'); + -- Internal signals. + i_out_reg <= g_init_reg(out_reg'RANGE); + ELSIF rising_edge(clk) THEN + -- Output signals. + reg_wr_arr <= nxt_reg_wr_arr; + reg_rd_arr <= nxt_reg_rd_arr; + int_rd_val <= nxt_rd_val; + int_rd_dat <= nxt_rd_dat; + -- Internal signals. + i_out_reg <= nxt_out_reg; + END IF; + END PROCESS; + + + p_control : PROCESS (rd_en, int_rd_dat, rd_adr, in_reg, i_out_reg, wr_adr, wr_en, wr_dat) + BEGIN + nxt_rd_val <= rd_en; -- rd_val depends only on rd_en, so for an out of range address the old rd_dat is output + + nxt_reg_rd_arr <= (OTHERS=>'0'); + nxt_rd_dat <= int_rd_dat; + IF rd_en = '1' THEN + FOR i IN 0 TO g_reg.nof_dat-1 LOOP + IF UNSIGNED(rd_adr) = i THEN + nxt_reg_rd_arr(I) <= '1'; + nxt_rd_dat <= in_reg((i+1)*g_reg.dat_w-1 DOWNTO i*g_reg.dat_w); + END IF; + END LOOP; + END IF; + + nxt_reg_wr_arr <= (OTHERS=>'0'); + nxt_out_reg <= i_out_reg; + IF wr_en = '1' THEN + FOR i IN 0 TO g_reg.nof_dat-1 LOOP + IF UNSIGNED(wr_adr) = i THEN + nxt_reg_wr_arr(I) <= '1'; + nxt_out_reg((i+1)*g_reg.dat_w-1 DOWNTO i*g_reg.dat_w) <= wr_dat; + END IF; + END LOOP; + END IF; + END PROCESS; + +END rtl;
trunk/common_reg_r_w.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/common_reg_r_w_dc.vhd =================================================================== --- trunk/common_reg_r_w_dc.vhd (nonexistent) +++ trunk/common_reg_r_w_dc.vhd (revision 2) @@ -0,0 +1,241 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2012 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +-- +------------------------------------------------------------------------------- + +-- Purpose: Provide dual clock domain crossing to common_reg_r_w.vhd +-- Description: +-- . Write vector to out_reg +-- . Read vector from in_reg or readback from out_reg +-- +-- 31 24 23 16 15 8 7 0 wi +-- |-----------------|-----------------|-----------------|-----------------| +-- | data[31:0] | 0 +-- |-----------------------------------------------------------------------| +-- | data[63:32] | 1 +-- |-----------------------------------------------------------------------| +-- +-- . g_readback +-- When g_readback is TRUE then the written data is read back from the st_clk +-- domain directly into the mm_clk domain, so without ST --> MM clock domain +-- crossing logic. This is allowed because the read back value is stable. +-- For readback the out_reg needs to be connected to in_reg, independent of +-- the g_readback setting, because the readback value is read back from the +-- st_clk domain. In this way the readback value also reveals that the +-- written value is indeed available in the st_clk domain (ie. this shows +-- that the st_clk is active). If g_cross_clock_domain=FALSE, then g_readback +-- is don't care. +-- In fact g_readback could better be called g_st_readback. An alternative +-- g_mm_readback could define direct read back in the MM clock domain and +-- would allow leaving the in_reg not connected. + +LIBRARY IEEE, common_pkg_lib, common_components_lib, common_ram_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; + +ENTITY common_reg_r_w_dc 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_in_new_latency : NATURAL := 0; -- >= 0 + g_readback : BOOLEAN := FALSE; -- must use FALSE for write/read or read only register when g_cross_clock_domain=TRUE + --g_readback : BOOLEAN := TRUE; -- can use TRUE for write and readback register + g_reg : t_c_mem := c_mem_reg; + g_init_reg : STD_LOGIC_VECTOR(c_mem_reg_init_w-1 DOWNTO 0) := (OTHERS => '0') + ); + PORT ( + -- Clocks and reset + mm_rst : IN STD_LOGIC; -- reset synchronous with mm_clk + mm_clk : IN STD_LOGIC; -- memory-mapped bus clock + st_rst : IN STD_LOGIC; -- reset synchronous with st_clk + st_clk : IN STD_LOGIC; -- other clock domain clock + + -- Memory Mapped Slave in mm_clk domain + sla_in : IN t_mem_mosi; -- actual ranges defined by g_reg + sla_out : OUT t_mem_miso; -- actual ranges defined by g_reg + + -- MM registers in st_clk domain + reg_wr_arr : OUT STD_LOGIC_VECTOR( g_reg.nof_dat-1 DOWNTO 0); + reg_rd_arr : OUT STD_LOGIC_VECTOR( g_reg.nof_dat-1 DOWNTO 0); + in_new : IN STD_LOGIC := '1'; + in_reg : IN STD_LOGIC_VECTOR(g_reg.dat_w*g_reg.nof_dat-1 DOWNTO 0); + out_reg : OUT STD_LOGIC_VECTOR(g_reg.dat_w*g_reg.nof_dat-1 DOWNTO 0); + out_new : OUT STD_LOGIC -- Pulses '1' when new data has been written. + ); +END common_reg_r_w_dc; + + +ARCHITECTURE str OF common_reg_r_w_dc IS + + -- Registers in mm_clk domain + SIGNAL vector_wr_arr : STD_LOGIC_VECTOR( g_reg.nof_dat-1 DOWNTO 0); + SIGNAL vector_rd_arr : STD_LOGIC_VECTOR( g_reg.nof_dat-1 DOWNTO 0); + SIGNAL out_vector : STD_LOGIC_VECTOR(g_reg.dat_w*g_reg.nof_dat-1 DOWNTO 0); + SIGNAL in_vector : STD_LOGIC_VECTOR(g_reg.dat_w*g_reg.nof_dat-1 DOWNTO 0); + + -- Initialize output to avoid Warning: (vsim-8684) No drivers exist on out port *, and its initial value is not used + SIGNAL i_sla_out : t_mem_miso := c_mem_miso_rst; + + SIGNAL reg_wr_arr_i : STD_LOGIC_VECTOR( g_reg.nof_dat-1 DOWNTO 0); + SIGNAL wr_pulse : STD_LOGIC; + SIGNAL toggle : STD_LOGIC; + SIGNAL out_new_i : STD_LOGIC; + +BEGIN + + ------------------------------------------------------------------------------ + -- MM register access in the mm_clk domain + ------------------------------------------------------------------------------ + + sla_out <= i_sla_out; + + u_reg : ENTITY work.common_reg_r_w + GENERIC MAP ( + g_reg => g_reg, + g_init_reg => g_init_reg + ) + PORT MAP ( + rst => mm_rst, + clk => mm_clk, + -- control side + wr_en => sla_in.wr, + wr_adr => sla_in.address(g_reg.adr_w-1 DOWNTO 0), + wr_dat => sla_in.wrdata(g_reg.dat_w-1 DOWNTO 0), + rd_en => sla_in.rd, + rd_adr => sla_in.address(g_reg.adr_w-1 DOWNTO 0), + rd_dat => i_sla_out.rddata(g_reg.dat_w-1 DOWNTO 0), + rd_val => i_sla_out.rdval, + -- data side + reg_wr_arr => vector_wr_arr, + reg_rd_arr => vector_rd_arr, + out_reg => out_vector, + in_reg => in_vector + ); + + + ------------------------------------------------------------------------------ + -- Transfer register value between mm_clk and st_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 + in_vector <= in_reg; + out_reg <= out_vector; + reg_wr_arr <= vector_wr_arr; + reg_rd_arr <= vector_rd_arr; + out_new <= vector_wr_arr(0); + END GENERATE; -- no_cross + + gen_cross : IF g_cross_clock_domain = TRUE GENERATE + + gen_rdback : IF g_readback=TRUE GENERATE + in_vector <= in_reg; + END GENERATE; + + gen_rd : IF g_readback=FALSE GENERATE + u_in_vector : ENTITY work.common_reg_cross_domain + GENERIC MAP ( + g_in_new_latency => g_in_new_latency + ) + PORT MAP ( + in_rst => st_rst, + in_clk => st_clk, + in_new => in_new, + in_dat => in_reg, + in_done => OPEN, + out_rst => mm_rst, + out_clk => mm_clk, + out_dat => in_vector, + out_new => OPEN + ); + END GENERATE; + + u_out_reg : ENTITY work.common_reg_cross_domain + GENERIC MAP( + g_out_dat_init => g_init_reg + ) + PORT MAP ( + in_rst => mm_rst, + in_clk => mm_clk, + in_dat => out_vector, + in_done => OPEN, + out_rst => st_rst, + out_clk => st_clk, + out_dat => out_reg, + out_new => out_new_i + ); + + u_toggle : ENTITY common_components_lib.common_switch + GENERIC MAP ( + g_rst_level => '0', + g_priority_lo => FALSE, + g_or_high => FALSE, + g_and_low => FALSE + ) + PORT MAP ( + rst => st_rst, + clk => st_clk, + switch_high => wr_pulse, + switch_low => out_new_i, + out_level => toggle + ); + + wr_pulse <= '0' WHEN vector_or(reg_wr_arr_i)='0' ELSE '1'; + out_new <= out_new_i AND toggle; + reg_wr_arr <= reg_wr_arr_i; + + gen_access_evt : FOR I IN 0 TO g_reg.nof_dat-1 GENERATE + u_reg_wr_arr : ENTITY common_components_lib.common_spulse + PORT MAP ( + in_rst => mm_rst, + in_clk => mm_clk, + in_pulse => vector_wr_arr(I), + in_busy => OPEN, + out_rst => st_rst, + out_clk => st_clk, + out_pulse => reg_wr_arr_i(I) + ); + + u_reg_rd_arr : ENTITY common_components_lib.common_spulse + PORT MAP ( + in_rst => mm_rst, + in_clk => mm_clk, + in_pulse => vector_rd_arr(I), + in_busy => OPEN, + out_rst => st_rst, + out_clk => st_clk, + out_pulse => reg_rd_arr(I) + ); + END GENERATE; + + END GENERATE; -- gen_cross + +END str;
trunk/common_reg_r_w_dc.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,32 @@ +hdl_lib_name = mm +hdl_library_clause_name = mm_lib +hdl_lib_uses_synth = common_pkg common_components common_ram +hdl_lib_uses_sim = +hdl_lib_technology = + +synth_files = + common_reg_cross_domain.vhd + common_reg_r_w.vhd + common_reg_r_w_dc.vhd + common_field_pkg.vhd + mm_fields.vhd + tb_common_mem_pkg.vhd + mm_file_pkg.vhd + common_mem_mux.vhd + mm_file_unb_pkg.vhd #UniBoard dependencies? FIXME TODO + +test_bench_files = + mm_file.vhd + tb_mm_file.vhd + tb_tb_mm_file.vhd + tb_common_mem_mux.vhd + +regression_test_vhdl = + tb_tb_mm_file.vhd + + +[modelsim_project_file] + + +[quartus_project_file] +
trunk/hdllib.cfg Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mm_fields.vhd =================================================================== --- trunk/mm_fields.vhd (nonexistent) +++ trunk/mm_fields.vhd (revision 2) @@ -0,0 +1,178 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2013 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +-- +------------------------------------------------------------------------------- + +-- Purpose: +-- . Define fields in an SLV that can be read/written via an MM interface. +-- Description: +-- . This is basically a wrapper around common_reg_r_w_dc, but with the +-- addition of a generic field description array and package functions +-- to ease the definition and assignment of individual fields within +-- the i/o SLVs. +-- . Each field defined in g_field_arr will get its own 32-bit MM register(s) +-- based on its defined length: +-- . <32 bits = one dedicated 32-bit register for that field +-- . >32 bits = multiple dedicated 32-bit registers for that field +-- . The register mode can be "RO" for input from slv_in (e.g. status) or "RW" +-- for output via slv_out (e.g. control). Other modes are not supported. +-- Hence the length of the reg_slv_* signals is equal to slv_in'LENGTH + +-- slv_out'LENGTH. +-- . The figure below shows how the following example field array would be mapped. +-- +-- c_my_field_arr:= (( "my_field_2", "RW", 2 ), +-- ( "my_field_1", "RO", 2 ), +-- ( "my_field_0", "RO", 1 )); +-- +-- ---------------------------------------------------------------------------------------------------------------- +-- | slv_in reg_slv_in_arr reg_slv_in common_reg_r_w reg_slv_out slv_out| +-- | | +-- | __ __ ______________ __ | +-- | w0|f0| w0|f0| |0 | w0| | | +-- | | | =====> | | =====> | RO | =====> | | =====> | +-- | | | | | | | | | | +-- | __ |--| |--| |--------------| |--| | +-- | |f0| w1|f1| w1|f1| |1 | w1| | __ | +-- | |f1| ==field_map_in==> |f1| =====> |f1| =====> | RO | =====> | | =====> field_map_out==> |f2| | +-- | |f1| | | | | | | | | |f2| | +-- | |--| |--| |--------------| |--| | +-- | w2| | w2|f2| |2 | w2|f2| | +-- | | | /===> |f2| =====> | RW | =====> |f2| ==+==> | +-- | |__| | |__| |______________| |__| | | +-- | | | | +-- | \================================================/ | +-- | | +-- ---------------------------------------------------------------------------------------------------------------- +-- . slv_in = 3 bits wide +-- . slv_out = 2 bits wide (= my_field_2 which is looped back to reg_slv_in because it is defined "RW") +-- . reg_reg_slv_in_arr, reg_slv_in, reg_slv_out = 3*c_word_w bits wide +-- Remarks: + +LIBRARY IEEE, common_pkg_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 work.common_field_pkg.ALL; + +ENTITY mm_fields IS + GENERIC ( + g_cross_clock_domain : BOOLEAN := TRUE; + g_use_slv_in_val : BOOLEAN := TRUE; -- use TRUE when slv_in_val is used, use FALSE to save logic when always slv_in_val='1' + g_field_arr : t_common_field_arr + ); + PORT ( + mm_rst : IN STD_LOGIC; + mm_clk : IN STD_LOGIC; + + mm_mosi : IN t_mem_mosi; + mm_miso : OUT t_mem_miso; + + slv_rst : IN STD_LOGIC; + slv_clk : IN STD_LOGIC; + + --fields in these SLVs are defined by g_field_arr + slv_in : IN STD_LOGIC_VECTOR(field_slv_in_len( g_field_arr)-1 DOWNTO 0) := (OTHERS=>'0'); -- slv of all "RO" fields in g_field_arr + slv_in_val : IN STD_LOGIC := '0'; -- strobe to signal that slv_in is valid and needs to be captured + + slv_out : OUT STD_LOGIC_VECTOR(field_slv_out_len(g_field_arr)-1 DOWNTO 0) -- slv of all "RW" fields in g_field_arr + ); +END mm_fields; + + +ARCHITECTURE str OF mm_fields IS + + CONSTANT c_reg_nof_words : NATURAL := field_nof_words(g_field_arr, c_word_w); + + CONSTANT c_reg : t_c_mem := (latency => 1, + adr_w => ceil_log2(c_reg_nof_words), + dat_w => c_word_w, + nof_dat => c_reg_nof_words, + init_sl => '0'); + + CONSTANT c_slv_out_defaults : STD_LOGIC_VECTOR(field_slv_out_len(g_field_arr)-1 DOWNTO 0) := field_map_defaults(g_field_arr); + -- Map the default values onto c_init_reg + CONSTANT c_init_reg : STD_LOGIC_VECTOR(c_mem_reg_init_w-1 DOWNTO 0) := RESIZE_UVEC(field_map_in(g_field_arr, c_slv_out_defaults, c_reg.dat_w, "RW"), c_mem_reg_init_w); + + SIGNAL slv_in_arr : STD_LOGIC_VECTOR(c_reg.dat_w*c_reg.nof_dat-1 DOWNTO 0); + SIGNAL reg_slv_in_arr : STD_LOGIC_VECTOR(c_reg.dat_w*c_reg.nof_dat-1 DOWNTO 0); + SIGNAL nxt_reg_slv_in_arr : STD_LOGIC_VECTOR(c_reg.dat_w*c_reg.nof_dat-1 DOWNTO 0); + + SIGNAL reg_slv_in : STD_LOGIC_VECTOR(c_reg.dat_w*c_reg.nof_dat-1 DOWNTO 0); + SIGNAL reg_slv_out : STD_LOGIC_VECTOR(c_reg.dat_w*c_reg.nof_dat-1 DOWNTO 0); + +BEGIN + + ----------------------------------------------------------------------------- + -- reg_slv_out is persistent (always valid) while slv_in is not. Register + -- slv_in_arr so reg_slv_in is persistent also. + ----------------------------------------------------------------------------- + gen_capture_input : IF g_use_slv_in_val=TRUE GENERATE + p_clk : PROCESS(slv_clk, slv_rst) + BEGIN + IF slv_rst='1' THEN + reg_slv_in_arr <= (OTHERS=>'0'); + ELSIF rising_edge(slv_clk) THEN + reg_slv_in_arr <= nxt_reg_slv_in_arr; + END IF; + END PROCESS; + + nxt_reg_slv_in_arr <= slv_in_arr WHEN slv_in_val = '1' ELSE reg_slv_in_arr; + END GENERATE; + + gen_wire_input : IF g_use_slv_in_val=FALSE GENERATE + reg_slv_in_arr <= slv_in_arr; + END GENERATE; + + ----------------------------------------------------------------------------- + -- Field mapping + ----------------------------------------------------------------------------- + -- Extract the all input fields ("RO") from slv_in and assign them to slv_in_arr + slv_in_arr <= field_map_in(g_field_arr, slv_in, c_reg.dat_w, "RO"); + + -- Map reg_slv_out onto slv_out for the write fields + slv_out <= field_map_out(g_field_arr, reg_slv_out, c_reg.dat_w); + + -- Create the correct reg_slv_in using fields from both reg_slv_in_arr ("RO") reg_slv_out ("RW") + reg_slv_in <= field_map(g_field_arr, reg_slv_in_arr, reg_slv_out, c_reg.dat_w); + + ----------------------------------------------------------------------------- + -- Actual MM <-> SLV R/W functionality is provided by common_reg_r_w_dc + ----------------------------------------------------------------------------- + u_common_reg_r_w_dc : ENTITY work.common_reg_r_w_dc + GENERIC MAP ( + g_cross_clock_domain => g_cross_clock_domain, + g_readback => FALSE, + g_reg => c_reg, + g_init_reg => c_init_reg + ) + PORT MAP ( + mm_rst => mm_rst, + mm_clk => mm_clk, + st_rst => slv_rst, + st_clk => slv_clk, + + sla_in => mm_mosi, + sla_out => mm_miso, + + in_reg => reg_slv_in, + out_reg => reg_slv_out + ); + +END str;
trunk/mm_fields.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mm_file.vhd =================================================================== --- trunk/mm_file.vhd (nonexistent) +++ trunk/mm_file.vhd (revision 2) @@ -0,0 +1,183 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2012 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +-- +------------------------------------------------------------------------------- + +-- Author: +-- D. van der Schuur May 2012 Initial +-- E. Kooistra Jan 2018 Removed unused generics and added remarks. +-- Purpose: Provide access to an MM slave via file IO +-- Description: +-- See mm_file_pkg. +-- +-- * Optional MM file IO throttle via g_mm_timeout, g_mm_pause: +-- Default g_mm_timeout=0 ns for full speed MM file IO rate. Optional use +-- g_mm_timeout>0 ns to throttle MM file IO rate. The mm_master_out wr and +-- rd strobes are monitored. As long as a strobe occurs within +-- g_mm_timeout then the MM file IO operates at full speed. When no strobe +-- occurs within g_mm_timeout, then a delay of g_mm_pause is inserted +-- until the next MM file IO access will be done. This throttling reduces +-- the file IO rate when the MM slave is idle and picks up again at full +-- speed when MM slave accesses appear again. +-- +-- The g_mm_timeout is in ns, and not defined in number of mm_clk cycles, +-- to make it independent of the simulation mm_clk period. This is +-- important to be able to handle clock domain crossings between a fast +-- simulation mm_clk and a relatively slow internal dp_clk. If the +-- g_mm_timeout is too short then it will occur for every MM access that +-- needs a MM-DP clock domain crossing. A dp_clk typically runs at +-- about 100 or 200 MHz, so period < about 10 ns. A clock domain crossing +-- takes about 25 clock cycles in both clock domains (see +-- common_reg_cross_domain.vhd). Hence a suitable default value for +-- g_mm_timeout is about 250 ns. With some margin use 1000 ns. +-- The g_mm_pause is defined in ns, but could as well have been defined +-- in number mm_clk cycle. Use g_mm_pause default 100 ns to have a factor +-- 1000 reduction in file IO rate witk c_mmf_mm_clk_period = 100 ps, while +-- not introducing too much delay in case a new MM access is pending. +-- +-- Remarks: +-- * Positional mapping of generics and port: +-- If necessary new generics or ports should be added after the existing +-- generics or ports, because then existing mm_file instances that use +-- positional mapping instead of explicit name mapping (with =>) still +-- compile ok. +-- +-- * Default g_mm_rd_latency=2: +-- The default g_mm_rd_latency=2 to fit both MM reg (which typically have rd +-- latency 1) and MM ram (for which some have rd latency 2). This works +-- because the mm_master_out.rd strobes have gaps. The maximum rd strobe +-- rate appears to be 1 strobe in every 4 cycles. By using default +-- g_mm_rd_latency=2 the mm_file instances do not explicitly have to map the +-- actual MM slave rd latency, because using 2 fits all. This ensures +-- that all existing mm_file instances that do not map g_mm_rd_latency still +-- work and for new mm_file instances it avoids the need to know whether the +-- MM slave actually has rd latency 1 or 2. +-- +-- * Default g_file_enable='1': +-- Default the mm_file instance will open the files. However if the MM slave +-- will not be used in a test, then it can be good to use g_file_enable='0' +-- to avoid these files. For multi tb or tb with many mm_file instances this +-- limits the number of file handlers and may help to improve the simulation +-- speed (and stability). +-- +LIBRARY IEEE, common_pkg_lib, common_ram_lib; +USE IEEE.std_logic_1164.ALL; +USE IEEE.numeric_std.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_pkg_lib.tb_common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE work.tb_common_mem_pkg.ALL; +USE common_pkg_lib.common_str_pkg.ALL; +USE work.mm_file_pkg.ALL; +USE IEEE.std_logic_textio.ALL; +USE std.textio.ALL; + +ENTITY mm_file IS + GENERIC ( + g_file_prefix : STRING; -- e.g. "ppsh" will create i/o files ppsh_stat.txt and ppsh_ctrl.txt + g_file_enable : STD_LOGIC := '1'; -- default use '1' to enable file IO, use '0' to disable file IO and force mm_master_out to c_mem_mosi_rst + g_mm_rd_latency : NATURAL := 2; -- default use 2 to fit 0, 1 or 2, must be >= read latency of the MM slave + g_mm_timeout : TIME := c_mmf_mm_timeout; -- use 0 ns for full speed MM, use > 0 ns to define time without MM access after which the MM file IO is paused + g_mm_pause : TIME := c_mmf_mm_pause -- defines time for which MM file IO is paused to reduce the file IO rate when the MM slave is idle + ); + PORT ( + mm_rst : IN STD_LOGIC; + mm_clk : IN STD_LOGIC; + + mm_master_out : OUT t_mem_mosi := c_mem_mosi_rst; + mm_master_in : IN t_mem_miso := c_mem_miso_rst + ); +END mm_file; + + +ARCHITECTURE str OF mm_file IS + + CONSTANT c_rd_file_name : STRING := g_file_prefix & ".ctrl"; + CONSTANT c_wr_file_name : STRING := g_file_prefix & ".stat"; + + SIGNAL i_mm_master_out : t_mem_mosi; + + -- Optional file IO throttle control + SIGNAL strobe : STD_LOGIC; + SIGNAL pause : STD_LOGIC; + SIGNAL polling : STD_LOGIC := '0'; -- monitor signal to view in Wave window when mmf_mm_from_file() is busy + SIGNAL timebegin : TIME := 0 ns; + SIGNAL timeout : TIME := 0 ns; + +BEGIN + + mm_master_out <= i_mm_master_out; + + no_file : IF g_file_enable='0' GENERATE + i_mm_master_out <= c_mem_mosi_rst; + END GENERATE; + + gen_file : IF g_file_enable='1' GENERATE + + p_file_to_mm : PROCESS + BEGIN + i_mm_master_out <= c_mem_mosi_rst; + + -- Create the ctrl file that we're going to read from + print_str("[" & time_to_str(NOW) & "] " & c_rd_file_name & ": Created" ); + mmf_file_create(c_rd_file_name); + + WHILE TRUE LOOP + mmf_mm_from_file(mm_clk, mm_rst, i_mm_master_out, mm_master_in, c_rd_file_name, c_wr_file_name, g_mm_rd_latency); + + -- Optional file IO throttle control + IF g_mm_timeout>0 ns AND pause='1' THEN + polling <= '0'; + WAIT FOR g_mm_pause; -- Pause the file IO when MM timeout is enabled and no strobes appeared for g_mm_timeout + + proc_common_wait_some_cycles(mm_clk, 1); -- Realign to mm_clk, not needed but done to resemble return from mmf_mm_from_file() + polling <= '1'; + END IF; + END LOOP; + + WAIT; + END PROCESS; + + -- Optional file IO throttle control + gen_mm_timeout_control : IF g_mm_timeout>0 ns GENERATE + strobe <= i_mm_master_out.wr OR i_mm_master_out.rd; -- detect MM access + + pause <= NOT strobe WHEN timeout>g_mm_timeout ELSE '0'; -- issue MM file IO pause after strobe timeout + + -- Use mm_clk event to update time based on NOW, without event it does not update + p_mm_now : PROCESS(mm_rst, mm_clk) + BEGIN + IF mm_rst='1' THEN + -- during reset no timeouts + timebegin <= NOW; + timeout <= 0 ns; + ELSE + -- use MM access to restart timeout + IF strobe='1' THEN + timebegin <= NOW; + END IF; + timeout <= NOW - timebegin; + END IF; + END PROCESS; + END GENERATE; + + END GENERATE; + +END str; +
trunk/mm_file.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mm_file_pkg.vhd =================================================================== --- trunk/mm_file_pkg.vhd (nonexistent) +++ trunk/mm_file_pkg.vhd (revision 2) @@ -0,0 +1,757 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2017 +-- 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 . +-- +------------------------------------------------------------------------------- + +-- Author : +-- D. van der Schuur May 2012 Original for Python - file IO - VHDL +-- E. Kooistra feb 2017 Added purpose and description +-- Added procedures for external control in a +-- pure VHDL test bench. +-- +-- Purpose: Provide DUT access via MM bus through file IO per MM slave +-- Description: +-- This package provides file IO access to MM slaves and to the status of +-- the simulation: +-- +-- 1) MM slave access +-- Access to MM slaves is provided by component mm_file.vhd that first calls +-- mmf_file_create() and loop forever calling mmf_mm_from_file(). Each MM +-- slave has a dedicated pair of request (.ctrl) and response (.stat) IO +-- files. +-- The mmf_file_create() creates the .ctrl file and mmf_mm_from_file() reads +-- it to check whether there is a WR or RD access request. For a WR request +-- the wr_data and wr_addr are read from the .ctrl and output on the MM bus +-- via mm_mosi. For a RD access request the rd_addr is read from the .ctrl +-- and output on the MM bus via mm_mosi. The after the read latency the +-- rd_data is written to the .stat file that is then created and closed. +-- +-- wr rd _________ __________ +-- mmf_mm_bus_wr() ---> ctrl file --->| |---mm_mosi-->| | +-- | mm_file | | MM slave | +-- mmf_mm_bus_rd() <--- stat file <---|___\_____|<--mm_miso---|__________| +-- rd wr \ +-- \--> loop: mmf_mm_from_file() +-- +-- The ctrl file is created by mm_file at initialization and recreated by +-- every call of mmf_mm_from_file(). +-- The stat file is recreated by every call of mmf_mm_bus_rd(). +-- +-- 2) Simulator access +-- External access to the simulation is provided via a .ctrl file that +-- supports GET_SIM_TIME and then report the NOW time via the .stat file. +-- The simulation access is provided via a procedure mmf_poll_sim_ctrl_file() +-- that works similar component mm_file.vhd. +-- +-- wr rd +-- |---> ctrl file --->| +-- mmf_sim_get_now()| |mmf_poll_sim_ctrl_file() +-- |<--- stat file <---| \ +-- rd wr \ +-- \--> loop: mmf_sim_ctrl_from_file() +-- +-- The ctrl file is created by mmf_poll_sim_ctrl_file at initialization and +-- recreated by every call of mmf_sim_ctrl_from_file(). +-- The stat file is recreated by every call of mmf_sim_get_now(). +-- +-- A) External control by a Python script +-- A Python script can issue requests via the .ctrl files to control the +-- simulation and read the .stat files. This models the MM access via a +-- Monitoring and Control protocol via 1GbE. +-- +-- Internal procedures: +-- . mmf_file_create(filename: IN STRING); +-- . mmf_mm_from_file(SIGNAL mm_clk : IN STD_LOGIC; +-- . mmf_sim_ctrl_from_file(rd_filename: IN STRING; +-- +-- External procedures (used in a VHDL design to provide access to the MM +-- slaves and simulation via file IO): +-- . mm_file.vhd --> instead of a procedure MM slave file IO uses a component +-- . mmf_poll_sim_ctrl_file() +-- +-- B) External control by a VHDL process --> see tb_mm_file.vhd +-- Instead of a Python script the file IO access to the MM slaves can also +-- be used in a pure VHDL testbench. This is useful when the MM slave bus +-- signals (mm_mosi, mm_miso) are not available on the entity of the DUT +-- (device under test), which is typically the case when a complete FPGA +-- design needs to be simulated. +-- +-- Internal procedures: +-- . mmf_wait_for_file_status() +-- . mmf_wait_for_file_empty() +-- . mmf_wait_for_file_not_empty() +-- +-- External procedures (used in a VHDL test bench to provide access to the +-- MM slaves in a DUT VHDL design and simulation via file IO): +-- . mmf_mm_bus_wr() +-- . mmf_mm_bus_rd() +-- . mmf_sim_get_now() +-- +-- External function to create unique sim.ctrl/sim.stat filename per test bench in a multi tb +-- . mmf_slave_prefix() +-- +-- Remarks: +-- . The timing of the MM access in mmf_mm_bus_wr() and mmf_mm_bus_rd() and the +-- simulation access in mmf_sim_get_now() is not critical. The timing of the first +-- access depends on the tb. Due to falling_edge(mm_clk) in mmf_wait_for_file_*() +-- all subsequent accesses will start at falling_edge(mm_clk) + +LIBRARY IEEE, common_pkg_lib, common_ram_lib; +USE IEEE.STD_LOGIC_1164.ALL; +USE IEEE.NUMERIC_STD.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_pkg_lib.tb_common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; +USE work.tb_common_mem_pkg.ALL; +USE std.textio.ALL; +USE IEEE.std_logic_textio.ALL; +USE common_pkg_lib.common_str_pkg.ALL; + +PACKAGE mm_file_pkg IS + + -- Constants used by mm_file.vhd + CONSTANT c_mmf_mm_clk_period : TIME := 100 ps; -- Default mm_clk period in simulation. Set much faster than DP clock to speed up + -- simulation of MM access. Without file IO throttling 100 ps is a good balance + -- between simulation speed and file IO rate. + CONSTANT c_mmf_mm_timeout : TIME := 1000 ns; -- Default MM file IO timeout period. Set large enough to account for MM-DP clock + -- domain crossing delays. Use 0 ns to disable file IO throttling, to have file IO + -- at the mm_clk rate. + CONSTANT c_mmf_mm_pause : TIME := 100 ns; -- Default MM file IO pause period after timeout. Balance between file IO rate + -- reduction and responsiveness to new MM access. + + -- Procedure to (re)create empty file + PROCEDURE mmf_file_create(filename: IN STRING); + + -- Procedure to perform an MM access from file + PROCEDURE mmf_mm_from_file(SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_rst : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi; + SIGNAL mm_miso : IN t_mem_miso; + rd_filename: IN STRING; + wr_filename: IN STRING; + rd_latency: IN NATURAL); + + -- Procedure to process a simulation status request from the .ctrl file and provide response via the .stat file + PROCEDURE mmf_sim_ctrl_from_file(rd_filename: IN STRING; + wr_filename: IN STRING); + + -- Procedure to poll the simulation status + PROCEDURE mmf_poll_sim_ctrl_file(rd_file_name: IN STRING; + wr_file_name: IN STRING); + + -- Procedure to poll the simulation status + PROCEDURE mmf_poll_sim_ctrl_file(SIGNAL mm_clk : IN STD_LOGIC; + rd_file_name: IN STRING; + wr_file_name: IN STRING); + + -- Procedures that keep reading the file until it has been made empty or not empty by some other program, + -- to ensure the file is ready for a new write access + PROCEDURE mmf_wait_for_file_status(rd_filename : IN STRING; -- file name with extension + exit_on_empty : IN BOOLEAN; + SIGNAL mm_clk : IN STD_LOGIC); + + PROCEDURE mmf_wait_for_file_empty(rd_filename : IN STRING; -- file name with extension + SIGNAL mm_clk : IN STD_LOGIC); + PROCEDURE mmf_wait_for_file_not_empty(rd_filename : IN STRING; -- file name with extension + SIGNAL mm_clk : IN STD_LOGIC); + + -- Procedure to issue a write access via the MM request .ctrl file + PROCEDURE mmf_mm_bus_wr(filename : IN STRING; -- file name without extension + wr_addr : IN INTEGER; -- use integer to support full 32 bit range + wr_data : IN INTEGER; + SIGNAL mm_clk : IN STD_LOGIC); + + -- Procedure to issue a read access via the MM request .ctrl file and get the read data from the MM response file + PROCEDURE mmf_mm_bus_rd(filename : IN STRING; -- file name without extension + rd_latency : IN NATURAL; + rd_addr : IN INTEGER; -- use integer to support full 32 bit range + SIGNAL rd_data : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + SIGNAL mm_clk : IN STD_LOGIC); + -- . rd_latency = 1 + PROCEDURE mmf_mm_bus_rd(filename : IN STRING; + rd_addr : IN INTEGER; + SIGNAL rd_data : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + SIGNAL mm_clk : IN STD_LOGIC); + + -- Procedure that reads the rd_data every rd_interval until has the specified rd_value, the proc arguments can be understood as a sentence + PROCEDURE mmf_mm_wait_until_value(filename : IN STRING; -- file name without extension + rd_addr : IN INTEGER; + c_representation : IN STRING; -- treat rd_data as "SIGNED" or "UNSIGNED" 32 bit word + SIGNAL rd_data : INOUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + c_condition : IN STRING; -- ">", ">=", "=", "<=", "<", "/=" + c_rd_value : IN INTEGER; + c_rd_interval : IN TIME; + SIGNAL mm_clk : IN STD_LOGIC); + + -- Procedure to get NOW via simulator status + PROCEDURE mmf_sim_get_now(filename : IN STRING; -- file name without extension + SIGNAL rd_now : OUT STRING; + SIGNAL mm_clk : IN STD_LOGIC); + + -- Functions to create prefixes for the mmf file filename + FUNCTION mmf_prefix(name : STRING; index : NATURAL) RETURN STRING; -- generic prefix name with index to be used for a file IO filename + FUNCTION mmf_tb_prefix(tb : INTEGER) RETURN STRING; -- fixed test bench prefix with index tb to allow file IO with multi tb + FUNCTION mmf_subrack_prefix(subrack : INTEGER) RETURN STRING; -- fixed subrack prefix with index subrack to allow file IO with multi subracks that use same unb numbers + + -- Functions to create mmf file prefix that is unique per slave, for increasing number of hierarchy levels: + -- . return "filepath/s0_i0_" + -- . return "filepath/s0_i0_s1_i1_" + -- . return "filepath/s0_i0_s1_i1_s2_i2_" + -- . return "filepath/s0_i0_s1_i1_s2_i2_s3_i3_" + -- . return "filepath/s0_i0_s1_i1_s2_i2_s3_i3_s4_i4_" + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL; s4 : STRING; i4 : NATURAL) RETURN STRING; + + CONSTANT c_mmf_local_dir_path : STRING := "mmfiles/"; -- local directory in project file build directory + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL) RETURN STRING; + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL; s4 : STRING; i4 : NATURAL) RETURN STRING; + + ---------------------------------------------------------------------------- + -- Declare mm_file component to support positional generic and port mapping of many instances in a TB + ---------------------------------------------------------------------------- + COMPONENT mm_file + GENERIC( + g_file_prefix : STRING; + g_file_enable : STD_LOGIC := '1'; + g_mm_rd_latency : NATURAL := 2; + g_mm_timeout : TIME := c_mmf_mm_timeout; + g_mm_pause : TIME := c_mmf_mm_pause + ); + PORT ( + mm_rst : IN STD_LOGIC; + mm_clk : IN STD_LOGIC; + mm_master_out : OUT t_mem_mosi; + mm_master_in : IN t_mem_miso + ); + END COMPONENT; + +END mm_file_pkg; + +PACKAGE BODY mm_file_pkg IS + + PROCEDURE mmf_file_create(filename: IN STRING) IS + FILE created_file : TEXT OPEN write_mode IS filename; + BEGIN + -- Write the file with nothing in it + write(created_file, ""); + END; + + PROCEDURE mmf_mm_from_file(SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_rst : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi; + SIGNAL mm_miso : IN t_mem_miso; + rd_filename: IN STRING; + wr_filename: IN STRING; + rd_latency: IN NATURAL) IS + FILE rd_file : TEXT; + FILE wr_file : TEXT; + + VARIABLE open_status_rd: file_open_status; + VARIABLE open_status_wr: file_open_status; + + VARIABLE rd_line : LINE; + VARIABLE wr_line : LINE; + + -- Note: Both the address and the data are interpreted as 32-bit data! + -- This means one has to use leading zeros in the file when either is + -- less than 8 hex characters, e.g.: + -- (address) 0000000A + -- (data) DEADBEEF + -- ...as a hex address 'A' would fit in only 4 bits, causing an error in hread(). + VARIABLE v_addr_slv : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + VARIABLE v_data_slv : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + + VARIABLE v_rd_wr_str : STRING(1 TO 2); -- Contains 'RD' or 'WR' + + BEGIN + + proc_common_wait_until_low(mm_clk, mm_rst); + + -- We have to open the file explicitely so we can check the status + file_open(open_status_rd, rd_file, rd_filename, read_mode); + + -- open_status may throw an error if the file is being written to by some other program + IF open_status_rd=open_ok THEN + + IF NOT endfile(rd_file) THEN + -- The file is not empty: process its contents + + -- Read a line from it, first line indicates RD or WR + readline(rd_file, rd_line); + read(rd_line, v_rd_wr_str); + + -- The second line represents the address offset: + readline(rd_file, rd_line); + hread(rd_line, v_addr_slv); -- read the string as HEX and assign to SLV. + + -- Write only: The third line contains the data to write: + IF v_rd_wr_str="WR" THEN + readline(rd_file, rd_line); + hread(rd_line, v_data_slv); -- read the string as HEX and assign to SLV. + END IF; + + -- We're done reading MM request from the .ctrl file. + -- Clear the .ctrl file by closing and recreating it, because we don't want to do the same + -- MM request again the next time this procedure is called. + file_close(rd_file); + mmf_file_create(rd_filename); + + -- Execute the MM request to the MM slave + IF v_rd_wr_str="WR" THEN + print_str("[" & time_to_str(now) & "] " & rd_filename & ": Writing 0x" & slv_to_hex(v_data_slv) & " to address 0x" & slv_to_hex(v_addr_slv)); + -- Treat 32 bit hex data from file as 32 bit VHDL INTEGER, so need to use signed TO_SINT() to avoid out of NATURAL range + -- warning in simulation due to '1' sign bit, because unsigned VHDL NATURAL only fits 31 bits + proc_mem_mm_bus_wr(TO_UINT(v_addr_slv), TO_SINT(v_data_slv), mm_clk, mm_miso, mm_mosi); + + ELSIF v_rd_wr_str="RD" THEN + proc_mem_mm_bus_rd(TO_UINT(v_addr_slv), mm_clk, mm_miso, mm_mosi); + IF rd_latency>0 THEN + proc_mem_mm_bus_rd_latency(rd_latency, mm_clk); + END IF; + v_data_slv := mm_miso.rddata(31 DOWNTO 0); + print_str("[" & time_to_str(now) & "] " & rd_filename & ": Reading from address 0x" & slv_to_hex(v_addr_slv) & ": 0x" & slv_to_hex(v_data_slv)); + + -- Write the RD response read data to the .stat file + file_open(open_status_wr, wr_file, wr_filename, write_mode); + hwrite(wr_line, v_data_slv); + writeline(wr_file, wr_line); + file_close(wr_file); + END IF; + + ELSE + -- Nothing to process; wait one MM clock cycle. + proc_common_wait_some_cycles(mm_clk, 1); + END IF; + + ELSE + REPORT "mmf_mm_from_file() could not open " & rd_filename & " at " & time_to_str(now) SEVERITY NOTE; + -- Try again next time; wait one MM clock cycle. + proc_common_wait_some_cycles(mm_clk, 1); + END IF; + + -- The END implicitely close the rd_file, if still necessary. + END; + + + PROCEDURE mmf_sim_ctrl_from_file(rd_filename: IN STRING; + wr_filename: IN STRING) IS + + FILE rd_file : TEXT; + FILE wr_file : TEXT; + + VARIABLE open_status_rd: file_open_status; + VARIABLE open_status_wr: file_open_status; + + VARIABLE rd_line : LINE; + VARIABLE wr_line : LINE; + + VARIABLE v_rd_wr_str : STRING(1 TO 12); -- "GET_SIM_TIME" + + BEGIN + + -- We have to open the file explicitely so we can check the status + file_open(open_status_rd, rd_file, rd_filename, read_mode); + + -- open_status may throw an error if the file is being written to by some other program + IF open_status_rd=open_ok THEN + + IF NOT endfile(rd_file) THEN + -- The file is not empty: process its contents + + -- Read a line from it, interpret the simulation request + readline(rd_file, rd_line); + read(rd_line, v_rd_wr_str); + + -- We're done reading this simulation request .ctrl file. Clear the file by closing and recreating it. + file_close(rd_file); + mmf_file_create(rd_filename); + + -- Execute the simulation request + IF v_rd_wr_str="GET_SIM_TIME" THEN + -- Write the GET_SIM_TIME response time NOW to the .stat file + file_open(open_status_wr, wr_file, wr_filename, write_mode); + write(wr_line, time_to_str(now)); + writeline(wr_file, wr_line); + file_close(wr_file); + END IF; + + ELSE + -- Nothing to process; wait in procedure mmf_poll_sim_ctrl_file + NULL; + END IF; + + ELSE + REPORT "mmf_mm_from_file() could not open " & rd_filename & " at " & time_to_str(now) SEVERITY NOTE; + -- Try again next time; wait in procedure mmf_poll_sim_ctrl_file + END IF; + + -- The END implicitely close the rd_file, if still necessary. + END; + + + PROCEDURE mmf_poll_sim_ctrl_file(rd_file_name: IN STRING; wr_file_name : IN STRING) IS + BEGIN + -- Create the ctrl file that we're going to read from + print_str("[" & time_to_str(now) & "] " & rd_file_name & ": Created" ); + mmf_file_create(rd_file_name); + + WHILE TRUE LOOP + mmf_sim_ctrl_from_file(rd_file_name, wr_file_name); + WAIT FOR 1 ns; + END LOOP; + + END; + + + PROCEDURE mmf_poll_sim_ctrl_file(SIGNAL mm_clk : IN STD_LOGIC; + rd_file_name: IN STRING; wr_file_name : IN STRING) IS + BEGIN + -- Create the ctrl file that we're going to read from + print_str("[" & time_to_str(now) & "] " & rd_file_name & ": Created" ); + mmf_file_create(rd_file_name); + + WHILE TRUE LOOP + mmf_sim_ctrl_from_file(rd_file_name, wr_file_name); + proc_common_wait_some_cycles(mm_clk, 1); + END LOOP; + + END; + + + PROCEDURE mmf_wait_for_file_status(rd_filename : IN STRING; -- file name with extension + exit_on_empty : IN BOOLEAN; + SIGNAL mm_clk : IN STD_LOGIC) IS + FILE rd_file : TEXT; + VARIABLE open_status_rd : file_open_status; + VARIABLE v_endfile : BOOLEAN; + BEGIN + -- Check on falling_edge(mm_clk) because mmf_mm_from_file() operates on rising_edge(mm_clk) + -- Note: In fact the file IO also works fine when rising_edge() is used, but then + -- tb_tb_mm_file.vhd takes about 1% more mm_clk cycles + WAIT UNTIL falling_edge(mm_clk); + + -- Keep reading the file until it has become empty by some other program + WHILE TRUE LOOP + -- Open the file in read mode to check whether it is empty + file_open(open_status_rd, rd_file, rd_filename, read_mode); + -- open_status may throw an error if the file is being written to by some other program + IF open_status_rd=open_ok THEN + v_endfile := endfile(rd_file); + file_close(rd_file); + IF exit_on_empty THEN + IF v_endfile THEN + -- The file is empty; continue + EXIT; + ELSE + -- The file is not empty; wait one MM clock cycle. + WAIT UNTIL falling_edge(mm_clk); + END IF; + ELSE + IF v_endfile THEN + -- The file is empty; wait one MM clock cycle. + WAIT UNTIL falling_edge(mm_clk); + ELSE + -- The file is not empty; continue + EXIT; + END IF; + END IF; + ELSE + REPORT "mmf_wait_for_file_status() could not open " & rd_filename & " at " & time_to_str(now) SEVERITY NOTE; + WAIT UNTIL falling_edge(mm_clk); + END IF; + END LOOP; + -- The END implicitely close the file, if still necessary. + END; + + PROCEDURE mmf_wait_for_file_empty(rd_filename : IN STRING; -- file name with extension + SIGNAL mm_clk : IN STD_LOGIC) IS + BEGIN + mmf_wait_for_file_status(rd_filename, TRUE, mm_clk); + END; + + PROCEDURE mmf_wait_for_file_not_empty(rd_filename : IN STRING; -- file name with extension + SIGNAL mm_clk : IN STD_LOGIC) IS + BEGIN + mmf_wait_for_file_status(rd_filename, FALSE, mm_clk); + END; + + PROCEDURE mmf_mm_bus_wr(filename : IN STRING; -- file name without extension + wr_addr : IN INTEGER; -- use integer to support full 32 bit range + wr_data : IN INTEGER; + SIGNAL mm_clk : IN STD_LOGIC) IS + CONSTANT ctrl_filename : STRING := filename & ".ctrl"; + FILE ctrl_file : TEXT; + VARIABLE open_status_wr : file_open_status; + VARIABLE wr_line : LINE; + + BEGIN + -- Write MM WR access to the .ctrl file. + -- The MM device is ready for a new MM request, because any previous MM request has finished at + -- mmf_mm_bus_wr() or mmf_mm_bus_rd() procedure exit, therefore just overwrite the .ctrl file. + file_open(open_status_wr, ctrl_file, ctrl_filename, write_mode); + -- open_status may throw an error if the file is being written to by some other program + IF open_status_wr=open_ok THEN + write(wr_line, STRING'("WR")); + writeline(ctrl_file, wr_line); + hwrite(wr_line, TO_SVEC(wr_addr, c_word_w)); + writeline(ctrl_file, wr_line); + hwrite(wr_line, TO_SVEC(wr_data, c_word_w)); + writeline(ctrl_file, wr_line); + file_close(ctrl_file); + ELSE + REPORT "mmf_mm_bus_wr() could not open " & ctrl_filename & " at " & time_to_str(now) SEVERITY NOTE; + END IF; + + -- Prepare for next MM request + -- Keep reading the .ctrl file until it is empty, to ensure that the MM device is ready for a new MM request + mmf_wait_for_file_empty(ctrl_filename, mm_clk); + + -- The END implicitely close the ctrl_file, if still necessary. + END; + + PROCEDURE mmf_mm_bus_rd(filename : IN STRING; -- file name without extension + rd_latency : IN NATURAL; + rd_addr : IN INTEGER; -- use integer to support full 32 bit range + SIGNAL rd_data : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + SIGNAL mm_clk : IN STD_LOGIC) IS + CONSTANT ctrl_filename : STRING := filename & ".ctrl"; + CONSTANT stat_filename : STRING := filename & ".stat"; + FILE ctrl_file : TEXT; + FILE stat_file : TEXT; + VARIABLE open_status_wr : file_open_status; + VARIABLE open_status_rd : file_open_status; + VARIABLE wr_line : LINE; + VARIABLE rd_line : LINE; + VARIABLE v_rd_data : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + + BEGIN + -- Clear the .stat file by recreating it, because we don't want to do read old file data again + mmf_file_create(stat_filename); + + -- Write MM RD access to the .ctrl file. + -- The MM device is ready for a new MM request, because any previous MM request has finished at + -- mmf_mm_bus_wr() or mmf_mm_bus_rd() procedure exit, therefore just overwrite the .ctrl file. + file_open(open_status_wr, ctrl_file, ctrl_filename, write_mode); + -- open_status may throw an error if the file is being written to by some other program + IF open_status_wr=open_ok THEN + write(wr_line, STRING'("RD")); + writeline(ctrl_file, wr_line); + hwrite(wr_line, TO_SVEC(rd_addr, c_word_w)); + writeline(ctrl_file, wr_line); + file_close(ctrl_file); + ELSE + REPORT "mmf_mm_bus_rd() could not open " & ctrl_filename & " at " & time_to_str(now) SEVERITY FAILURE; + END IF; + + -- Wait until the MM RD access has written the read data to the .stat file + mmf_wait_for_file_not_empty(stat_filename, mm_clk); + + -- Read the MM RD access read data from the .stat file + file_open(open_status_rd, stat_file, stat_filename, read_mode); + -- open_status may throw an error if the file is being written to by some other program + IF open_status_rd=open_ok THEN + readline(stat_file, rd_line); + hread(rd_line, v_rd_data); + file_close(stat_file); + rd_data <= v_rd_data; + -- wait to ensure rd_data has got v_rd_data, otherwise rd_data still holds the old data on procedure exit + -- the wait should be < mm_clk period/2 to not affect the read rate + WAIT FOR 1 fs; + ELSE + REPORT "mmf_mm_bus_rd() could not open " & stat_filename & " at " & time_to_str(now) SEVERITY FAILURE; + END IF; + + -- No need to prepare for next MM request, because: + -- . the .ctrl file must already be empty because the .stat file was there + -- . the .stat file will be cleared on this procedure entry + + -- The END implicitely closes the files, if still necessary + END; + + -- rd_latency = 1 + PROCEDURE mmf_mm_bus_rd(filename : IN STRING; + rd_addr : IN INTEGER; + SIGNAL rd_data : OUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + SIGNAL mm_clk : IN STD_LOGIC) IS + BEGIN + mmf_mm_bus_rd(filename, 1, rd_addr, rd_data, mm_clk); + END; + + PROCEDURE mmf_mm_wait_until_value(filename : IN STRING; -- file name without extension + rd_addr : IN INTEGER; + c_representation : IN STRING; -- treat rd_data as "SIGNED" or "UNSIGNED" 32 bit word + SIGNAL rd_data : INOUT STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0); + c_condition : IN STRING; -- ">", ">=", "=", "<=", "<", "/=" + c_rd_value : IN INTEGER; + c_rd_interval : IN TIME; + SIGNAL mm_clk : IN STD_LOGIC) IS + BEGIN + WHILE TRUE LOOP + -- Read current + mmf_mm_bus_rd(filename, rd_addr, rd_data, mm_clk); -- only read low part + IF c_representation="SIGNED" THEN + IF c_condition=">" THEN IF TO_SINT(rd_data)> c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition=">=" THEN IF TO_SINT(rd_data)>=c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition="/=" THEN IF TO_SINT(rd_data)/=c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition="<=" THEN IF TO_SINT(rd_data)<=c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition="<" THEN IF TO_SINT(rd_data)< c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSE IF TO_SINT(rd_data) =c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; -- default: "=" + END IF; + ELSE -- default: UNSIGED + IF c_condition=">" THEN IF TO_UINT(rd_data)> c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition=">=" THEN IF TO_UINT(rd_data)>=c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition="/=" THEN IF TO_UINT(rd_data)/=c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition="<=" THEN IF TO_UINT(rd_data)<=c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSIF c_condition="<" THEN IF TO_UINT(rd_data)< c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; + ELSE IF TO_UINT(rd_data) =c_rd_value THEN EXIT; ELSE WAIT FOR c_rd_interval; END IF; -- default: "=" + END IF; + END IF; + END LOOP; + END mmf_mm_wait_until_value; + + + PROCEDURE mmf_sim_get_now(filename : IN STRING; -- file name without extension + SIGNAL rd_now : OUT STRING; + SIGNAL mm_clk : IN STD_LOGIC) IS + CONSTANT ctrl_filename : STRING := filename & ".ctrl"; + CONSTANT stat_filename : STRING := filename & ".stat"; + FILE ctrl_file : TEXT; + FILE stat_file : TEXT; + VARIABLE open_status_wr : file_open_status; + VARIABLE open_status_rd : file_open_status; + VARIABLE wr_line : LINE; + VARIABLE rd_line : LINE; + VARIABLE v_rd_now : STRING(rd_now'RANGE); + + BEGIN + -- Clear the sim.stat file by recreating it, because we don't want to do read old simulator status again + mmf_file_create(stat_filename); + + -- Write GET_SIM_TIME to the sim.ctrl file + -- The simulation is ready for a new simulation status request, because any previous simulation status request has finished at + -- mmf_sim_get_now() procedure exit, therefore just overwrite the .ctrl file. + file_open(open_status_wr, ctrl_file, ctrl_filename, write_mode); + -- open_status may throw an error if the file is being written to by some other program + IF open_status_wr=open_ok THEN + write(wr_line, STRING'("GET_SIM_TIME")); + writeline(ctrl_file, wr_line); + file_close(ctrl_file); + ELSE + REPORT "mmf_sim_get_now() could not open " & ctrl_filename & " at " & time_to_str(now) SEVERITY FAILURE; + END IF; + + -- Wait until the simulation has written the simulation status to the sim.stat file + mmf_wait_for_file_not_empty(stat_filename, mm_clk); + + -- Read the GET_SIM_TIME simulation status from the .stat file + file_open(open_status_rd, stat_file, stat_filename, read_mode); + -- open_status may throw an error if the file is being written to by some other program + IF open_status_rd=open_ok THEN + readline(stat_file, rd_line); + read(rd_line, v_rd_now); + file_close(stat_file); + rd_now <= v_rd_now; + print_str("GET_SIM_TIME = " & v_rd_now & " at " & time_to_str(now)); + ELSE + REPORT "mmf_sim_get_now() could not open " & stat_filename & " at " & time_to_str(now) SEVERITY FAILURE; + END IF; + + -- No need to prepare for next simulation status request, because: + -- . the .ctrl file must already be empty because the .stat file was there + -- . the .stat file will be cleared on this procedure entry + + -- The END implicitely closes the files, if still necessary + END; + + -- Functions to create prefixes for the mmf file filename + FUNCTION mmf_prefix(name : STRING; index : NATURAL) RETURN STRING IS + BEGIN + RETURN name & "_" & int_to_str(index) & "_"; + END; + + FUNCTION mmf_tb_prefix(tb : INTEGER) RETURN STRING IS + BEGIN + RETURN mmf_prefix("TB", tb); + END; + + FUNCTION mmf_subrack_prefix(subrack : INTEGER) RETURN STRING IS + BEGIN + RETURN mmf_prefix("SUBRACK", subrack); + END; + + -- Functions to create mmf file prefix that is unique per slave, for increasing number of hierarchy levels: + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL) RETURN STRING IS + BEGIN + RETURN dir_path & mmf_prefix(s0, i0); + END; + + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL) RETURN STRING IS + BEGIN + RETURN dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1); + END; + + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL) RETURN STRING IS + BEGIN + RETURN dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1) & mmf_prefix(s2, i2); + END; + + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL) RETURN STRING IS + BEGIN + RETURN dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1) & mmf_prefix(s2, i2) & mmf_prefix(s3, i3); + END; + + FUNCTION mmf_slave_prefix(dir_path, s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL; s4 : STRING; i4 : NATURAL) RETURN STRING IS + BEGIN + RETURN dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1) & mmf_prefix(s2, i2) & mmf_prefix(s3, i3) & mmf_prefix(s4, i4); + END; + + -- Use local dir_path + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL) RETURN STRING IS + BEGIN + RETURN c_mmf_local_dir_path & mmf_prefix(s0, i0); + END; + + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL) RETURN STRING IS + BEGIN + RETURN c_mmf_local_dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1); + END; + + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL) RETURN STRING IS + BEGIN + RETURN c_mmf_local_dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1) & mmf_prefix(s2, i2); + END; + + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL) RETURN STRING IS + BEGIN + RETURN c_mmf_local_dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1) & mmf_prefix(s2, i2) & mmf_prefix(s3, i3); + END; + + FUNCTION mmf_slave_prefix(s0 : STRING; i0 : NATURAL; s1 : STRING; i1 : NATURAL; s2 : STRING; i2 : NATURAL; s3 : STRING; i3 : NATURAL; s4 : STRING; i4 : NATURAL) RETURN STRING IS + BEGIN + RETURN c_mmf_local_dir_path & mmf_prefix(s0, i0) & mmf_prefix(s1, i1) & mmf_prefix(s2, i2) & mmf_prefix(s3, i3) & mmf_prefix(s4, i4); + END; + +END mm_file_pkg; +
trunk/mm_file_pkg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/mm_file_unb_pkg.vhd =================================================================== --- trunk/mm_file_unb_pkg.vhd (nonexistent) +++ trunk/mm_file_unb_pkg.vhd (revision 2) @@ -0,0 +1,98 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2012 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib; +USE common_pkg_lib.common_pkg.ALL; +USE common_pkg_lib.common_str_pkg.ALL; +USE work.mm_file_pkg.ALL; + +PACKAGE mm_file_unb_pkg IS + + TYPE t_c_mmf_unb_sys IS RECORD + nof_unb : NATURAL; -- Nof used UniBoard in our system [0..nof_unb-1] + nof_fn : NATURAL; -- Nof used FNs [0..nof_fn-1] per UniBoard + nof_bn : NATURAL; -- Nof used BNs [0..nof_fn-1] per UniBoard + END RECORD; + + CONSTANT c_mmf_unb_nof_fn : NATURAL := 4; + CONSTANT c_mmf_unb_nof_bn : NATURAL := 4; + CONSTANT c_mmf_unb_nof_pn : NATURAL := c_mmf_unb_nof_fn + c_mmf_unb_nof_bn; -- = 8 + + -- use fixed central directory to ease use of Python test case with Modelsim + CONSTANT c_mmf_unb_file_path : STRING := "$UNB/Software/python/sim/"; + + -- create mmf file prefix that is unique per slave + FUNCTION mmf_unb_file_prefix(sys: t_c_mmf_unb_sys; node: NATURAL) RETURN STRING; + FUNCTION mmf_unb_file_prefix( unb, node: NATURAL; node_type: STRING) RETURN STRING; -- unb 0,1,..., node = 0:3 for FN or BN + FUNCTION mmf_unb_file_prefix( unb, node: NATURAL) RETURN STRING; -- unb 0,1,..., node = 0:7, with 0:3 for FN and 4:7 for BN + FUNCTION mmf_unb_file_prefix(tb, unb, node: NATURAL) RETURN STRING; -- idem, with extra index tb = 0,1,... for use with multi testbench + FUNCTION mmf_unb_file_prefix(tb, subrack, unb, node: NATURAL) RETURN STRING; -- idem, with extra index subrack = 0,1,... to support same local unb range per subrack + +END mm_file_unb_pkg; + +PACKAGE BODY mm_file_unb_pkg IS + + FUNCTION mmf_unb_file_prefix(sys: t_c_mmf_unb_sys; node: NATURAL) RETURN STRING IS + -- This function is used to create files for node function instances that (can) run on + -- an FN or a BN. One generate loop can be used for all node instances, no need to + -- use a separate FOR loop for the back nodes and the front nodes as this function + -- determines the UniBoard index for you. + VARIABLE v_nodes_per_board : NATURAL := sys.nof_fn + sys.nof_bn; + VARIABLE v_board_index : NATURAL := node/v_nodes_per_board; + VARIABLE v_node_nr : NATURAL := node REM v_nodes_per_board; + VARIABLE v_node_type : STRING(1 TO 2) := sel_a_b(v_node_nr>=sys.nof_fn, "BN", "FN"); + VARIABLE v_node_index : NATURAL := sel_a_b(v_node_nr>=sys.nof_fn, v_node_nr-sys.nof_fn, v_node_nr); + BEGIN + RETURN mmf_slave_prefix(c_mmf_unb_file_path, "UNB", v_board_index, v_node_type, v_node_index); + END; + + FUNCTION mmf_unb_file_prefix(unb, node: NATURAL; node_type: STRING) RETURN STRING IS + -- Use this function and pass the UNB and node type BN 0:3 or node type FN 0:3 index. + BEGIN + RETURN mmf_slave_prefix(c_mmf_unb_file_path, "UNB", unb, node_type, node); + END; + + FUNCTION mmf_unb_file_prefix(unb, node: NATURAL) RETURN STRING IS + -- Use this function and pass the UNB and node 0:7 index. + CONSTANT c_node_type : STRING(1 TO 2) := sel_a_b(node>=c_mmf_unb_nof_fn, "BN", "FN"); + CONSTANT c_node_nr : NATURAL := node MOD c_mmf_unb_nof_fn; -- PN 0:3 --> FN 0:3, PN 4:7 --> BN 0:3 + BEGIN + RETURN mmf_slave_prefix(c_mmf_unb_file_path, "UNB", unb, c_node_type, c_node_nr); + END; + + FUNCTION mmf_unb_file_prefix(tb, unb, node: NATURAL) RETURN STRING IS + -- Use this function and pass the UNB and node 0:7 index and a test bench index to allow file IO with multi tb. + CONSTANT c_node_type : STRING(1 TO 2) := sel_a_b(node>=c_mmf_unb_nof_fn, "BN", "FN"); + CONSTANT c_node_nr : NATURAL := node MOD c_mmf_unb_nof_fn; -- PN 0:3 --> FN 0:3, PN 4:7 --> BN 0:3 + BEGIN + RETURN mmf_slave_prefix(c_mmf_unb_file_path, "TB", tb, "UNB", unb, c_node_type, c_node_nr); + END; + + FUNCTION mmf_unb_file_prefix(tb, subrack, unb, node: NATURAL) RETURN STRING IS + -- Use this function and pass the UNB and node 0:7 index and a test bench index to allow file IO with multi subrack and multi tb. + CONSTANT c_node_type : STRING(1 TO 2) := sel_a_b(node>=c_mmf_unb_nof_fn, "BN", "FN"); + CONSTANT c_node_nr : NATURAL := node MOD c_mmf_unb_nof_fn; -- PN 0:3 --> FN 0:3, PN 4:7 --> BN 0:3 + BEGIN + RETURN mmf_slave_prefix(c_mmf_unb_file_path, "TB", tb, "SUBRACK", subrack, "UNB", unb, c_node_type, c_node_nr); + END; + +END mm_file_unb_pkg; +
trunk/mm_file_unb_pkg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/tb_common_mem_mux.vhd =================================================================== --- trunk/tb_common_mem_mux.vhd (nonexistent) +++ trunk/tb_common_mem_mux.vhd (revision 2) @@ -0,0 +1,126 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2009 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +-- +------------------------------------------------------------------------------- + +LIBRARY IEEE, common_pkg_lib, 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 common_pkg_lib.tb_common_pkg.ALL; +USE work.tb_common_mem_pkg.ALL; + +ENTITY tb_common_mem_mux IS + GENERIC ( + g_nof_mosi : POSITIVE := 16; -- Number of memory interfaces in the array. + g_mult_addr_w : POSITIVE := 4 -- Address width of each memory-interface element in the array. + ); +END tb_common_mem_mux; + +-- Usage: +-- > as 10 +-- > run -all + + +ARCHITECTURE tb OF tb_common_mem_mux IS + + CONSTANT clk_period : TIME := 10 ns; + + CONSTANT c_data_w : NATURAL := 32; + CONSTANT c_test_ram : t_c_mem := (latency => 1, + adr_w => g_mult_addr_w, + dat_w => c_data_w, + nof_dat => 2**g_mult_addr_w, + init_sl => '0'); + SIGNAL rst : STD_LOGIC; + SIGNAL clk : STD_LOGIC := '1'; + SIGNAL tb_end : STD_LOGIC; + + SIGNAL mosi_arr : t_mem_mosi_arr(g_nof_mosi - 1 DOWNTO 0); + SIGNAL miso_arr : t_mem_miso_arr(g_nof_mosi - 1 DOWNTO 0); + SIGNAL mosi : t_mem_mosi; + SIGNAL miso : t_mem_miso; + +BEGIN + + clk <= NOT clk OR tb_end AFTER clk_period/2; + rst <= '1', '0' AFTER clk_period*5; + + p_stimuli : PROCESS + VARIABLE temp : INTEGER; + BEGIN + tb_end <= '0'; + mosi <= c_mem_mosi_rst; + + -- Write the whole memory range + FOR I IN 0 TO g_nof_mosi-1 LOOP + FOR J IN 0 TO 2**g_mult_addr_w-1 LOOP + proc_mem_mm_bus_wr(I*2**g_mult_addr_w + J, I+J, clk, mosi); + END LOOP; + END LOOP; + + -- Read back the whole range and check if data is as expected + FOR I IN 0 TO g_nof_mosi-1 LOOP + FOR J IN 0 TO 2**g_mult_addr_w-1 LOOP + proc_mem_mm_bus_rd(I*2**g_mult_addr_w + J, clk, mosi); + proc_common_wait_some_cycles(clk, 1); + temp := TO_UINT(miso.rddata(31 DOWNTO 0)); + IF(temp /= I+J) THEN + REPORT "Error! Readvalue is not as expected" SEVERITY ERROR; + END IF; + END LOOP; + END LOOP; + tb_end <= '1'; + WAIT; + END PROCESS; + + generation_of_test_rams : FOR I IN 0 TO g_nof_mosi-1 GENERATE + u_test_rams : ENTITY common_ram_lib.common_ram_r_w + GENERIC MAP ( + g_ram => c_test_ram, + g_init_file => "UNUSED" + ) + PORT MAP ( + rst => rst, + clk => clk, + clken => '1', + wr_en => mosi_arr(I).wr, + wr_adr => mosi_arr(I).address(g_mult_addr_w-1 DOWNTO 0), + wr_dat => mosi_arr(I).wrdata(c_data_w-1 DOWNTO 0), + rd_en => mosi_arr(I).rd, + rd_adr => mosi_arr(I).address(g_mult_addr_w-1 DOWNTO 0), + rd_dat => miso_arr(I).rddata(c_data_w-1 DOWNTO 0), + rd_val => miso_arr(I).rdval + ); + END GENERATE; + + d_dut : ENTITY work.common_mem_mux + GENERIC MAP ( + g_nof_mosi => g_nof_mosi, + g_mult_addr_w => g_mult_addr_w + ) + PORT MAP ( + mosi_arr => mosi_arr, + miso_arr => miso_arr, + mosi => mosi, + miso => miso + ); + +END tb;
trunk/tb_common_mem_mux.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/tb_common_mem_pkg.vhd =================================================================== --- trunk/tb_common_mem_pkg.vhd (nonexistent) +++ trunk/tb_common_mem_pkg.vhd (revision 2) @@ -0,0 +1,240 @@ +------------------------------------------------------------------------------- +-- +-- 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_ram_lib; +USE IEEE.std_logic_1164.ALL; +USE common_pkg_lib.common_pkg.ALL; +USE common_ram_lib.common_ram_pkg.ALL; + + +PACKAGE tb_common_mem_pkg IS + + ------------------------------------------------------------------------------ + -- MM bus access functions + ------------------------------------------------------------------------------ + + -- The mm_miso input needs to be declared as signal, because otherwise the + -- procedure does not notice a change (also not when the mm_clk is declared + -- as signal). + + -- Write data to the MM bus + PROCEDURE proc_mem_mm_bus_wr(CONSTANT wr_addr : IN NATURAL; -- [31:0] + CONSTANT wr_data : IN INTEGER; -- [31:0] + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_miso : IN t_mem_miso; -- used for waitrequest + SIGNAL mm_mosi : OUT t_mem_mosi); + + PROCEDURE proc_mem_mm_bus_wr(CONSTANT wr_addr : IN NATURAL; -- [31:0] + CONSTANT wr_data : IN INTEGER; -- [31:0] + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi); + + PROCEDURE proc_mem_mm_bus_wr(CONSTANT wr_addr : IN NATURAL; -- [31:0] + CONSTANT wr_data : IN STD_LOGIC_VECTOR; -- [31:0] + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi); + + -- Read data request to the MM bus + PROCEDURE proc_mem_mm_bus_rd(CONSTANT rd_addr : IN NATURAL; -- [31:0] + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_miso : IN t_mem_miso; -- used for waitrequest + SIGNAL mm_mosi : OUT t_mem_mosi); + + PROCEDURE proc_mem_mm_bus_rd(CONSTANT rd_addr : IN NATURAL; -- [31:0] + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi); + + -- Wait for read data valid after read latency mm_clk cycles + PROCEDURE proc_mem_mm_bus_rd_latency(CONSTANT c_rd_latency : IN NATURAL; + SIGNAL mm_clk : IN STD_LOGIC); + + -- Write array of data words to the memory + PROCEDURE proc_mem_write_ram(CONSTANT offset : IN NATURAL; + CONSTANT nof_data : IN NATURAL; + CONSTANT data_arr : IN t_slv_32_arr; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi); + + PROCEDURE proc_mem_write_ram(CONSTANT data_arr : IN t_slv_32_arr; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi); + + -- Read array of data words from the memory + PROCEDURE proc_mem_read_ram(CONSTANT offset : IN NATURAL; + CONSTANT nof_data : IN NATURAL; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi; + SIGNAL mm_miso : IN t_mem_miso; + SIGNAL data_arr : OUT t_slv_32_arr); + + PROCEDURE proc_mem_read_ram(SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi; + SIGNAL mm_miso : IN t_mem_miso; + SIGNAL data_arr : OUT t_slv_32_arr); + +END tb_common_mem_pkg; + + +PACKAGE BODY tb_common_mem_pkg IS + + ------------------------------------------------------------------------------ + -- Private functions + ------------------------------------------------------------------------------ + + -- Issues a rd or a wr MM access + PROCEDURE proc_mm_access(SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_access : OUT STD_LOGIC) IS + BEGIN + mm_access <= '1'; + WAIT UNTIL rising_edge(mm_clk); + mm_access <= '0'; + END proc_mm_access; + + -- Issues a rd or a wr MM access and wait for it to have finished + PROCEDURE proc_mm_access(SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_waitreq : IN STD_LOGIC; + SIGNAL mm_access : OUT STD_LOGIC) IS + BEGIN + mm_access <= '1'; + WAIT UNTIL rising_edge(mm_clk); + WHILE mm_waitreq='1' LOOP + WAIT UNTIL rising_edge(mm_clk); + END LOOP; + mm_access <= '0'; + END proc_mm_access; + + ------------------------------------------------------------------------------ + -- Public functions + ------------------------------------------------------------------------------ + + -- Write data to the MM bus + PROCEDURE proc_mem_mm_bus_wr(CONSTANT wr_addr : IN NATURAL; + CONSTANT wr_data : IN INTEGER; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_miso : IN t_mem_miso; + SIGNAL mm_mosi : OUT t_mem_mosi) IS + BEGIN + mm_mosi.address <= TO_MEM_ADDRESS(wr_addr); + mm_mosi.wrdata <= TO_MEM_DATA(wr_data); + proc_mm_access(mm_clk, mm_miso.waitrequest, mm_mosi.wr); + END proc_mem_mm_bus_wr; + + PROCEDURE proc_mem_mm_bus_wr(CONSTANT wr_addr : IN NATURAL; + CONSTANT wr_data : IN INTEGER; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi) IS + BEGIN + mm_mosi.address <= TO_MEM_ADDRESS(wr_addr); + mm_mosi.wrdata <= TO_MEM_DATA(wr_data); + proc_mm_access(mm_clk, mm_mosi.wr); + END proc_mem_mm_bus_wr; + + PROCEDURE proc_mem_mm_bus_wr(CONSTANT wr_addr : IN NATURAL; + CONSTANT wr_data : IN STD_LOGIC_VECTOR; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi) IS + BEGIN + mm_mosi.address <= TO_MEM_ADDRESS(wr_addr); + mm_mosi.wrdata <= RESIZE_UVEC(wr_data, c_mem_data_w); + proc_mm_access(mm_clk, mm_mosi.wr); + END proc_mem_mm_bus_wr; + + + -- Read data request to the MM bus + -- Use proc_mem_mm_bus_rd_latency() to wait for the MM MISO rd_data signal + -- to show the data after some read latency + PROCEDURE proc_mem_mm_bus_rd(CONSTANT rd_addr : IN NATURAL; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_miso : IN t_mem_miso; + SIGNAL mm_mosi : OUT t_mem_mosi) IS + BEGIN + mm_mosi.address <= TO_MEM_ADDRESS(rd_addr); + proc_mm_access(mm_clk, mm_miso.waitrequest, mm_mosi.rd); + END proc_mem_mm_bus_rd; + + PROCEDURE proc_mem_mm_bus_rd(CONSTANT rd_addr : IN NATURAL; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi) IS + BEGIN + mm_mosi.address <= TO_MEM_ADDRESS(rd_addr); + proc_mm_access(mm_clk, mm_mosi.rd); + END proc_mem_mm_bus_rd; + + -- Wait for read data valid after read latency mm_clk cycles + -- Directly assign mm_miso.rddata to capture the read data + PROCEDURE proc_mem_mm_bus_rd_latency(CONSTANT c_rd_latency : IN NATURAL; + SIGNAL mm_clk : IN STD_LOGIC) IS + BEGIN + FOR I IN 0 TO c_rd_latency-1 LOOP WAIT UNTIL rising_edge(mm_clk); END LOOP; + END proc_mem_mm_bus_rd_latency; + + + -- Write array of data words to the memory + PROCEDURE proc_mem_write_ram(CONSTANT offset : IN NATURAL; + CONSTANT nof_data : IN NATURAL; + CONSTANT data_arr : IN t_slv_32_arr; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi) IS + CONSTANT c_data_arr : t_slv_32_arr(data_arr'LENGTH-1 DOWNTO 0) := data_arr; -- map to fixed range [h:0] + BEGIN + FOR I IN 0 TO nof_data-1 LOOP + proc_mem_mm_bus_wr(offset + I, c_data_arr(I), mm_clk, mm_mosi); + END LOOP; + END proc_mem_write_ram; + + PROCEDURE proc_mem_write_ram(CONSTANT data_arr : IN t_slv_32_arr; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi) IS + CONSTANT c_offset : NATURAL := 0; + CONSTANT c_nof_data : NATURAL := data_arr'LENGTH; + BEGIN + proc_mem_write_ram(c_offset, c_nof_data, data_arr, mm_clk, mm_mosi); + END proc_mem_write_ram; + + -- Read array of data words from the memory + PROCEDURE proc_mem_read_ram(CONSTANT offset : IN NATURAL; + CONSTANT nof_data : IN NATURAL; + SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi; + SIGNAL mm_miso : IN t_mem_miso; + SIGNAL data_arr : OUT t_slv_32_arr) IS + BEGIN + FOR I IN 0 TO nof_data-1 LOOP + proc_mem_mm_bus_rd(offset+I, mm_clk, mm_mosi); + proc_mem_mm_bus_rd_latency(1, mm_clk); -- assume read latency is 1 + data_arr(I) <= mm_miso.rddata(31 DOWNTO 0); + END LOOP; + -- wait one mm_clk cycle more to have last rddata captured in signal data_arr (otherwise this proc would need to use variable data_arr) + WAIT UNTIL rising_edge(mm_clk); + END proc_mem_read_ram; + + PROCEDURE proc_mem_read_ram(SIGNAL mm_clk : IN STD_LOGIC; + SIGNAL mm_mosi : OUT t_mem_mosi; + SIGNAL mm_miso : IN t_mem_miso; + SIGNAL data_arr : OUT t_slv_32_arr) IS + CONSTANT c_offset : NATURAL := 0; + CONSTANT c_nof_data : NATURAL := data_arr'LENGTH; + BEGIN + proc_mem_read_ram(c_offset, c_nof_data, mm_clk, mm_mosi, mm_miso, data_arr); + END proc_mem_read_ram; + +END tb_common_mem_pkg;
trunk/tb_common_mem_pkg.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/tb_mm_file.vhd =================================================================== --- trunk/tb_mm_file.vhd (nonexistent) +++ trunk/tb_mm_file.vhd (revision 2) @@ -0,0 +1,237 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2012 +-- ASTRON (Netherlands Institute for Radio Astronomy) +-- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands +-- +-- This program is free software: you can redistribute it and/or modify +-- it under the terms of the GNU General Public License as published by +-- the Free Software Foundation, either version 3 of the License, or +-- (at your option) any later version. +-- +-- This program is distributed in the hope that it will be useful, +-- but WITHOUT ANY WARRANTY; without even the implied warranty of +-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +-- GNU General Public License for more details. +-- +-- You should have received a copy of the GNU General Public License +-- along with this program. If not, see . +-- +------------------------------------------------------------------------------- +-- +-- Author: +-- D. van der Schuur May 2012 Original with manual file IO using an editor. +-- E. Kooistra Feb 2017 Added purpose and description +-- Added external control by p_mm_stimuli and +-- p_sim_stimuli +-- Purpose: Testbench for MM and simulation control via file io +-- Description: +-- This testbench verifies mm_file and mm_file_pkg. +-- 1) p_mm_stimuli +-- The p_mm_stimuli uses mmf_mm_bus_wr() and mmf_mm_bus_rd() to access a MM +-- slave register instance of common_reg_r_w_dc via mm_file using a MM slave +-- .ctrl and .stat file. The p_mm_stimuli verifies the W/R accesses. +-- 2) p_sim_stimuli +-- The p_sim_stimuli waits for get_now and then it uses mmf_sim_get_now() to +-- read the simulator status via mmf_poll_sim_ctrl_file() using a sim.ctrl +-- and sim.stat file. The p_sim_stimuli does not verify read rd_now value, +-- but it does print it. +-- Usage: +-- > as 5 +-- > run -all +-- The tb is self stopping and self checking. +-- For example observe mm_mosi, mm_miso, rd_now and out_reg_arr in wave window. + +LIBRARY IEEE, common_pkg_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 common_pkg_lib.common_str_pkg.ALL; +USE common_pkg_lib.tb_common_pkg.ALL; +USE work.mm_file_pkg.ALL; + +ENTITY tb_mm_file IS + GENERIC ( + g_tb_index : NATURAL := 0; + g_mm_nof_accesses : NATURAL := 100; + g_mm_timeout : TIME := 0 ns;--100 ns; -- default 0 ns for full speed MM, use > 0 to define number of mm_clk without MM access after which the MM file IO is paused + g_mm_pause : TIME := 1000 ns; -- defines the time for which MM file IO is paused to reduce the file IO rate when the MM slave is idle + g_timeout_gap : INTEGER := -1;--4; -- no gap when < 0, else force MM access gap after g_timeout_gap wr or rd strobes + g_cross_clock_domain : BOOLEAN := FALSE --TRUE + ); +END tb_mm_file; + +ARCHITECTURE tb OF tb_mm_file IS + + CONSTANT c_mm_clk_period : TIME := c_mmf_mm_clk_period; -- = 100 ps; + CONSTANT c_mm_nof_dat : NATURAL := smallest(c_mem_reg_init_w/c_32, g_mm_nof_accesses); + CONSTANT c_mm_rd_latency : NATURAL := 2; + + CONSTANT c_cross_nof_mm_clk : NATURAL := sel_a_b(g_cross_clock_domain, 100, 0); -- > 2*24 see common_reg_cross_domain, factor 2 for W/R + + -- Determine node mm_file prefix based on --unb --gn (similar as done in mmf_unb_file_prefix()) + CONSTANT c_unb_nr : NATURAL := 3; --unb + CONSTANT c_pn_nr : NATURAL := 1; --gn = 0:7 + CONSTANT c_node_type : STRING(1 TO 2):= sel_a_b(c_pn_nr<4, "FN", "BN"); + CONSTANT c_node_nr : NATURAL := sel_a_b(c_node_type="BN", c_pn_nr-4, c_pn_nr); + + -- Use local mmfiles/ subdirectory in mm project build directory + CONSTANT c_sim_file_pathname : STRING := mmf_slave_prefix("TB", g_tb_index) & "sim"; + CONSTANT c_reg_r_w_dc_file_pathname : STRING := mmf_slave_prefix("TB", g_tb_index, "UNB", c_unb_nr, c_node_type, c_node_nr) & "REG_R_W_DC"; + + --TYPE t_c_mem IS RECORD + -- latency : NATURAL; -- read latency + -- adr_w : NATURAL; + -- dat_w : NATURAL; + -- nof_dat : NATURAL; -- optional, nof dat words <= 2**adr_w + -- init_sl : STD_LOGIC; -- optional, init all dat words to std_logic '0', '1' or 'X' + -- --init_file : STRING; -- "UNUSED", unconstrained length can not be in record + --END RECORD; + CONSTANT c_mem_reg : t_c_mem := (c_mm_rd_latency, ceil_log2(c_mm_nof_dat), c_32, c_mm_nof_dat, '0'); + + SIGNAL tb_state : STRING(1 TO 5) := "Init "; + SIGNAL tb_end : STD_LOGIC := '0'; + SIGNAL mm_clk : STD_LOGIC := '0'; + SIGNAL mm_rst : STD_LOGIC; + + SIGNAL get_now : STD_LOGIC := '0'; + SIGNAL rd_now : STRING(1 TO 16); -- sufficient to fit TIME NOW in ns as a string + + SIGNAL mm_mosi : t_mem_mosi; + SIGNAL mm_miso : t_mem_miso; + SIGNAL file_wr_data : STD_LOGIC_VECTOR(c_32-1 DOWNTO 0); + SIGNAL file_rd_data : STD_LOGIC_VECTOR(c_32-1 DOWNTO 0); + + SIGNAL reg_wr_arr : STD_LOGIC_VECTOR( c_mem_reg.nof_dat-1 DOWNTO 0); + SIGNAL reg_rd_arr : STD_LOGIC_VECTOR( c_mem_reg.nof_dat-1 DOWNTO 0); + SIGNAL in_new : STD_LOGIC := '1'; + SIGNAL in_reg : STD_LOGIC_VECTOR(c_32*c_mem_reg.nof_dat-1 DOWNTO 0); + SIGNAL out_reg : STD_LOGIC_VECTOR(c_32*c_mem_reg.nof_dat-1 DOWNTO 0); + SIGNAL out_new : STD_LOGIC; -- Pulses '1' when new data has been written. + + SIGNAL out_reg_arr : t_slv_32_arr(c_mem_reg.nof_dat-1 DOWNTO 0); + +BEGIN + + mm_clk <= NOT mm_clk OR tb_end AFTER c_mm_clk_period/2; + mm_rst <= '1', '0' AFTER c_mm_clk_period*10; + + -- DUT mm access files 'c_reg_r_w_dc_file_pathname'.ctrl and 'c_reg_r_w_dc_file_pathname'.stat + p_mm_stimuli : PROCESS + VARIABLE v_addr : NATURAL; + BEGIN + proc_common_wait_until_low(mm_clk, mm_rst); + proc_common_wait_some_cycles(mm_clk, 3); + + -- Write all nof_dat once + tb_state <= "Write"; + FOR I IN 0 TO c_mm_nof_dat-1 LOOP + IF I=g_timeout_gap THEN + WAIT FOR 2*c_mmf_mm_timeout; + END IF; + file_wr_data <= TO_UVEC(I, c_32); + mmf_mm_bus_wr(c_reg_r_w_dc_file_pathname, I, I, mm_clk); + END LOOP; + + proc_common_wait_some_cycles(mm_clk, c_cross_nof_mm_clk); + + -- Read all nof_dat once + tb_state <= "Read "; + FOR I IN 0 TO c_mm_nof_dat-1 LOOP + IF I=g_timeout_gap THEN + WAIT FOR 2*c_mmf_mm_timeout; + END IF; + mmf_mm_bus_rd(c_reg_r_w_dc_file_pathname, c_mem_reg.latency, I, file_rd_data, mm_clk); + ASSERT I=TO_UINT(file_rd_data) REPORT "Read data is wrong." SEVERITY ERROR; + END LOOP; + + -- Write/Read + tb_state <= "Both "; + FOR I IN 0 TO g_mm_nof_accesses-1 LOOP + IF I=g_timeout_gap THEN + WAIT FOR 2*c_mmf_mm_timeout; + END IF; + file_wr_data <= TO_UVEC(I, c_32); + v_addr := I MOD c_mm_nof_dat; + mmf_mm_bus_wr(c_reg_r_w_dc_file_pathname, v_addr, I, mm_clk); + proc_common_wait_some_cycles(mm_clk, c_cross_nof_mm_clk); + mmf_mm_bus_rd(c_reg_r_w_dc_file_pathname, c_mem_reg.latency, v_addr, file_rd_data, mm_clk); + ASSERT TO_UINT(file_wr_data)=TO_UINT(file_rd_data) REPORT "Write/read data is wrong." SEVERITY ERROR; + END LOOP; + + proc_common_gen_pulse(mm_clk, get_now); + tb_state <= "End "; + + proc_common_wait_some_cycles(mm_clk, g_mm_nof_accesses); + tb_end <= '1'; + WAIT; + END PROCESS; + + u_mm_file : ENTITY work.mm_file + GENERIC MAP( + g_file_prefix => c_reg_r_w_dc_file_pathname, + g_mm_rd_latency => c_mem_reg.latency, -- the mm_file g_mm_rd_latency must be >= the MM slave read latency + g_mm_timeout => g_mm_timeout, + g_mm_pause => g_mm_pause + ) + PORT MAP ( + mm_rst => mm_rst, + mm_clk => mm_clk, + + mm_master_out => mm_mosi, + mm_master_in => mm_miso + ); + + -- Target MM reg + u_reg_r_w_dc : ENTITY work.common_reg_r_w_dc + GENERIC MAP ( + g_cross_clock_domain => g_cross_clock_domain, + g_in_new_latency => 0, + g_readback => FALSE, + g_reg => c_mem_reg + --g_init_reg => STD_LOGIC_VECTOR(c_mem_reg_init_w-1 DOWNTO 0) := (OTHERS => '0') + ) + PORT MAP ( + -- Clocks and reset + mm_rst => mm_rst, + mm_clk => mm_clk, + st_rst => mm_rst, + st_clk => mm_clk, + + -- Memory Mapped Slave in mm_clk domain + sla_in => mm_mosi, + sla_out => mm_miso, + + -- MM registers in st_clk domain + reg_wr_arr => reg_wr_arr, + reg_rd_arr => reg_rd_arr, + in_new => in_new, + in_reg => in_reg, + out_reg => out_reg, + out_new => out_new + ); + + in_reg <= out_reg; + + p_wire : PROCESS(out_reg) + BEGIN + FOR I IN c_mem_reg.nof_dat-1 DOWNTO 0 LOOP + out_reg_arr(I) <= out_reg((I+1)*c_32-1 DOWNTO I*c_32); + END LOOP; + END PROCESS; + + -- Also verify simulation status access + mmf_poll_sim_ctrl_file(mm_clk, c_sim_file_pathname & ".ctrl", c_sim_file_pathname & ".stat"); + + p_sim_stimuli : PROCESS + BEGIN + proc_common_wait_until_low(mm_clk, mm_rst); + proc_common_wait_some_cycles(mm_clk, 10); + + proc_common_wait_until_hi_lo(mm_clk, get_now); + mmf_sim_get_now(c_sim_file_pathname, rd_now, mm_clk); + WAIT; + END PROCESS; + +END tb;
trunk/tb_mm_file.vhd Property changes : Added: svn:executable ## -0,0 +1 ## +* \ No newline at end of property Index: trunk/tb_tb_mm_file.vhd =================================================================== --- trunk/tb_tb_mm_file.vhd (nonexistent) +++ trunk/tb_tb_mm_file.vhd (revision 2) @@ -0,0 +1,54 @@ +------------------------------------------------------------------------------- +-- +-- Copyright (C) 2017 +-- 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 . +-- +------------------------------------------------------------------------------- + +-- Author: +-- E. Kooistra Feb 2017 Initial. +-- Purpose: Multi testbench of tb_mm_file to verify mm_file and mm_file_pkg. +-- Usage: +-- > as 4 +-- > run -all + +LIBRARY IEEE; +USE IEEE.std_logic_1164.ALL; + +ENTITY tb_tb_mm_file IS +END tb_tb_mm_file; + +ARCHITECTURE tb OF tb_tb_mm_file IS + SIGNAL tb_end : STD_LOGIC := '0'; -- declare tb_end to avoid 'No objects found' error on 'when -label tb_end' +BEGIN + -- g_tb_index : NATURAL := 0; + -- g_mm_nof_accesses : NATURAL := 100; + -- g_mm_timeout : TIME := sel_a_b(g_mm_throttle_en, 1 ns, 0 ns); -- default 0 for full speed MM, use > 0 to define number of mm_clk without MM access after which the MM file IO is paused + -- g_mm_pause : TIME := 1 us; -- defines the time for which MM file IO is paused to reduce the file IO rate when the MM slave is idle + -- g_timeout_gap : INTEGER := -1; -- no gap when < 0, else force MM access gap after g_timeout_gap wr or rd strobes + -- g_cross_clock_domain : BOOLEAN := FALSE --TRUE + + u_one_clk : ENTITY work.tb_mm_file GENERIC MAP (0, 10000, 0 ns, 1 us, -1, FALSE); + u_one_clk_mm_throttle : ENTITY work.tb_mm_file GENERIC MAP (1, 10000, 100 ns, 1 us, -1, FALSE); + u_cross_clk : ENTITY work.tb_mm_file GENERIC MAP (2, 1000, 0 ns, 1 us, -1, TRUE); + u_cross_clk_mm_throttle : ENTITY work.tb_mm_file GENERIC MAP (3, 1000, 100 ns, 1 us, -1, TRUE); + u_with_gap_one_clk : ENTITY work.tb_mm_file GENERIC MAP (4, 10000, 0 ns, 1 us, 3, FALSE); + u_with_gap_one_clk_mm_throttle : ENTITY work.tb_mm_file GENERIC MAP (5, 10000, 100 ns, 1 us, 3, FALSE); + u_with_gap_cross_clk : ENTITY work.tb_mm_file GENERIC MAP (6, 1000, 0 ns, 1 us, 3, TRUE); + u_with_gap_cross_clk_mm_throttle : ENTITY work.tb_mm_file GENERIC MAP (7, 1000, 100 ns, 1 us, 3, TRUE); + +END tb;
trunk/tb_tb_mm_file.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.