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

Subversion Repositories wishbone_bfm

Compare Revisions

  • This comparison shows the changes necessary to convert path
    /
    from Rev 13 to Rev 14
    Reverse comparison

Rev 13 → Rev 14

/tags/arelease/rtl/io_package.vhd
0,0 → 1,616
-------------------------------------------------------------------------------
---- ----
---- WISHBONE Wishbone_BFM IP Core ----
---- ----
---- This file is part of the Wishbone_BFM project ----
---- http://www.opencores.org/cores/Wishbone_BFM/ ----
---- ----
---- Description ----
---- Implementation of Wishbone_BFM IP core according to ----
---- Wishbone_BFM IP core specification document. ----
---- ----
---- To Do: ----
---- NA ----
---- ----
---- Author(s): ----
---- Andrew Mulcock, amulcock@opencores.org ----
---- ----
-------------------------------------------------------------------------------
---- ----
---- Copyright (C) 2008 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source 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 Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.opencores.org/lgpl.shtml ----
---- ----
-------------------------------------------------------------------------------
---- ----
-- CVS Revision History ----
---- ----
-- $Log: not supported by cvs2svn $ ----
---- ----
 
 
-- Package File Template
--
-- Purpose: This package defines supplemental types, subtypes,
-- constants, and functions
 
 
library IEEE;
use IEEE.STD_LOGIC_1164.all;
 
-- -------------------------------------------------------------------------
package io_pack is
-- -------------------------------------------------------------------------
 
constant write32_time_out : integer := 6; -- number of clocks to wait
-- on w32, before an error
constant read32_time_out : integer := 6; -- number of clocks to wait
-- on r32, before an error
 
constant clk_period : time := 10 ns; -- period of simulation clock
 
constant max_block_size : integer := 128; -- maximum number of read or write
-- locations in a block transfer
 
type cycle_type is ( unknown,
bus_rst,
bus_idle,
rd32, rd16, rd8, -- read
wr32, wr16, wr8, -- write
rmw32, rmw16, rmw8, -- read modify write
bkr32, bkr16, brw8, -- block read
bkw32, bkw16, bkw8 -- block write
);
type bus_cycle is
record
c_type : cycle_type;
add_o : std_logic_vector( 31 downto 0);
dat_o : std_logic_vector( 31 downto 0);
dat_i : std_logic_vector( 31 downto 0);
we : std_logic;
stb : std_logic;
cyc : std_logic;
ack : std_logic;
err : std_logic;
rty : std_logic;
lock : std_logic;
sel : std_logic_vector( 3 downto 0);
clk : std_logic;
end record;
 
 
 
-- define the wishbone bus signal to share
-- with main procedure
-- Need to define it as the weekest possible ( 'Z' )
-- not so that we get a tri state bus, but so that
-- procedures called can over drive the signal in the test bench.
-- else test bench gets 'U's.
--
signal bus_c : bus_cycle :=
( unknown,
(others => 'Z'),
(others => 'Z'),
(others => 'Z'),
'Z',
'Z',
'Z',
'Z',
'Z',
'Z',
'Z',
(others => 'Z'),
'Z'
);
 
type block_type is array ( max_block_size downto 0 ) of std_logic_vector( 31 downto 0 );
 
 
-- ----------------------------------------------------------------------
-- to_nibble
-- ----------------------------------------------------------------------
-- usage to_nibble( slv ); -- convert 4 bit slv to a character
function to_nibble( s:std_logic_vector(3 downto 0)) return character;
 
 
-- ----------------------------------------------------------------------
-- to_hex
-- ----------------------------------------------------------------------
-- usage to_hex( slv ); -- convert a slv to a string
function to_hex( v:std_logic_vector) return string;
 
 
 
 
 
 
 
 
-- ----------------------------------------------------------------------
-- clock_wait
-- ----------------------------------------------------------------------
-- usage clock_wait( number of cycles, bus_record ); -- wait n number of clock cycles
procedure clock_wait(
constant no_of_clocks : in integer;
signal bus_c : inout bus_cycle
);
 
 
-- ----------------------------------------------------------------------
-- wb_init
-- ----------------------------------------------------------------------
-- usage wb_init( bus_record ); -- Initalises the wishbone bus
procedure wb_init(
signal bus_c : inout bus_cycle
);
 
 
-- ----------------------------------------------------------------------
-- wb_rst
-- ----------------------------------------------------------------------
-- usage wb_rst( 10, RST_sys, bus_record ); -- reset system for 10 clocks
procedure wb_rst (
constant no_of_clocks : in integer;
signal reset : out std_logic;
signal bus_c : inout bus_cycle
);
 
 
 
