Skip to content
Snippets Groups Projects
Select Git revision
  • c65245de1c4f09e479b700e8f22e2c34bb4b9ead
  • master default protected
  • RTSD-375
  • L2SDP-1134
  • L2SDP-1137
  • L2SDP-LIFT
  • L2SDP-1113
  • HPR-158
8 results

tb_tech_mac_10g.vhd

Blame
  • Code owners
    Assign users and groups as approvers for specific file changes. Learn more.
    tb_tech_mac_10g.vhd 12.50 KiB
    -------------------------------------------------------------------------------
    --
    -- Copyright (C) 2014
    -- ASTRON (Netherlands Institute for Radio Astronomy) <http://www.astron.nl/>
    -- P.O.Box 2, 7990 AA Dwingeloo, The Netherlands
    --
    -- This program is free software: you can redistribute it and/or modify
    -- it under the terms of the GNU General Public License as published by
    -- the Free Software Foundation, either version 3 of the License, or
    -- (at your option) any later version.
    --
    -- This program is distributed in the hope that it will be useful,
    -- but WITHOUT ANY WARRANTY; without even the implied warranty of
    -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
    -- GNU General Public License for more details.
    --
    -- You should have received a copy of the GNU General Public License
    -- along with this program.  If not, see <http://www.gnu.org/licenses/>.
    --
    -------------------------------------------------------------------------------
    
    -- Purpose: Testbench for tech_mac_10g the 10G Ethernet IP technology wrapper.
    -- Description:
    --   The tb is self checking based on:
    --   . proc_tech_mac_10g_rx_packet() for expected header and data type
    --   . tx_pkt_cnt=rx_pkt_cnt > 0 must be true at the tb_end.
    -- Usage:
    --   > do wave_tb_tech_mac_10g.do
    --   > run -all
    
    LIBRARY IEEE, technology_lib, common_lib, dp_lib;
    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.common_interface_layers_pkg.ALL;
    USE common_lib.common_network_layers_pkg.ALL;
    USE common_lib.common_network_total_header_pkg.ALL;
    USE common_lib.tb_common_pkg.ALL;
    USE dp_lib.dp_stream_pkg.ALL;
    USE technology_lib.technology_pkg.ALL;
    USE technology_lib.technology_select_pkg.ALL;
    USE WORK.tech_mac_10g_component_pkg.ALL;
    USE WORK.tb_tech_mac_10g_pkg.ALL;
    
    
    ENTITY tb_tech_mac_10g IS
      -- Test bench control parameters
      GENERIC (
        g_technology : NATURAL := c_tech_select_default;
        --   g_data_type = c_tb_tech_mac_10g_data_type_symbols  = 0
        --   g_data_type = c_tb_tech_mac_10g_data_type_counter  = 1
        g_data_type  : NATURAL := c_tb_tech_mac_10g_data_type_symbols
      );
    END tb_tech_mac_10g;
    
    
    ARCHITECTURE tb OF tb_tech_mac_10g IS
    
      CONSTANT mm_clk_period            : TIME := 20 ns;    --  50 MHz
      CONSTANT tx_ref_clk_156_period    : TIME :=  6.4 ns;  -- 156.25 MHz
      CONSTANT phy_delay                : TIME :=  0 ns;
      
      CONSTANT c_st_loopback        : BOOLEAN := FALSE;  -- default FALSE to verify the DUT, else use TRUE to verify the tb itself without the DUT
      CONSTANT c_rl                 : NATURAL := 1;
      CONSTANT c_nof_tx_not_valid   : NATURAL := 0;  -- when > 0 then pull tx valid low for c_nof_tx_not_valid beats during tx
      --CONSTANT c_pkt_length_arr     : t_nat_natural_arr := (0, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 1472, 1473, 9000);
      CONSTANT c_pkt_length_arr     : t_nat_natural_arr := array_init(0, 50, 1) & (1472, 1473) & 9000;  -- frame longer than 1518-46 = 1472 is received with rx_sosi.err = 8
                                                                                                        -- jumbo frame is 9018-46 = 8972
      CONSTANT c_nof_pkt            : NATURAL := c_pkt_length_arr'LENGTH;
    
      CONSTANT c_dst_mac            : STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE) := X"10FA01020300";
      CONSTANT c_src_mac            : STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE) := X"123456789ABC";  -- = 12-34-56-78-9A-BC
      CONSTANT c_src_mac_tx         : STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE) := c_src_mac;
      --CONSTANT c_src_mac_tx         : STD_LOGIC_VECTOR(c_network_eth_mac_slv'RANGE) := X"100056789ABC";  -- = 10-00-56-78-9A-BC
      CONSTANT c_ethertype          : STD_LOGIC_VECTOR(c_network_eth_type_slv'RANGE) := X"10FA";
      CONSTANT c_etherlen           : STD_LOGIC_VECTOR(c_network_eth_type_slv'RANGE) := "0000000000010000";
    
      -- Packet headers
      CONSTANT c_eth_header_ethertype : t_network_eth_header := (c_dst_mac, c_src_mac_tx, c_ethertype);
      CONSTANT c_eth_header_etherlen  : t_network_eth_header := (c_dst_mac, c_src_mac_tx, c_etherlen);
      
      SIGNAL total_header      : t_network_total_header := c_network_total_header_ones;  -- default fill all fields with value 1
      
      -- Clocks and reset
      SIGNAL tb_end            : STD_LOGIC := '0';
      SIGNAL mm_clk            : STD_LOGIC := '0';  -- memory-mapped bus clock
      SIGNAL mm_rst            : STD_LOGIC;         -- reset synchronous with mm_clk
      SIGNAL tx_ref_clk_312    : STD_LOGIC := '1';  -- mac_10g
      SIGNAL tx_ref_clk_156    : STD_LOGIC := '0';  -- mac_10g reference clock
      SIGNAL tx_rst            : STD_LOGIC;         -- reset synchronous with tx_ref_clk_156
      SIGNAL rx_phy_clk_312    : STD_LOGIC := '1';  -- mac_10g
      SIGNAL rx_phy_clk_156    : STD_LOGIC := '0';  -- mac_10g rx clock from phy = tx_ref_clk_156 in this tb
      SIGNAL rx_rst            : STD_LOGIC;         -- reset synchronous with rx_phy_clk_156 = tx_ref_clk_156 in this tb
    
      -- 10G MAC control interface
      SIGNAL mm_init           : STD_LOGIC := '1';
      SIGNAL mm_mosi_wrdata    : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- 32 bit;
      SIGNAL mm_mosi           : t_mem_mosi;
      SIGNAL mm_miso           : t_mem_miso;
      SIGNAL mm_miso_rdval     : STD_LOGIC;
      SIGNAL mm_miso_rddata    : STD_LOGIC_VECTOR(c_word_w-1 DOWNTO 0);  -- 32 bit;
      
      -- 10G MAC transmit interface
      -- . The tb is the ST source
      SIGNAL tx_en             : STD_LOGIC := '1';
      SIGNAL tx_siso           : t_dp_siso;
      SIGNAL tx_sosi           : t_dp_sosi;
      SIGNAL tx_sosi_data      : STD_LOGIC_VECTOR(c_tech_mac_10g_data_w-1 DOWNTO 0);  -- 64 bit
      
      -- 10G MAC receive interface
      -- . The tb is the ST sink
      SIGNAL rx_siso           : t_dp_siso;
      SIGNAL rx_sosi           : t_dp_sosi;
      SIGNAL rx_sosi_data      : STD_LOGIC_VECTOR(c_tech_mac_10g_data_w-1 DOWNTO 0);  -- 64 bit
    
      -- 10G MAC XGMII interface
      SIGNAL xgmii_tx_data     : STD_LOGIC_VECTOR(c_xgmii_w-1 DOWNTO 0);  -- 72 bit
      SIGNAL xgmii_rx_data     : STD_LOGIC_VECTOR(c_xgmii_w-1 DOWNTO 0);  -- 72 bit
    
      -- Verification
      SIGNAL expected_sosi_arr : t_dp_sosi_arr(0 TO c_nof_pkt-1);
    
      SIGNAL tx_pkt_cnt     : NATURAL := 0;
      SIGNAL rx_pkt_cnt     : NATURAL := 0;
      
    BEGIN
    
      -- run 50 us
      mm_clk         <= NOT mm_clk         AFTER mm_clk_period/2;          -- MM clock
      tx_ref_clk_156 <= NOT tx_ref_clk_156 AFTER tx_ref_clk_156_period/2;  -- mac_10g tx reference clock
      tx_ref_clk_312 <= NOT tx_ref_clk_312 AFTER tx_ref_clk_156_period/4;
      rx_phy_clk_156 <= tx_ref_clk_156;                                    -- use tx_ref_clk_156 to model PHY
      rx_phy_clk_312 <= tx_ref_clk_312;
      
      mm_rst <= '1', '0' AFTER mm_clk_period*10;
      tx_rst <= '1', '0' AFTER tx_ref_clk_156_period*10;
      rx_rst <= '1', '0' AFTER tx_ref_clk_156_period*10;
    
      -- debug signals to ease monitoring in wave window  
      tx_sosi_data <= tx_sosi.data(c_tech_mac_10g_data_w-1 DOWNTO 0);
      rx_sosi_data <= rx_sosi.data(c_tech_mac_10g_data_w-1 DOWNTO 0);
      
      mm_mosi_wrdata <= mm_mosi.wrdata(c_word_w-1 DOWNTO 0);
      mm_miso_rddata <= mm_miso.rddata(c_word_w-1 DOWNTO 0);
      mm_miso_rdval <= '1' WHEN mm_mosi.rd='1' AND mm_miso.waitrequest='0' ELSE '0';  -- c_rd_latency = 1
                       
      -- Use signal to leave unused fields 'X'
      total_header.eth <= c_eth_header_ethertype;
    
      p_mm_setup : PROCESS
      BEGIN
        mm_init  <= '1';
        mm_mosi.wr <= '0';
        mm_mosi.rd <= '0';
    
        -- wait until after reset release
        proc_common_wait_until_low(mm_clk, mm_rst);
        proc_common_wait_some_cycles(mm_clk, 10);
    
        proc_tech_mac_10g_setup(g_technology,
                                c_src_mac,
                                mm_clk, mm_miso, mm_mosi);
        mm_init <= '0';
        WAIT;
      END PROCESS;
    
      
      p_ff_transmitter : PROCESS
      BEGIN
        -- . Avalon ST
        tx_sosi  <= c_dp_sosi_rst;
    
        WHILE mm_init/='0' LOOP
          WAIT UNTIL rising_edge(tx_ref_clk_156);
        END LOOP;
        proc_common_wait_some_cycles(tx_ref_clk_156, 10);
    
        -- Loopback txp->rxp so use promiscuous mode or use DST_MAC = c_src_mac to send to itself
        
        -- TX frame:
        -- . I=0 is empty payload, so only 4 words of the ETH header with 46 padding zeros, so empty = 2
        -- . For I=1 to 46 the payload length remains 46 with padding zeros, so empty = 2
        -- . For I>46 the payload length is I and empty = 4 - (I mod 4)
        
        FOR I IN 0 TO c_nof_pkt-1 LOOP
          proc_tech_mac_10g_tx_packet(total_header, c_pkt_length_arr(I), g_data_type, c_rl, c_nof_tx_not_valid, tx_ref_clk_156, tx_en, tx_siso, tx_sosi);
          proc_common_wait_some_cycles(tx_ref_clk_156, 0);
        END LOOP;
    
        proc_common_wait_some_cycles(tx_ref_clk_156, c_pkt_length_arr(c_nof_pkt-1)/c_tech_mac_10g_symbols_per_beat);
        proc_common_wait_some_cycles(tx_ref_clk_156, 100);
        tb_end <= '1';
        WAIT;
      END PROCESS;
    
      
      p_ff_receiver : PROCESS
      BEGIN
        -- . Avalon ST
        rx_siso <= c_dp_siso_hold;
    
        WHILE mm_init/='0' LOOP
          WAIT UNTIL rising_edge(rx_phy_clk_156);
        END LOOP;
    
        -- Receive forever
        WHILE TRUE LOOP
          proc_tech_mac_10g_rx_packet(total_header, g_data_type, rx_phy_clk_156, rx_sosi, rx_siso);
        END LOOP;
    
        WAIT;
      END PROCESS;
      
      
      p_ff_store_tx_sosi_at_eop : PROCESS(tx_ref_clk_156)
        VARIABLE vI : NATURAL := 0;
      BEGIN
        IF rising_edge(tx_ref_clk_156) THEN
          IF tx_sosi.eop='1' THEN
            expected_sosi_arr(vI) <= tx_sosi;
            vI := vI +1;
          END IF;
        END IF;
      END PROCESS;
    
      p_ff_verify_rx_sosi_at_eop : PROCESS(rx_phy_clk_156)
        VARIABLE vI   : NATURAL := 0;
        VARIABLE vLow : NATURAL := 0;
      BEGIN
        IF rising_edge(rx_phy_clk_156) THEN
          IF rx_sosi.eop='1' THEN
              -- frame shorter than 64 get padded so em 
            IF c_pkt_length_arr(vI) < 64 - 14 - 20 - 8 - 4 THEN  -- = minimum frame 64 - ETH 14 - IP 20 - UDP 8 - CRC 4
              -- frame shorter than 64 get padded so empty after stripping the Rx CRC is fixed 4, which becomes 6 due to pre header padding for UDP word align
              IF TO_UINT(rx_sosi.empty) /= 6 THEN
                REPORT "RX: Wrong padded empty" SEVERITY ERROR;
              END IF;
            ELSE
              IF rx_sosi.empty /= expected_sosi_arr(vI).empty THEN
                REPORT "RX: Wrong empty" SEVERITY ERROR;
              ELSE
                vLow := TO_UINT(rx_sosi.empty)*8;
                ASSERT rx_sosi.data(63 DOWNTO vLow) = expected_sosi_arr(vI).data(63 DOWNTO vLow)  REPORT "RX: Wrong data at eop" SEVERITY ERROR;
              END IF;
            END IF;
            vI := vI +1;
          END IF;
        END IF;
      END PROCESS;
    
      gen_dut : IF c_st_loopback=FALSE GENERATE
        dut : ENTITY work.tech_mac_10g
        GENERIC MAP (
          g_technology          => g_technology,
          --g_pre_header_padding  => FALSE
          g_pre_header_padding  => TRUE
        )
        PORT MAP (
          -- MM
          mm_clk           => mm_clk,
          mm_rst           => mm_rst,
          csr_mosi         => mm_mosi,        -- CSR = control status register
          csr_miso         => mm_miso,
      
          -- ST
          tx_clk_312       => tx_ref_clk_312,
          tx_clk_156       => tx_ref_clk_156, -- 156.25 MHz local reference
          tx_rst           => tx_rst,
          tx_snk_in        => tx_sosi,        -- 64 bit data
          tx_snk_out       => tx_siso, 
          
          rx_clk_312       => rx_phy_clk_312,
          rx_clk_156       => rx_phy_clk_156, -- 156.25 MHz from rx phy
          rx_rst           => rx_rst,
          rx_src_out       => rx_sosi,        -- 64 bit data
          rx_src_in        => rx_siso, 
          
          -- XGMII
          xgmii_tx_data    => xgmii_tx_data,  -- 72 bit
          xgmii_rx_data    => xgmii_rx_data   -- 72 bit
        );
      END GENERATE;
    
      no_dut : IF c_st_loopback=TRUE GENERATE
        rx_sosi <= tx_sosi;
        tx_siso <= rx_siso;
      END GENERATE;
    
      -- Loopback XGMII
      xgmii_rx_data <= TRANSPORT xgmii_tx_data AFTER phy_delay;
    
      -- Verification
      tx_pkt_cnt <= tx_pkt_cnt + 1 WHEN tx_sosi.sop='1' AND rising_edge(tx_ref_clk_156);
      rx_pkt_cnt <= rx_pkt_cnt + 1 WHEN rx_sosi.eop='1' AND rising_edge(rx_phy_clk_156);
      
      p_tb_end : PROCESS  
      BEGIN
        WAIT UNTIL tb_end='1';
        
        -- Verify that all transmitted packets have been received
        IF tx_pkt_cnt=0 THEN
          REPORT "No packets were transmitted." SEVERITY ERROR;
        ELSIF rx_pkt_cnt=0 THEN
          REPORT "No packets were received." SEVERITY ERROR;
        ELSIF tx_pkt_cnt/=rx_pkt_cnt THEN
          REPORT "Not all transmitted packets were received." SEVERITY ERROR;
        END IF;
        
        -- Stop the simulation
        ASSERT FALSE REPORT "Simulation finished." SEVERITY FAILURE;
        WAIT;
      END PROCESS;
      
    END tb;