Newer
Older

Eric Kooistra
committed
-------------------------------------------------------------------------------
--
-- Copyright (C) 2010
-- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
-- JIVE (Joint Institute for VLBI in Europe) <http://www.jive.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, technology_lib, common_lib, dp_lib;

Eric Kooistra
committed
USE IEEE.std_logic_1164.ALL;
USE IEEE.numeric_std.ALL;
USE common_lib.common_pkg.ALL;
USE common_lib.common_mem_pkg.ALL;
USE common_lib.tb_common_mem_pkg.ALL;
USE common_lib.common_network_layers_pkg.ALL;
USE common_lib.common_network_total_header_pkg.ALL;
USE dp_lib.dp_stream_pkg.ALL;
USE dp_lib.tb_dp_pkg.ALL;
USE technology_lib.technology_pkg.ALL;

Eric Kooistra
committed

Eric Kooistra
committed
-- Test bench supported packet data types

Eric Kooistra
committed
CONSTANT c_tb_tech_tse_data_type_symbols : NATURAL := 0;
CONSTANT c_tb_tech_tse_data_type_counter : NATURAL := 1;
CONSTANT c_tb_tech_tse_data_type_arp : NATURAL := 2;
CONSTANT c_tb_tech_tse_data_type_ping : NATURAL := 3; -- over IP/ICMP
CONSTANT c_tb_tech_tse_data_type_udp : NATURAL := 4; -- over IP

Eric Kooistra
committed

Eric Kooistra
committed
FUNCTION func_tech_tse_header_size(data_type : NATURAL) RETURN NATURAL; -- raw ethernet: 4 header words, protocol ethernet: 11 header words

Eric Kooistra
committed
-- Configure the TSE MAC
PROCEDURE proc_tech_tse_setup(CONSTANT c_technology : IN NATURAL;
CONSTANT c_promis_en : IN BOOLEAN;

Eric Kooistra
committed
CONSTANT c_tse_tx_fifo_depth : IN NATURAL;
CONSTANT c_tse_rx_fifo_depth : IN NATURAL;
CONSTANT c_tx_ready_latency : IN NATURAL;
CONSTANT src_mac : IN STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE);
SIGNAL psc_access : OUT STD_LOGIC;
SIGNAL mm_clk : IN STD_LOGIC;
SIGNAL mm_miso : IN t_mem_miso;
SIGNAL mm_mosi : OUT t_mem_mosi);

Eric Kooistra
committed
PROCEDURE proc_tech_tse_setup_stratixiv(CONSTANT c_promis_en : IN BOOLEAN;
CONSTANT c_tse_tx_fifo_depth : IN NATURAL;
CONSTANT c_tse_rx_fifo_depth : IN NATURAL;
CONSTANT c_tx_ready_latency : IN NATURAL;
CONSTANT src_mac : IN STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE);
SIGNAL psc_access : OUT STD_LOGIC;
SIGNAL mm_clk : IN STD_LOGIC;
SIGNAL mm_miso : IN t_mem_miso;
SIGNAL mm_mosi : OUT t_mem_mosi);

Eric Kooistra
committed
PROCEDURE proc_tech_tse_tx_packet(CONSTANT total_header : IN t_network_total_header;
CONSTANT data_len : IN NATURAL; -- in symbols = octets = bytes
CONSTANT c_data_type : IN NATURAL; -- c_tb_tech_tse_data_type_*
CONSTANT c_ready_latency : IN NATURAL; -- 0, 1 are supported by proc_dp_stream_ready_latency()
CONSTANT c_nof_not_valid : IN NATURAL; -- when > 0 then pull tx valid low for c_nof_not_valid beats during tx
SIGNAL ff_clk : IN STD_LOGIC;
SIGNAL ff_en : IN STD_LOGIC; -- similar purpose as c_nof_not_valid, but not used so pass on signal '1'
SIGNAL ff_src_in : IN t_dp_siso;
SIGNAL ff_src_out : OUT t_dp_sosi);

Eric Kooistra
committed
-- Receive and verify packet from the TSE MAC

Eric Kooistra
committed
PROCEDURE proc_tech_tse_rx_packet(CONSTANT total_header : IN t_network_total_header;
CONSTANT c_data_type : IN NATURAL; -- c_tb_tech_tse_data_type_*
SIGNAL ff_clk : IN STD_LOGIC;
SIGNAL ff_snk_in : IN t_dp_sosi;
SIGNAL ff_snk_out : OUT t_dp_siso);