-- ----------------------------------------------------------------------
-- wr_32
-- ----------------------------------------------------------------------
-- usage wr_32 ( address, data , bus_record )-- write 32 bit data to a 32 bit address
procedure wr_32 (
constant address_data : in std_logic_vector( 31 downto 0);
constant write_data : in std_logic_vector( 31 downto 0);
signal bus_c : inout bus_cycle
);
 
-- ----------------------------------------------------------------------
-- rd_32
-- ----------------------------------------------------------------------
-- usage rd_32 ( address, data , bus_record )-- read 32 bit data from a 32 bit address
procedure rd_32 (
constant address_data : in std_logic_vector( 31 downto 0);
variable read_data : out std_logic_vector( 31 downto 0);
signal bus_c : inout bus_cycle
);
 
 
-- ----------------------------------------------------------------------
-- rmw_32
-- ----------------------------------------------------------------------
-- usage rmw_32 ( address, read_data, write_data , bus_record )-- read 32 bit data from a 32 bit address
-- then write new 32 bit data to that address
 
procedure rmw_32 (
constant address_data : in std_logic_vector( 31 downto 0);
variable read_data : out std_logic_vector( 31 downto 0);
constant write_data : in std_logic_vector( 31 downto 0);
signal bus_c : inout bus_cycle
);
 
 
-- ----------------------------------------------------------------------
-- bkw_32
-- ----------------------------------------------------------------------
-- usage bkw_32 ( address_array, write_data_array, array_size , bus_record )
-- write each data to the coresponding address of the array
 
procedure bkw_32 (
constant address_data : in block_type;
constant write_data : in block_type;
constant array_size : in integer;
signal bus_c : inout bus_cycle
);
 
-- ----------------------------------------------------------------------
-- bkr_32
-- ----------------------------------------------------------------------
-- usage bkr_32 ( address_array, read_data_array, array_size , bus_record )
-- read from each address data to the coresponding address of the array
 
procedure bkr_32 (
constant address_data : in block_type;
variable read_data : out block_type;
constant array_size : in integer;
signal bus_c : inout bus_cycle
) ;
 
 
 
-- -------------------------------------------------------------------------
end io_pack;
-- -------------------------------------------------------------------------
 
 
 
 
 
-- -------------------------------------------------------------------------
-- -------------------------------------------------------------------------
-- -------------------------------------------------------------------------
package body io_pack is
-- -------------------------------------------------------------------------
 