Eric Kooistra
committed

Eric Kooistra
committed

Eric Kooistra
committed

Eric Kooistra
committed
------------------------------------------------------------------------------
-- LOCAL ITEMS
------------------------------------------------------------------------------
CONSTANT c_nof_eth_beats : NATURAL := c_network_total_header_32b_eth_nof_words; -- nof words in eth part of the header
CONSTANT c_nof_hdr_beats : NATURAL := c_network_total_header_32b_nof_words; -- nof words in the total header

Eric Kooistra
committed

Eric Kooistra
committed
-- Use default word addressing for MAC registers according to table 4.8, 4.9
-- Use halfword addressing for PCS register to match table 4.17
FUNCTION func_map_pcs_addr(pcs_addr : NATURAL) RETURN NATURAL IS
BEGIN
RETURN pcs_addr * 2 + c_tech_tse_byte_addr_pcs_offset;
END func_map_pcs_addr;

Eric Kooistra
committed

Eric Kooistra
committed
------------------------------------------------------------------------------
-- GLOBAL ITEMS
------------------------------------------------------------------------------

Eric Kooistra
committed

Eric Kooistra
committed
FUNCTION func_tech_tse_header_size(data_type : NATURAL) RETURN NATURAL IS

Eric Kooistra
committed
BEGIN
CASE data_type IS

Eric Kooistra
committed
WHEN c_tb_tech_tse_data_type_symbols => RETURN c_network_total_header_32b_eth_nof_words;
WHEN c_tb_tech_tse_data_type_counter => RETURN c_network_total_header_32b_eth_nof_words;

Eric Kooistra
committed
WHEN OTHERS => NULL;
END CASE;
RETURN c_network_total_header_32b_nof_words;

Eric Kooistra
committed
END func_tech_tse_header_size;

Eric Kooistra
committed
-- Configure the TSE MAC
PROCEDURE proc_tech_tse_setup(CONSTANT c_technology : IN NATURAL;
CONSTANT c_promis_en : IN BOOLEAN;

Eric Kooistra
committed
CONSTANT c_tse_tx_fifo_depth : IN NATURAL;
CONSTANT c_tse_rx_fifo_depth : IN NATURAL;
CONSTANT c_tx_ready_latency : IN NATURAL;
CONSTANT src_mac : IN STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE);
SIGNAL psc_access : OUT STD_LOGIC;
SIGNAL mm_clk : IN STD_LOGIC;
SIGNAL mm_miso : IN t_mem_miso;
SIGNAL mm_mosi : OUT t_mem_mosi) IS
BEGIN
CASE c_technology IS
WHEN c_tech_stratixiv => proc_tech_tse_setup_stratixiv(c_promis_en, c_tse_tx_fifo_depth, c_tse_rx_fifo_depth, c_tx_ready_latency, src_mac, psc_access, mm_clk, mm_miso, mm_mosi);
WHEN OTHERS => proc_tech_tse_setup_stratixiv(c_promis_en, c_tse_tx_fifo_depth, c_tse_rx_fifo_depth, c_tx_ready_latency, src_mac, psc_access, mm_clk, mm_miso, mm_mosi); -- default to c_tech_stratixiv
END CASE;
END proc_tech_tse_setup;
-- . The src_mac[47:0] = 0x123456789ABC for MAC address 12-34-56-78-9A-BC
PROCEDURE proc_tech_tse_setup_stratixiv(CONSTANT c_promis_en : IN BOOLEAN;
CONSTANT c_tse_tx_fifo_depth : IN NATURAL;
CONSTANT c_tse_rx_fifo_depth : IN NATURAL;
CONSTANT c_tx_ready_latency : IN NATURAL;
CONSTANT src_mac : IN STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE);
SIGNAL psc_access : OUT STD_LOGIC;
SIGNAL mm_clk : IN STD_LOGIC;
SIGNAL mm_miso : IN t_mem_miso;
SIGNAL mm_mosi : OUT t_mem_mosi) IS

Eric Kooistra
committed
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
CONSTANT c_mac0 : INTEGER := TO_SINT(hton(src_mac(47 DOWNTO 16), 4));
CONSTANT c_mac1 : INTEGER := TO_SINT(hton(src_mac(15 DOWNTO 0), 2));
BEGIN
-- PSC control
psc_access <= '1';
proc_mem_mm_bus_rd(func_map_pcs_addr(16#22#), mm_clk, mm_miso, mm_mosi); -- REV --> 0x0901
proc_mem_mm_bus_wr(func_map_pcs_addr(16#28#), 16#0008#, mm_clk, mm_miso, mm_mosi); -- IF_MODE <-- Force 1GbE, no autonegatiation
proc_mem_mm_bus_rd(func_map_pcs_addr(16#00#), mm_clk, mm_miso, mm_mosi); -- CONTROL --> 0x1140
proc_mem_mm_bus_rd(func_map_pcs_addr(16#02#), mm_clk, mm_miso, mm_mosi); -- STATUS --> 0x000D
proc_mem_mm_bus_wr(func_map_pcs_addr(16#00#), 16#0140#, mm_clk, mm_miso, mm_mosi); -- CONTROL <-- Auto negotiate disable
psc_access <= '0';
-- MAC control
proc_mem_mm_bus_rd(16#000#, mm_clk, mm_miso, mm_mosi); -- REV --> CUST_VERSION & 0x0901
IF c_promis_en=FALSE THEN
proc_mem_mm_bus_wr(16#008#, 16#0100004B#, mm_clk, mm_miso, mm_mosi);
ELSE
proc_mem_mm_bus_wr(16#008#, 16#0100005B#, mm_clk, mm_miso, mm_mosi);
END IF;
-- COMMAND_CONFIG <--
-- Only the bits relevant to UniBoard are explained here, others are 0
-- [ 0] = TX_ENA = 1, enable tx datapath
-- [ 1] = RX_ENA = 1, enable rx datapath
-- [ 2] = XON_GEN = 0
-- [ 3] = ETH_SPEED = 1, enable 1GbE operation
-- [ 4] = PROMIS_EN = 0, when 1 then receive all frames
-- [ 5] = PAD_EN = 0, when 1 enable receive padding removal (requires ethertype=payload length)
-- [ 6] = CRC_FWD = 1, enable receive CRC forward
-- [ 7] = PAUSE_FWD = 0
-- [ 8] = PAUSE_IGNORE = 0
-- [ 9] = TX_ADDR_INS = 0, when 1 then MAX overwrites tx SRC MAC with mac_0,1 or one of the supplemental mac
-- [ 10] = HD_ENA = 0
-- [ 11] = EXCESS_COL = 0
-- [ 12] = LATE_COL = 0
-- [ 13] = SW_RESET = 0, when 1 MAC disables tx and rx, clear statistics and flushes receive FIFO
-- [ 14] = MHAS_SEL = 0, select multicast address resolutions hash-code mode
-- [ 15] = LOOP_ENA = 0
-- [18-16] = TX_ADDR_SEL[2:0] = 000, TX_ADDR_INS insert mac_0,1 or one of the supplemental mac
-- [ 19] = MAGIC_EN = 0
-- [ 20] = SLEEP = 0
-- [ 21] = WAKEUP = 0
-- [ 22] = XOFF_GEN = 0
-- [ 23] = CNT_FRM_ENA = 0
-- [ 24] = NO_LGTH_CHECK = 1, when 0 then check payload length of received frames (requires ethertype=payload length)
-- [ 25] = ENA_10 = 0
-- [ 26] = RX_ERR_DISC = 0, when 1 then discard erroneous frames (requires store and forward mode, so rx_section_full=0)
-- when 0 then pass on with rx_err[0]=1
-- [ 27] = DISABLE_RD_TIMEOUT = 0
-- [30-28] = RSVD = 000
-- [ 31] = CNT_RESET = 0, when 1 clear statistics
proc_mem_mm_bus_wr(16#00C#, c_mac0, mm_clk, mm_miso, mm_mosi); -- MAC_0
proc_mem_mm_bus_wr(16#010#, c_mac1, mm_clk, mm_miso, mm_mosi); -- MAC_1 <-- SRC_MAC = 12-34-56-78-9A-BC
proc_mem_mm_bus_wr(16#05C#, 16#0000000C#, mm_clk, mm_miso, mm_mosi); -- TX_IPG_LENGTH <-- interpacket gap = 12
--proc_mem_mm_bus_wr(16#014#, 16#000005EE#, mm_clk, mm_miso, mm_mosi); -- FRM_LENGTH <-- receive max frame length = 1518
proc_mem_mm_bus_wr(16#014#, 16#0000233A#, mm_clk, mm_miso, mm_mosi); -- FRM_LENGTH <-- receive max frame length = 9018
-- FIFO legenda:
-- . Tx section full = There is enough data in the FIFO to start reading it, when 0 then store and forward.
-- . Rx section full = There is enough data in the FIFO to start reading it, when 0 then store and forward.
-- . Tx section empty = There is not much empty space anymore in the FIFO, warn user via ff_tx_septy
-- . Rx section empty = There is not much empty space anymore in the FIFO, inform remote device via XOFF flow control
-- . Tx almost full = Assert ff_tx_a_full and deassert ff_tx_rdy. Furthermore TX_ALMOST_FULL = c_tx_ready_latency+3,
-- so choose 3 for zero tx ready latency
-- . Rx almost full = Assert ff_rx_a_full and if the user is not ready ff_rx_rdy then:
-- --> break off the reception with an error to avoid FIFO overflow
-- . Tx almost empty = Assert ff_tx_a_empty and if the FIFO does not contain a eop yet then:
-- --> break off the transmission with an error to avoid FIFO underflow
-- . Rx almost empty = Assert ff_rx_a_empty
-- Typical FIFO values:
-- . TX_SECTION_FULL = 16 > 8 = TX_ALMOST_EMPTY
-- . RX_SECTION_FULL = 16 > 8 = RX_ALMOST_EMPTY
-- . TX_SECTION_EMPTY = D-16 < D-3 = Tx FIFO depth - TX_ALMOST_FULL
-- . RX_SECTION_EMPTY = D-16 < D-8 = Rx FIFO depth - RX_ALMOST_FULL
-- . c_tse_tx_fifo_depth = 1 M9K = 256*32b = 1k * 8b is sufficient when the Tx user respects ff_tx_rdy, to store a complete
-- ETH packet would require 1518 byte, so 2 M9K = 2k * 8b
-- . c_tse_rx_fifo_depth = 1 M9K = 256*32b = 1k * 8b is sufficient when the Rx user ff_rx_rdy is sufficiently active
proc_mem_mm_bus_wr(16#01C#, c_tse_rx_fifo_depth-16, mm_clk, mm_miso, mm_mosi); -- RX_SECTION_EMPTY <-- default FIFO depth - 16, >3
proc_mem_mm_bus_wr(16#020#, 16, mm_clk, mm_miso, mm_mosi); -- RX_SECTION_FULL <-- default 16
proc_mem_mm_bus_wr(16#024#, c_tse_tx_fifo_depth-16, mm_clk, mm_miso, mm_mosi); -- TX_SECTION_EMPTY <-- default FIFO depth - 16, >3
proc_mem_mm_bus_wr(16#028#, 16, mm_clk, mm_miso, mm_mosi); -- TX_SECTION_FULL <-- default 16, >~ 8 otherwise no tx
proc_mem_mm_bus_wr(16#02C#, 8, mm_clk, mm_miso, mm_mosi); -- RX_ALMOST_EMPTY <-- default 8
proc_mem_mm_bus_wr(16#030#, 8, mm_clk, mm_miso, mm_mosi); -- RX_ALMOST_FULL <-- default 8
proc_mem_mm_bus_wr(16#034#, 8, mm_clk, mm_miso, mm_mosi); -- TX_ALMOST_EMPTY <-- default 8
proc_mem_mm_bus_wr(16#038#, c_tx_ready_latency+3, mm_clk, mm_miso, mm_mosi); -- TX_ALMOST_FULL <-- default 3
proc_mem_mm_bus_rd(16#0E8#, mm_clk, mm_miso, mm_mosi); -- TX_CMD_STAT --> 0x00040000 : [18]=1 TX_SHIFT16, [17]=0 OMIT_CRC
proc_mem_mm_bus_rd(16#0EC#, mm_clk, mm_miso, mm_mosi); -- RX_CMD_STAT --> 0x02000000 : [25]=1 RX_SHIFT16
WAIT UNTIL rising_edge(mm_clk);
END proc_tech_tse_setup_stratixiv;

Eric Kooistra
committed
-- Transmit user packet
-- . Use word aligned payload data, so with half word inserted before the 14 byte header
-- . Packets can be send immediately after eachother so new sop directly after last eop
-- . The word rate is controlled by respecting ready from the MAC

Eric Kooistra
committed
PROCEDURE proc_tech_tse_tx_packet(CONSTANT total_header : IN t_network_total_header;
CONSTANT data_len : IN NATURAL; -- in symbols = octets = bytes
CONSTANT c_data_type : IN NATURAL; -- c_tb_tech_tse_data_type_*
CONSTANT c_ready_latency : IN NATURAL; -- 0, 1 are supported by proc_dp_stream_ready_latency()
CONSTANT c_nof_not_valid : IN NATURAL; -- when > 0 then pull tx valid low for c_nof_not_valid beats during tx
SIGNAL ff_clk : IN STD_LOGIC;
SIGNAL ff_en : IN STD_LOGIC; -- similar purpose as c_nof_not_valid, but not used so pass on signal '1'
SIGNAL ff_src_in : IN t_dp_siso;
SIGNAL ff_src_out : OUT t_dp_sosi) IS
CONSTANT c_eth_header : t_network_eth_header := total_header.eth;
CONSTANT c_arp_words_arr : t_network_total_header_32b_arr := func_network_total_header_construct_arp( total_header.eth, total_header.arp);
CONSTANT c_icmp_words_arr : t_network_total_header_32b_arr := func_network_total_header_construct_icmp(total_header.eth, total_header.ip, total_header.icmp);
CONSTANT c_udp_words_arr : t_network_total_header_32b_arr := func_network_total_header_construct_udp( total_header.eth, total_header.ip, total_header.udp);

Eric Kooistra
committed

Eric Kooistra
committed
CONSTANT c_mod : NATURAL := data_len MOD c_tech_tse_symbols_per_beat;
CONSTANT c_nof_data_beats : NATURAL := data_len / c_tech_tse_symbols_per_beat + sel_a_b(c_mod, 1, 0);
CONSTANT c_empty : NATURAL := sel_a_b(c_mod, c_tech_tse_symbols_per_beat - c_mod, 0);
VARIABLE v_sym : UNSIGNED(c_tech_tse_symbol_w-1 DOWNTO 0) := (OTHERS=>'0');
VARIABLE v_num : UNSIGNED(c_tech_tse_data_w-1 DOWNTO 0) := (OTHERS=>'0');

Eric Kooistra
committed
BEGIN
ff_src_out.empty <= TO_DP_EMPTY(0);
----------------------------------------------------------------------------
-- ETH Header
-- . sop
ff_src_out.data <= RESIZE_DP_DATA(c_udp_words_arr(0)); -- all arp, icmp and udp contain the same eth header, so it is ok to use c_udp_words_arr

Eric Kooistra
committed
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '1', '0', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);
ff_src_out.data <= RESIZE_DP_DATA(c_udp_words_arr(1)); -- prepare data before loop, so proc_dp_stream_ready_latency can be called at start of the loops

Eric Kooistra
committed
FOR I IN 2 TO c_nof_eth_beats-1 LOOP
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '0', '0', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);
ff_src_out.data <= RESIZE_DP_DATA(c_udp_words_arr(I));

Eric Kooistra
committed
END LOOP;
----------------------------------------------------------------------------
-- ETH higher layer headers

Eric Kooistra
committed
IF c_data_type=c_tb_tech_tse_data_type_arp THEN

Eric Kooistra
committed
FOR I IN c_nof_eth_beats TO c_nof_hdr_beats-2 LOOP
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '0', '0', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);
ff_src_out.data <= RESIZE_DP_DATA(c_arp_words_arr(I));

Eric Kooistra
committed
END LOOP;
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '0', '0', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);
-- . eop
ff_src_out.data <= RESIZE_DP_DATA(c_arp_words_arr(c_nof_hdr_beats-1));

Eric Kooistra
committed
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '0', '1', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);

Eric Kooistra
committed
ELSIF c_data_type=c_tb_tech_tse_data_type_ping OR c_data_type=c_tb_tech_tse_data_type_udp THEN

Eric Kooistra
committed
FOR I IN c_nof_eth_beats TO c_nof_hdr_beats-1 LOOP
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '0', '0', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);
CASE c_data_type IS

Eric Kooistra
committed
WHEN c_tb_tech_tse_data_type_ping => ff_src_out.data <= RESIZE_DP_DATA(c_icmp_words_arr(I));
WHEN c_tb_tech_tse_data_type_udp => ff_src_out.data <= RESIZE_DP_DATA(c_udp_words_arr(I));

Eric Kooistra
committed
WHEN OTHERS => NULL;
END CASE;
END LOOP;
END IF;
----------------------------------------------------------------------------
-- Data

Eric Kooistra
committed
IF c_data_type/=c_tb_tech_tse_data_type_arp THEN

Eric Kooistra
committed
FOR I IN 0 TO c_nof_data_beats-1 LOOP
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '0', '0', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);
CASE c_data_type IS

Eric Kooistra
committed
WHEN c_tb_tech_tse_data_type_counter =>

Eric Kooistra
committed
-- data : X"00000001", X"00000002", X"00000003", etc
v_num := v_num + 1;
ff_src_out.data <= RESIZE_DP_DATA(STD_LOGIC_VECTOR(v_num));
WHEN OTHERS =>
-- data : X"01020304", X"05060708", X"090A0B0C", etc

Eric Kooistra
committed
FOR J IN c_tech_tse_symbols_per_beat-1 DOWNTO 0 LOOP

Eric Kooistra
committed
v_sym := v_sym + 1;

Eric Kooistra
committed
ff_src_out.data((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w) <= STD_LOGIC_VECTOR(v_sym);

Eric Kooistra
committed
END LOOP;
END CASE;
-- tb : pull valid low for some time during the middle of the payload
IF c_nof_not_valid > 0 AND I=c_nof_data_beats/2 THEN
ff_src_out.valid <= '0';
FOR I IN 0 TO c_nof_not_valid LOOP WAIT UNTIL rising_edge(ff_clk); END LOOP;
ff_src_out.valid <= '1';
END IF;
END LOOP;
--------------------------------------------------------------------------
-- Last data
IF c_empty > 0 THEN
-- Overwrite empty data
ff_src_out.empty <= TO_DP_EMPTY(c_empty);
FOR J IN c_empty-1 DOWNTO 0 LOOP

Eric Kooistra
committed
ff_src_out.data((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w) <= (OTHERS=>'0');

Eric Kooistra
committed
END LOOP;
END IF;
-- . eop
proc_dp_stream_ready_latency(c_ready_latency, ff_clk, ff_src_in.ready, ff_en, '0', '1', '0', '1', ff_src_out.sync, ff_src_out.valid, ff_src_out.sop, ff_src_out.eop);
END IF;
----------------------------------------------------------------------------
-- Initialize for next tx packet
ff_src_out.data <= TO_DP_DATA(0);
ff_src_out.valid <= '0';
ff_src_out.eop <= '0';
ff_src_out.empty <= TO_DP_EMPTY(0);

Eric Kooistra
committed
END proc_tech_tse_tx_packet;

Eric Kooistra
committed
-- Receive packet
-- . Use word aligned payload data, so with half word inserted before the 14 byte header
-- . Packets can be always be received, assume the user application is always ready
-- . The CRC32 is also passed on to the user at eop.
-- . Note that when empty/=0 then the CRC32 is not word aligned, so therefore use prev_data to be able
-- to handle part of last data word in case empty/=0 at eop

Eric Kooistra
committed
PROCEDURE proc_tech_tse_rx_packet(CONSTANT total_header : IN t_network_total_header;
CONSTANT c_data_type : IN NATURAL; -- c_tb_tech_tse_data_type_*
SIGNAL ff_clk : IN STD_LOGIC;
SIGNAL ff_snk_in : IN t_dp_sosi;
SIGNAL ff_snk_out : OUT t_dp_siso) IS
CONSTANT c_eth_header : t_network_eth_header := total_header.eth;
CONSTANT c_arp_words_arr : t_network_total_header_32b_arr := func_network_total_header_construct_arp( total_header.eth, total_header.arp);
CONSTANT c_icmp_words_arr : t_network_total_header_32b_arr := func_network_total_header_construct_icmp(total_header.eth, total_header.ip, total_header.icmp);
CONSTANT c_udp_words_arr : t_network_total_header_32b_arr := func_network_total_header_construct_udp( total_header.eth, total_header.ip, total_header.udp);

Eric Kooistra
committed
VARIABLE v_sym : UNSIGNED(c_tech_tse_symbol_w-1 DOWNTO 0) := (OTHERS=>'0');
VARIABLE v_num : UNSIGNED(c_tech_tse_data_w-1 DOWNTO 0) := (OTHERS=>'0');

Eric Kooistra
committed
VARIABLE v_empty : NATURAL;
VARIABLE v_first : BOOLEAN := TRUE;

Eric Kooistra
committed
VARIABLE v_data : STD_LOGIC_VECTOR(c_tech_tse_data_w-1 DOWNTO 0);
VARIABLE v_prev_data : STD_LOGIC_VECTOR(c_tech_tse_data_w-1 DOWNTO 0);

Eric Kooistra
committed
BEGIN
-- Keep ff_rx_snk_out.ready='1' and ff_rx_snk_out.xon='1' all the time
ff_snk_out <= c_dp_siso_rdy;
----------------------------------------------------------------------------
-- Verify ETH Header
-- . wait for sop
proc_dp_stream_valid_sop(ff_clk, ff_snk_in.valid, ff_snk_in.sop);
ASSERT ff_snk_in.data(31 DOWNTO 16) = X"0000" REPORT "RX: Wrong ETH alignment half word not zero" SEVERITY ERROR;
ASSERT ff_snk_in.data(15 DOWNTO 0) = c_eth_header.dst_mac(47 DOWNTO 32) REPORT "RX: Wrong ETH dst_mac_addr(47 DOWNTO 32)" SEVERITY ERROR;
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
ASSERT ff_snk_in.data(31 DOWNTO 0) = c_eth_header.dst_mac(31 DOWNTO 0) REPORT "RX: Wrong ETH dst_mac_addr(31 DOWNTO 0)" SEVERITY ERROR;
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
ASSERT ff_snk_in.data(31 DOWNTO 0) = c_eth_header.src_mac(47 DOWNTO 16) REPORT "RX: Wrong ETH src_mac_addr(47 DOWNTO 16)" SEVERITY ERROR;
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
ASSERT ff_snk_in.data(31 DOWNTO 16) = c_eth_header.src_mac(15 DOWNTO 0) REPORT "RX: Wrong ETH src_mac_addr(15 DOWNTO 0)" SEVERITY ERROR;
ASSERT ff_snk_in.data(15 DOWNTO 0) = c_eth_header.eth_type REPORT "RX: Wrong ETH ethertype" SEVERITY ERROR;
----------------------------------------------------------------------------
-- Verify ETH higher layer headers

Eric Kooistra
committed
IF c_data_type=c_tb_tech_tse_data_type_arp THEN

Eric Kooistra
committed
FOR I IN c_nof_eth_beats TO c_nof_hdr_beats-1 LOOP
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
ASSERT ff_snk_in.data(31 DOWNTO 0) = c_arp_words_arr(I) REPORT "RX: Wrong ARP response word" SEVERITY ERROR;

Eric Kooistra
committed
END LOOP;
-- . continue to eop
WHILE ff_snk_in.eop /= '1' LOOP
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
END LOOP;

Eric Kooistra
committed
ELSIF c_data_type=c_tb_tech_tse_data_type_ping OR c_data_type=c_tb_tech_tse_data_type_udp THEN

Eric Kooistra
committed
FOR I IN c_nof_eth_beats TO c_nof_hdr_beats-1 LOOP
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
IF I/=c_network_total_header_32b_ip_header_checksum_wi THEN -- do not verify tx ip header checksum

Eric Kooistra
committed
CASE c_data_type IS

Eric Kooistra
committed
WHEN c_tb_tech_tse_data_type_ping => ASSERT ff_snk_in.data(31 DOWNTO 0) = c_icmp_words_arr(I) REPORT "RX: Wrong IP/ICMP = PING response word" SEVERITY ERROR;
WHEN c_tb_tech_tse_data_type_udp => ASSERT ff_snk_in.data(31 DOWNTO 0) = c_udp_words_arr(I) REPORT "RX: Wrong IP/UDP response word" SEVERITY ERROR;

Eric Kooistra
committed
WHEN OTHERS => NULL;
END CASE;
END IF;
END LOOP;
END IF;
----------------------------------------------------------------------------
-- Verify DATA

Eric Kooistra
committed
IF c_data_type/=c_tb_tech_tse_data_type_arp THEN

Eric Kooistra
committed
-- . continue to eop
v_first := TRUE;
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
WHILE ff_snk_in.eop /= '1' LOOP
v_prev_data := v_data;

Eric Kooistra
committed
v_data := ff_snk_in.data(c_tech_tse_data_w-1 DOWNTO 0);

Eric Kooistra
committed
IF v_first = FALSE THEN
CASE c_data_type IS

Eric Kooistra
committed
WHEN c_tb_tech_tse_data_type_counter =>

Eric Kooistra
committed
-- data : X"00000001", X"00000002", X"00000003", etc
v_num := v_num + 1;
IF UNSIGNED(v_prev_data)/=0 THEN -- do not verify zero padding
ASSERT UNSIGNED(v_prev_data) = v_num REPORT "RX: Wrong data word" SEVERITY ERROR;
END IF;
WHEN OTHERS =>
-- data : X"01020304", X"05060708", X"090A0B0C", etc

Eric Kooistra
committed
FOR J IN c_tech_tse_symbols_per_beat-1 DOWNTO 0 LOOP

Eric Kooistra
committed
v_sym := v_sym + 1;

Eric Kooistra
committed
IF UNSIGNED(v_prev_data((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w))/=0 THEN -- do not verify zero padding
ASSERT UNSIGNED(v_prev_data((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w)) = v_sym REPORT "RX: Wrong data symbol" SEVERITY ERROR;

Eric Kooistra
committed
END IF;
END LOOP;
END CASE;
END IF;
v_first := FALSE;
proc_dp_stream_valid(ff_clk, ff_snk_in.valid);
END LOOP;
--------------------------------------------------------------------------
-- Verify last DATA and CRC32 if empty/=0 else the last word is only the CRC32
v_prev_data := v_data;

Eric Kooistra
committed
v_data := ff_snk_in.data(c_tech_tse_data_w-1 DOWNTO 0);
v_empty := TO_INTEGER(UNSIGNED(ff_snk_in.empty(c_tech_tse_empty_w-1 DOWNTO 0)));

Eric Kooistra
committed
IF v_empty > 0 THEN
FOR J IN v_empty-1 DOWNTO 0 LOOP

Eric Kooistra
committed
v_prev_data((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w) := (OTHERS=>'0');

Eric Kooistra
committed
END LOOP;
CASE c_data_type IS

Eric Kooistra
committed
WHEN c_tb_tech_tse_data_type_counter =>

Eric Kooistra
committed
-- data : X"00000001", X"00000002", X"00000003", etc
v_num := v_num + 1;
FOR J IN v_empty-1 DOWNTO 0 LOOP

Eric Kooistra
committed
v_num((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w) := (OTHERS=>'0'); -- force CRC32 symbols in last data word to 0

Eric Kooistra
committed
END LOOP;
IF UNSIGNED(v_prev_data)/=0 THEN -- do not verify zero padding
ASSERT UNSIGNED(v_prev_data) = v_num REPORT "RX: Wrong empty data word" SEVERITY ERROR;
END IF;
WHEN OTHERS =>
-- data : X"01020304", X"05060708", X"090A0B0C", etc

Eric Kooistra
committed
FOR J IN c_tech_tse_symbols_per_beat-1 DOWNTO v_empty LOOP -- ignore CRC32 symbols in last data word

Eric Kooistra
committed
v_sym := v_sym + 1;

Eric Kooistra
committed
IF UNSIGNED(v_prev_data((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w))/=0 THEN -- do not verify zero padding
ASSERT UNSIGNED(v_prev_data((J+1)*c_tech_tse_symbol_w-1 DOWNTO J*c_tech_tse_symbol_w)) = v_sym REPORT "RX: Wrong empty data symbol" SEVERITY ERROR;

Eric Kooistra
committed
END IF;
END LOOP;
END CASE;
END IF;
END IF;
-- No verify on CRC32 word

Eric Kooistra
committed
END proc_tech_tse_rx_packet;

Eric Kooistra
committed