-- ----------------------------------------------------------------------
-- to_nibble
-- ----------------------------------------------------------------------
-- usage to_nibble( slv ); -- convert 4 bit slv to a character
function to_nibble( s:std_logic_vector(3 downto 0)) return character is
begin
case s is
when "0000" => return '0';
when "0001" => return '1';
when "0010" => return '2';
when "0011" => return '3';
when "0100" => return '4';
when "0101" => return '5';
when "0110" => return '6';
when "0111" => return '7';
when "1000" => return '8';
when "1001" => return '9';
when "1010" => return 'A';
when "1011" => return 'B';
when "1100" => return 'C';
when "1101" => return 'D';
when "1110" => return 'E';
when "1111" => return 'F';
when others=> return '?';
end case;
end function to_nibble;
 
 
-- ----------------------------------------------------------------------
-- to_hex
-- ----------------------------------------------------------------------
-- usage to_hex( slv ); -- convert a slv to a string
function to_hex( v:std_logic_vector) return string is
constant c:std_logic_vector(v'length+3 downto 1) := "000" & to_x01(v);
begin
if v'length < 1 then return ""; end if;
return to_hex(c(v'length downto 5)) & to_nibble(c(4 downto 1));
end function to_hex;
 
 
 
-- ----------------------------------------------------------------------
-- clock_wait
-- ----------------------------------------------------------------------
-- usage clock_wait( number of cycles, bus_record ); -- wait n number of clock cycles
procedure clock_wait(
constant no_of_clocks : in integer;
signal bus_c : inout bus_cycle
) is
begin
for n in 1 to no_of_clocks loop
wait until rising_edge( bus_c.clk );
end loop;
 
end procedure clock_wait;
 
 
 
-- --------------------------------------------------------------------
-- usage wb_init( bus_record ); -- Initalises the wishbone bus
procedure wb_init(
signal bus_c : inout bus_cycle
) is
begin
 
bus_c.c_type <= bus_idle;
bus_c.add_o <= ( others => '0');
bus_c.dat_o <= ( others => '0');
bus_c.we <= '0';
bus_c.stb <= '0';
bus_c.cyc <= '0';
bus_c.lock <= '0';
 
wait until rising_edge( bus_c.clk ); -- allign to next clock
end procedure wb_init;
 
 
-- --------------------------------------------------------------------
-- usage wb_rst( 10, RST_sys, bus_record ); -- reset system for 10 clocks
procedure wb_rst (
constant no_of_clocks : in integer;
signal reset : out std_logic;
signal bus_c : inout bus_cycle
) is
begin
bus_c.c_type <= bus_rst;
bus_c.stb <= '0';
bus_c.cyc <= '0';
 
reset <= '1';
for n in 1 to no_of_clocks loop
wait until falling_edge( bus_c.clk );
end loop;
reset <= '0';
wait until rising_edge( bus_c.clk);
end procedure wb_rst;
 
-- --------------------------------------------------------------------
procedure wr_32 (
constant address_data : in std_logic_vector( 31 downto 0);
constant write_data : in std_logic_vector( 31 downto 0);
signal bus_c : inout bus_cycle
) is
 
variable bus_write_timer : integer;
 
begin
 
bus_c.c_type <= wr32;
bus_c.add_o <= address_data;
bus_c.dat_o <= write_data;
bus_c.we <= '1'; -- write cycle
bus_c.sel <= ( others => '1'); -- on all four banks
bus_c.cyc <= '1';
bus_c.stb <= '1';
bus_write_timer := 0;
wait until rising_edge( bus_c.clk );
while bus_c.ack = '0' loop
bus_write_timer := bus_write_timer + 1;
wait until rising_edge( bus_c.clk );
exit when bus_write_timer >= write32_time_out;
end loop;
 
bus_c.c_type <= bus_idle;
bus_c.add_o <= ( others => '0');
bus_c.dat_o <= ( others => '0');
bus_c.we <= '0';
bus_c.sel <= ( others => '0');
bus_c.cyc <= '0';
bus_c.stb <= '0';
 
end procedure wr_32;
 
 
 
-- ----------------------------------------------------------------------
-- rd_32
-- ----------------------------------------------------------------------
-- usage rd_32 ( address, data , bus_record )-- read 32 bit data from a 32 bit address
--
-- Note: need read data to be a variable to be passed back to calling process;
-- If it's a signal, it's one delta out, and in the calling process
-- it will have the wrong value, the one after the clock !
--
 
procedure rd_32 (
constant address_data : in std_logic_vector( 31 downto 0);
variable read_data : out std_logic_vector( 31 downto 0);
signal bus_c : inout bus_cycle
) is
 
variable bus_read_timer : integer;
 
begin
 
bus_c.c_type <= rd32;
bus_c.add_o <= address_data;
bus_c.we <= '0'; -- read cycle
bus_c.sel <= ( others => '1'); -- on all four banks
bus_c.cyc <= '1';
bus_c.stb <= '1';
bus_read_timer := 0;
 
wait until rising_edge( bus_c.clk );
while bus_c.ack = '0' loop
bus_read_timer := bus_read_timer + 1;
wait until rising_edge( bus_c.clk );
exit when bus_read_timer >= read32_time_out;
end loop;
 
read_data := bus_c.dat_i;
bus_c.c_type <= bus_idle;
bus_c.add_o <= ( others => '0');
bus_c.dat_o <= ( others => '0');
bus_c.we <= '0';
bus_c.sel <= ( others => '0');
bus_c.cyc <= '0';
bus_c.stb <= '0';
 
end procedure rd_32;
 
-- ----------------------------------------------------------------------
-- rmw_32
-- ----------------------------------------------------------------------
-- usage rmw_32 ( address, read_data, write_data , bus_record )-- read 32 bit data from a 32 bit address
-- then write new 32 bit data to that address
 
procedure rmw_32 (
constant address_data : in std_logic_vector( 31 downto 0);
variable read_data : out std_logic_vector( 31 downto 0);
constant write_data : in std_logic_vector( 31 downto 0);
signal bus_c : inout bus_cycle
) is
 
variable bus_read_timer : integer;
variable bus_write_timer : integer;
 
begin
-- first read
bus_c.c_type <= rmw32;
bus_c.add_o <= address_data;
bus_c.we <= '0'; -- read cycle
bus_c.sel <= ( others => '1'); -- on all four banks
bus_c.cyc <= '1';
bus_c.stb <= '1';
bus_read_timer := 0;
 
wait until rising_edge( bus_c.clk );
while bus_c.ack = '0' loop
bus_read_timer := bus_read_timer + 1;
wait until rising_edge( bus_c.clk );
exit when bus_read_timer >= read32_time_out;
end loop;
 
read_data := bus_c.dat_i;
 
-- now write
bus_c.dat_o <= write_data;
bus_c.we <= '1'; -- write cycle
bus_write_timer := 0;
wait until rising_edge( bus_c.clk );
while bus_c.ack = '0' loop
bus_write_timer := bus_write_timer + 1;
wait until rising_edge( bus_c.clk );
exit when bus_write_timer >= write32_time_out;
end loop;
 
bus_c.c_type <= bus_idle;
bus_c.add_o <= ( others => '0');
bus_c.dat_o <= ( others => '0');
bus_c.we <= '0';
bus_c.sel <= ( others => '0');
bus_c.cyc <= '0';
bus_c.stb <= '0';
 
end procedure rmw_32;
 
 
-- ----------------------------------------------------------------------
-- bkw_32
-- ----------------------------------------------------------------------
-- usage bkw_32 ( address_array, write_data_array, array_size , bus_record )
-- write each data to the coresponding address of the array
 
procedure bkw_32 (
constant address_data : in block_type;
constant write_data : in block_type;
constant array_size : in integer;
signal bus_c : inout bus_cycle
) is
variable bus_write_timer : integer;
 
begin
-- for each element, perform a write 32.
 
for n in 0 to array_size - 1 loop
bus_c.c_type <= bkw32;
bus_c.add_o <= address_data(n);
bus_c.dat_o <= write_data(n);
bus_c.we <= '1'; -- write cycle
bus_c.sel <= ( others => '1'); -- on all four banks
bus_c.cyc <= '1';
bus_c.stb <= '1';
bus_write_timer := 0;
wait until rising_edge( bus_c.clk );
while bus_c.ack = '0' loop
bus_write_timer := bus_write_timer + 1;
wait until rising_edge( bus_c.clk );
exit when bus_write_timer >= write32_time_out;
end loop;
bus_c.c_type <= bus_idle;
bus_c.add_o <= ( others => '0');
bus_c.dat_o <= ( others => '0');
bus_c.we <= '0';
bus_c.sel <= ( others => '0');
bus_c.cyc <= '0';
bus_c.stb <= '0';
end loop;
 
end procedure bkw_32;
 
-- ----------------------------------------------------------------------
-- bkr_32
-- ----------------------------------------------------------------------
-- usage bkr_32 ( address_array, read_data_array, array_size , bus_record )
-- read from each address data to the coresponding address of the array
 
procedure bkr_32 (
constant address_data : in block_type;
variable read_data : out block_type;
constant array_size : in integer;
signal bus_c : inout bus_cycle
) is
variable bus_read_timer : integer;
 
begin
-- for each element, perform a read 32.
 
for n in 0 to array_size - 1 loop
bus_c.c_type <= bkr32;
bus_c.add_o <= address_data(n);
bus_c.we <= '0'; -- read cycle
bus_c.sel <= ( others => '1'); -- on all four banks
bus_c.cyc <= '1';
bus_c.stb <= '1';
bus_read_timer := 0;
wait until rising_edge( bus_c.clk );
while bus_c.ack = '0' loop
bus_read_timer := bus_read_timer + 1;
wait until rising_edge( bus_c.clk );
exit when bus_read_timer >= read32_time_out;
end loop;
 
read_data(n) := bus_c.dat_i;
bus_c.c_type <= bus_idle;
bus_c.add_o <= ( others => '0');
bus_c.dat_o <= ( others => '0');
bus_c.we <= '0';
bus_c.sel <= ( others => '0');
bus_c.cyc <= '0';
bus_c.stb <= '0';
end loop;
 
end procedure bkr_32;
 
 
-- -------------------------------------------------------------------------
end io_pack;
-- -------------------------------------------------------------------------
/tags/arelease/rtl/wb_master.vhd
0,0 → 1,227
-------------------------------------------------------------------------------
---- ----
---- WISHBONE Wishbone_BFM IP Core ----
---- ----
---- This file is part of the Wishbone_BFM project ----
---- http://www.opencores.org/cores/Wishbone_BFM/ ----
---- ----
---- Description ----
---- Implementation of Wishbone_BFM IP core according to ----
---- Wishbone_BFM IP core specification document. ----
---- ----
---- To Do: ----
---- NA ----
---- ----
---- Author(s): ----
---- Andrew Mulcock, amulcock@opencores.org ----
---- ----
-------------------------------------------------------------------------------
---- ----
---- Copyright (C) 2008 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source 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 Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.opencores.org/lgpl.shtml ----
---- ----
-------------------------------------------------------------------------------
---- ----
-- CVS Revision History ----
---- ----
-- $Log: not supported by cvs2svn $ ----
---- ----
 
 
-- file to 'exercise' the Wishbone bus.
--
-- Idea is to look like a wishbone master,
-- and provide procedures to exercise the bus.
--
-- syscon is an external module that provides the reset and clocks
-- to all the other modules in the design.
--
-- to enable the test script in this master to control
-- the syscon reset and clock stop,
-- this master provides tow 'extra' outputs
-- rst_i and clk_stop
--
-- when rst_sys is high, then syscon will issue a reset
-- when clk_stop is high, then syscon will stop the clock
-- on the next low transition. i.e. stopped clock is low.
 
use work.io_pack.all;
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_textio.all;
 
-- --------------------------------------------------------------------
-- --------------------------------------------------------------------
 
entity wb_master is
port(
-- sys_con control ports
RST_sys : out std_logic;
CLK_stop : out std_logic;
-- WISHBONE master interface:
RST_I : in std_logic;
CLK_I : in std_logic;
 
ADR_O : out std_logic_vector( 31 downto 0 );
DAT_I : in std_logic_vector( 31 downto 0 );
DAT_O : out std_logic_vector( 31 downto 0 );
WE_O : out std_logic;
 
STB_O : out std_logic;
CYC_O : out std_logic;
ACK_I : in std_logic;
ERR_I : in std_logic;
RTY_I : in std_logic;
LOCK_O : out std_logic;
SEL_O : out std_logic_vector( 3 downto 0 );
CYCLE_IS : out cycle_type
);
end entity wb_master;
 
-- --------------------------------------------------------------------
architecture Behavioral of wb_master is
-- --------------------------------------------------------------------
 
signal reset_int : std_logic;
 
 
-- --------------------------------------------------------------------
begin
-- --------------------------------------------------------------------
 
-- concurrent assignemente to map record to the wishbone bus
 
ADR_O <= bus_c.add_o; -- address bus out of master
DAT_O <= bus_c.dat_o; -- data bus out of master
WE_O <= bus_c.we; -- wite enable out of master
STB_O <= bus_c.stb; -- wishbone strobe out of master
CYC_O <= bus_c.cyc; -- wishbone cycle out of master
LOCK_O <= bus_c.lock; -- wishbone Lock out of master
SEL_O <= bus_c.sel; -- slelects which of the 4 bytes to use for 32 bit
CYCLE_IS <= bus_c.c_type; -- monitor output, to know what master is up to
 
bus_c.dat_i <= DAT_I;
bus_c.ack <= ACK_I;
bus_c.err <= ERR_I;
bus_c.rty <= RTY_I;
bus_c.clk <= CLK_I;
 
 
-- concurent signal as can't pass out port to procedure ?
RST_sys <= reset_int;
 
-- --------------------------------------------------------------------
test_loop : process
 
-- need to use variables to get 'data' down from the procedures,
-- if we used a signal, then we get the value after the clock edge,
-- which is not what we want, we need the value at the clock edge.
--
variable slv_32 : std_logic_vector( 31 downto 0);
 
variable bka_test_array : block_type :=
( others => x"0000_0000");
variable bkd_test_array : block_type :=
( others => x"0000_0000");
 
 
 
 
begin
 
-- Wait 100 ns for global reset to finish
wait for 100 ns;
 
--clock_wait( 2, bus_c );
 
 
wb_init( bus_c); -- initalise wishbone bus
wb_rst( 2, reset_int, bus_c ); -- reset system for 2 clocks
 
-- set up some address / data pairs
bka_test_array(0) := X"0000_0002";
bkd_test_array(0) := X"5555_0002";
 
bka_test_array(1) := X"0000_0004";
bkd_test_array(1) := X"55AA_0004";
 
bka_test_array(2) := X"0000_0006";
bkd_test_array(2) := X"AAAA_0006";
 
 
bkw_32( bka_test_array, bkd_test_array, 3, bus_c);
 
clock_wait( 1, bus_c );
 
bkr_32( bka_test_array, bkd_test_array, 3, bus_c);
 
report to_hex(bkd_test_array(0));
report to_hex(bkd_test_array(1));
report to_hex(bkd_test_array(2));
 
--
--wr_32( x"8000_0004", x"5555_5555", bus_c); -- write 32 bits address of 32 bit data
--
--rd_32( x"8000_0004", slv_32, bus_c); -- read 32 bits address of 32 bit data
--report to_hex( slv_32);
--
--clock_wait( 2, bus_c );
--
--rmw_32( x"8000_0004", slv_32, x"ABCD_EF01", bus_c );
--report to_hex( slv_32);
--
--clock_wait( 2, bus_c );
--
--rmw_32( x"8000_0004", slv_32, x"01CD_EFAB", bus_c );
--report to_hex( slv_32);
--
 
 
clock_wait( 1, bus_c );
wb_rst( 2, reset_int, bus_c ); -- reset system for 2 clocks
 
 
 
 
 
 
-- --------------------------------------------------------------------
-- and stop the test running
-- --------------------------------------------------------------------
 
CLK_stop <= '1';
wait;
 
end process test_loop;
 
 
 
 
 
-- --------------------------------------------------------------------
end architecture Behavioral;
-- --------------------------------------------------------------------
/tags/arelease/rtl/syscon.vhd
0,0 → 1,109
-------------------------------------------------------------------------------
---- ----
---- WISHBONE Wishbone_BFM IP Core ----
---- ----
---- This file is part of the Wishbone_BFM project ----
---- http://www.opencores.org/cores/Wishbone_BFM/ ----
---- ----
---- Description ----
---- Implementation of Wishbone_BFM IP core according to ----
---- Wishbone_BFM IP core specification document. ----
---- ----
---- To Do: ----
---- NA ----
---- ----
---- Author(s): ----
---- Andrew Mulcock, amulcock@opencores.org ----
---- ----
-------------------------------------------------------------------------------
---- ----
---- Copyright (C) 2008 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source 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 Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.opencores.org/lgpl.shtml ----
---- ----
-------------------------------------------------------------------------------
---- ----
-- CVS Revision History ----
---- ----
-- $Log: not supported by cvs2svn $ ----
---- ----
 
 
use work.io_pack.all; -- contains the clock frequency integer
 
 
library ieee;
use ieee.std_logic_1164.all;
-- --------------------------------------------------------------------
-- --------------------------------------------------------------------
 
entity syscon is
port(
-- sys_con ports
RST_sys : in std_logic;
CLK_stop : in std_logic;
RST_O : out std_logic;
CLK_O : out std_logic
);
 
end syscon;
 
architecture Behavioral of syscon is
 
signal clk_internal : std_logic;
signal rst_internal : std_logic := '0'; -- not reset
 
begin
 
 
-- --------------------------------------------------------------------
-- --------------------------------------------------------------------
-- --------------------------------------------------------------------
-- sys con siumulator
clock_loop : process
begin
clk_internal <= '0';
if CLK_stop = '1' then
wait;
end if;
wait for clk_period/2;
clk_internal <= '1';
wait for clk_period/2;
end process clock_loop;
 
 
CLK_O <= clk_internal;
 
rst_loop : process ( RST_sys, clk_internal )
begin
if ( RST_sys = '1' ) then
rst_internal <= '1';
elsif rising_edge( clk_internal ) then
if RST_sys = '0' then
rst_internal <= '0';
end if;
end if;
end process rst_loop;
 
RST_O <= rst_internal;
 
end Behavioral;
/tags/arelease/rtl/wbtb_1m_1s.vhd
0,0 → 1,184
-------------------------------------------------------------------------------
---- ----
---- WISHBONE Wishbone_BFM IP Core ----
---- ----
---- This file is part of the Wishbone_BFM project ----
---- http://www.opencores.org/cores/Wishbone_BFM/ ----
---- ----
---- Description ----
---- Implementation of Wishbone_BFM IP core according to ----
---- Wishbone_BFM IP core specification document. ----
---- ----
---- To Do: ----
---- NA ----
---- ----
---- Author(s): ----
---- Andrew Mulcock, amulcock@opencores.org ----
---- ----
-------------------------------------------------------------------------------
---- ----
---- Copyright (C) 2008 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source 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 Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.opencores.org/lgpl.shtml ----
---- ----
-------------------------------------------------------------------------------
---- ----
-- CVS Revision History ----
---- ----
-- $Log: not supported by cvs2svn $ ----
---- ----
 
--
-- wbtb_1m_1s
--
-- this testbench joins together
-- one wishbone master and one wishbone slave,
-- along with the required sys_con module
--
-- having only on emaster and one slave, no logic is
-- required, outputs of one connect to inputs of the other.
--
 
 
use work.io_pack.all;
 
library ieee;
use ieee.std_logic_1164.all;
 
ENTITY wbtb_1m_1s_vhd IS
END wbtb_1m_1s_vhd;
 
ARCHITECTURE behavior OF wbtb_1m_1s_vhd IS
 
-- Component Declaration for wishbone system controler
COMPONENT syscon
PORT(
RST_sys : in std_logic;
CLK_stop : in std_logic;
RST_O : out std_logic;
CLK_O : out std_logic
);
END COMPONENT;
 
-- Component Declaration for wishbone master
COMPONENT wb_master
PORT(
RST_I : IN std_logic;
CLK_I : IN std_logic;
DAT_I : IN std_logic_vector(31 downto 0);
ACK_I : IN std_logic;
ERR_I : IN std_logic;
RTY_I : IN std_logic;
SEL_O : OUT std_logic_vector(3 downto 0);
RST_sys : OUT std_logic;
CLK_stop : OUT std_logic;
ADR_O : OUT std_logic_vector(31 downto 0);
DAT_O : OUT std_logic_vector(31 downto 0);
WE_O : OUT std_logic;
STB_O : OUT std_logic;
CYC_O : OUT std_logic;
LOCK_O : OUT std_logic;
CYCLE_IS : OUT cycle_type
);
END COMPONENT;
 
 
-- Component Declaration for wishbone slave
COMPONENT wb_mem_32x16
PORT(
ACK_O : out std_logic;
ADR_I : in std_logic_vector( 3 downto 0 );
CLK_I : in std_logic;
DAT_I : in std_logic_vector( 31 downto 0 );
DAT_O : out std_logic_vector( 31 downto 0 );
STB_I : in std_logic;
WE_I : in std_logic
);
END COMPONENT;
 
--Inputs
SIGNAL RST_I : std_logic := '0';
SIGNAL CLK_I : std_logic := '0';
SIGNAL ACK_I : std_logic := '0';
SIGNAL ERR_I : std_logic := '0';
SIGNAL RTY_I : std_logic := '0';
SIGNAL DAT_I : std_logic_vector(31 downto 0) := (others=>'0');
 
--Outputs
SIGNAL RST_sys : std_logic;
SIGNAL CLK_stop : std_logic;
SIGNAL ADR_O : std_logic_vector(31 downto 0);
SIGNAL DAT_O : std_logic_vector(31 downto 0);
SIGNAL WE_O : std_logic;
SIGNAL STB_O : std_logic;
SIGNAL CYC_O : std_logic;
SIGNAL LOCK_O : std_logic;
SIGNAL SEL_O : std_logic_vector(3 downto 0);
SIGNAL CYCLE_IS : cycle_type;
 
 
-- ---------------------------------------------------------------
BEGIN
-- ---------------------------------------------------------------
-- module port => signal name
-- Instantiate the system controler
sys_con: syscon PORT MAP(
RST_sys => RST_sys,
CLK_stop => CLK_stop,
RST_O => RST_I,
CLK_O => CLK_I
);
 
-- Instantiate the wishbone master
wb_m1: wb_master PORT MAP(
RST_sys => RST_sys,
CLK_stop => CLK_stop,
RST_I => RST_I,
CLK_I => CLK_I,
ADR_O => ADR_O,
DAT_I => DAT_I,
DAT_O => DAT_O,
WE_O => WE_O,
STB_O => STB_O,
CYC_O => CYC_O,
ACK_I => ACK_I,
ERR_I => ERR_I,
RTY_I => RTY_I,
LOCK_O => LOCK_O,
SEL_O => SEL_O,
CYCLE_IS => CYCLE_IS
);
 
 
-- Instantiate the wishbone slave
wb_s1: wb_mem_32x16 PORT MAP(
ACK_O => ACK_I,
ADR_I => ADR_O( 3 downto 0 ),
CLK_I => CLK_I,
DAT_I => DAT_O,
DAT_O => DAT_I,
STB_I => STB_O,
WE_I => WE_O
);
 
 
END;
/tags/arelease/rtl/wbmem32X16.vhd
0,0 → 1,98
--------------------------------------------------------------------------------
---- ----
---- WISHBONE wishbone out port from b3 spec IP Core ----
---- ----
---- This file is part of the wishbone out port from b3 spec project ----
---- http://www.opencores.org/cores/wishbone_out_port ----
---- ----
---- Description ----
---- Implementation of the wishbone out port from b3 spec IP core ----
---- according to wishbone out port from b3 spec IP core specification ----
---- document. ----
---- ----
---- To Do: ----
---- NA ----
---- ----
---- Taken directly from the wishbone out port from b3 spec, appendix A ----
---- Changes made, 'tidy up', I like things in lines ----
---- change name, as Xilinx tools ( 9.2 sp 4 ) do not like ----
---- entity same name as the file name. ----
---- Used others clause for sync reset. ----
---- ----
---- Author(s): ----
---- Andrew Mulcock, amulcock@opencores.org ----
---- ----
--------------------------------------------------------------------------------
---- ----
---- Copyright (C) 2008 Authors and OPENCORES.ORG ----
---- ----
---- This source file may be used and distributed without ----
---- restriction provided that this copyright statement is not ----
---- removed from the file and that any derivative work contains ----
---- the original copyright notice and the associated disclaimer. ----
---- ----
---- This source file is free software; you can redistribute it ----
---- and/or modify it under the terms of the GNU Lesser General ----
---- Public License as published by the Free Software Foundation; ----
---- either version 2.1 of the License, or (at your option) any ----
---- later version. ----
---- ----
---- This source 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 Lesser General Public License for more ----
---- details. ----
---- ----
---- You should have received a copy of the GNU Lesser General ----
---- Public License along with this source; if not, download it ----
---- from http://www.opencores.org/lgpl.shtml ----
---- ----
--------------------------------------------------------------------------------
---- ----
-- CVS Revision History ----
---- ----
-- $Log: not supported by cvs2svn $ ----
---- ----
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
 
entity WB_MEM_32X16 is
port(
-- WISHBONE SLAVE interface:
-- Single-Port RAM with Asynchronous Read
--
ACK_O : out std_logic;
ADR_I : in std_logic_vector( 3 downto 0 );
CLK_I : in std_logic;
DAT_I : in std_logic_vector( 31 downto 0 );
DAT_O : out std_logic_vector( 31 downto 0 );
STB_I : in std_logic;
WE_I : in std_logic
);
end entity WB_MEM_32X16;
 
 
architecture rtl of WB_MEM_32X16 is
 
type ram_type is array (15 downto 0) of std_logic_vector (31 downto 0);
signal RAM : ram_type;
 
begin
 
REG: process( CLK_I )
begin
if( rising_edge( CLK_I ) ) then
if( (STB_I and WE_I) = '1' ) then
RAM(to_integer(unsigned(ADR_I))) <= DAT_I;
end if;
end if;
end process REG;
 
ACK_O <= STB_I;
 
DAT_O <= RAM(to_integer(unsigned(ADR_I)));
 
end architecture rtl;
/tags/arelease/doc/src/wb_bfm_testbench.odg Cannot display: file marked as a binary type. svn:mime-type = application/octet-stream
tags/arelease/doc/src/wb_bfm_testbench.odg Property changes : Added: svn:mime-type ## -0,0 +1 ## +application/octet-stream \ 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.