Commit 05346fed authored by dpedrett's avatar dpedrett

RST_i signal removed from VME64xCore_Top, add odd parity control, default…

RST_i signal removed from VME64xCore_Top, add odd parity control, default configuration: WB Data bus 32 bit, module disabled

git-svn-id: http://svn.ohwr.org/vme64x-core/trunk@151 665b4545-5c6b-4c24-801b-41150b02b44b
parent f4dd4cec
This diff is collapsed.
This diff is collapsed.
-------------------------------------------------------------------------------
-- Title : Main package file
-- Project : Generics RAMs and FIFOs collection
-------------------------------------------------------------------------------
-- File : genram_pkg.vhd
-- Author : Tomasz Wlostowski
-- Company : CERN BE-CO-HT
-- Created : 2011-01-25
-- Last update: 2011-05-11
-- Platform :
-- Standard : VHDL'93
-------------------------------------------------------------------------------
--
-- Copyright (c) 2011 CERN
--
-- 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.gnu.org/licenses/lgpl-2.1.html
--
-------------------------------------------------------------------------------
-- Revisions :
-- Date Version Author Description
-- 2011-01-25 1.0 twlostow Created
-------------------------------------------------------------------------------
library ieee;
use ieee.std_logic_1164.all;
use IEEE.numeric_std.all;
package genram_pkg is
function f_log2_size (A : natural) return natural;
-- Single-port synchronous RAM
component generic_spram
generic (
g_data_width : natural ;
g_size : natural := 16 ;
g_with_byte_enable : boolean := false;
g_init_file : string := "";
g_addr_conflict_resolution : string := "read_first") ;
port (
rst_n_i : in std_logic;
clk_i : in std_logic;
bwe_i : in std_logic_vector((g_data_width+7)/8-1 downto 0);
we_i : in std_logic;
a_i : in std_logic_vector(f_log2_size(g_size)-1 downto 0);
d_i : in std_logic_vector(g_data_width-1 downto 0);
q_o : out std_logic_vector(g_data_width-1 downto 0));
end component;
component generic_dpram
generic (
g_data_width : natural;
g_size : natural;
g_with_byte_enable : boolean := false;
g_addr_conflict_resolution : string := "read_first";
g_init_file : string := "";
g_dual_clock : boolean := true);
port (
rst_n_i : in std_logic := '1';
clka_i : in std_logic;
bwea_i : in std_logic_vector(g_data_width/8-1 downto 0);
wea_i : in std_logic;
aa_i : in std_logic_vector(f_log2_size(g_size)-1 downto 0);
da_i : in std_logic_vector(g_data_width-1 downto 0);
qa_o : out std_logic_vector(g_data_width-1 downto 0);
clkb_i : in std_logic;
bweb_i : in std_logic_vector(g_data_width/8-1 downto 0);
web_i : in std_logic;
ab_i : in std_logic_vector(f_log2_size(g_size)-1 downto 0);
db_i : in std_logic_vector(g_data_width-1 downto 0);
qb_o : out std_logic_vector(g_data_width-1 downto 0));
end component;
component generic_async_fifo
generic (
g_data_width : natural;
g_size : natural;
g_show_ahead : boolean := false;
g_with_rd_empty : boolean := true;
g_with_rd_full : boolean := false;
g_with_rd_almost_empty : boolean := false;
g_with_rd_almost_full : boolean := false;
g_with_rd_count : boolean := false;
g_with_wr_empty : boolean := false;
g_with_wr_full : boolean := true;
g_with_wr_almost_empty : boolean := false;
g_with_wr_almost_full : boolean := false;
g_with_wr_count : boolean := false;
g_almost_empty_threshold : integer := 0;
g_almost_full_threshold : integer := 0);
port (
rst_n_i : in std_logic := '1';
clk_wr_i : in std_logic;
d_i : in std_logic_vector(g_data_width-1 downto 0);
we_i : in std_logic;
wr_empty_o : out std_logic;
wr_full_o : out std_logic;
wr_almost_empty_o : out std_logic;
wr_almost_full_o : out std_logic;
wr_count_o : out std_logic_vector(f_log2_size(g_size)-1 downto 0);
clk_rd_i : in std_logic;
q_o : out std_logic_vector(g_data_width-1 downto 0);
rd_i : in std_logic;
rd_empty_o : out std_logic;
rd_full_o : out std_logic;
rd_almost_empty_o : out std_logic;
rd_almost_full_o : out std_logic;
rd_count_o : out std_logic_vector(f_log2_size(g_size)-1 downto 0));
end component;
component generic_sync_fifo
generic (
g_data_width : natural;
g_size : natural;
g_show_ahead : boolean := false;
g_with_empty : boolean := true;
g_with_full : boolean := true;
g_with_almost_empty : boolean := false;
g_with_almost_full : boolean := false;
g_with_count : boolean := false;
g_almost_empty_threshold : integer := 0;
g_almost_full_threshold : integer := 0);
port (
rst_n_i : in std_logic := '1';
clk_i : in std_logic;
d_i : in std_logic_vector(g_data_width-1 downto 0);
we_i : in std_logic;
q_o : out std_logic_vector(g_data_width-1 downto 0);
rd_i : in std_logic;
empty_o : out std_logic;
full_o : out std_logic;
almost_empty_o : out std_logic;
almost_full_o : out std_logic;
count_o : out std_logic_vector(f_log2_size(g_size)-1 downto 0));
end component;
end genram_pkg;
package body genram_pkg is
function f_log2_size (A : natural) return natural is
begin
for I in 1 to 64 loop -- Works for up to 64 bits
if (2**I >= A) then
return(I);
end if;
end loop;
return(63);
end function f_log2_size;
end genram_pkg;
--______________________________________________________________________________
-- VME TO WB INTERFACE
--
-- CERN,BE/CO-HT
--______________________________________________________________________________
-- File: ram_8bits.vhd
--______________________________________________________________________________
--______________________________________________________________________________
-- Authors:
-- Pablo Alvarez Sanchez (Pablo.Alvarez.Sanchez@cern.ch)
-- Davide Pedretti (Davide.Pedretti@cern.ch)
-- Date 06/2012
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.gnu.org/licenses/lgpl-2.1.html
----------------------------------------------------------------------------------------------
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use ieee.std_logic_arith.all;
library work;
use work.genram_pkg.all;
entity ram_8bits is
generic (
size : natural := 256
);
Port ( addr : in std_logic_vector (f_log2_size(size)-1 downto 0);
di : in std_logic_vector (7 downto 0);
do : out std_logic_vector (7 downto 0);
we : in std_logic;
clk_i : in std_logic);
end ram_8bits;
architecture Behavioral of ram_8bits is
type t_ram_type is array(size-1 downto 0) of std_logic_vector(7 downto 0);
signal sram : t_ram_type;
begin
process (clk_i)
begin
if (clk_i'event and clk_i = '1') then
if (we = '1') then
sram(conv_integer(unsigned(addr))) <= di;
end if;
do <= sram(conv_integer(unsigned(addr)));
end if;
end process;
end Behavioral;
--______________________________________________________________________
-- VME TO WB INTERFACE
--
-- CERN,BE/CO-HT
--______________________________________________________________________
-- File: spram.vhd
--______________________________________________________________________________
-- Description: single port ram with byte granularity
--______________________________________________________________________________
-- Authors:
-- Pablo Alvarez Sanchez (Pablo.Alvarez.Sanchez@cern.ch)
-- Davide Pedretti (Davide.Pedretti@cern.ch)
-- Date 06/2012
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.gnu.org/licenses/lgpl-2.1.html
---------------------------------------------------------------------------------------
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use ieee.std_logic_arith.all;
library work;
use work.genram_pkg.all;
entity spram is
generic (
-- standard parameters
g_data_width : natural := 64;
g_size : natural := 256;
-- if true, the user can write individual bytes by using bwe_i
g_with_byte_enable : boolean := true; --not used
-- RAM read-on-write conflict resolution. Can be "read_first" (read-then-write)
-- or "write_first" (write-then-read)
g_addr_conflict_resolution : string := "read_first"; -- not used
g_init_file : string := "" -- not used
);
port (
clk_i : in std_logic; -- clock input
-- byte write enable
bwe_i : in std_logic_vector(((g_data_width)/8)-1 downto 0);
-- address input
a_i : in std_logic_vector(f_log2_size(g_size)-1 downto 0);
-- data input
d_i : in std_logic_vector(g_data_width-1 downto 0);
-- data output
q_o : out std_logic_vector(g_data_width-1 downto 0)
);
end spram;
architecture Behavioral of spram is
constant c_num_bytes : integer := (g_data_width)/8;
begin
spram: for i in 0 to c_num_bytes-1 generate
ram8bits : entity work.ram_8bits
generic map(g_size)
port map(addr => a_i,
di => d_i(8*i+7 downto 8*i),
do => q_o(8*i+7 downto 8*i),
we => bwe_i(i),
clk_i => clk_i
);
end generate;
end Behavioral;
This diff is collapsed.
--______________________________________________________________________
-- VME TO WB INTERFACE
--
-- CERN,BE/CO-HT
--______________________________________________________________________
-- File: xwb_ram.vhd
--______________________________________________________________________
-- Description: This block acts as WB Slave to test the vme64x interface
-- Block diagram:
-- ____________________________________________
-- | |
-- | |
-- | __________ ______________ |
-- | | WB | | INT_COUNT | |
-- | | LOGIC | |______________| |
-- W | | | ______________ |
-- B | | | | FREQ | |
-- | |__________| |______________| |
-- B | ______________ |
-- U | | | |
-- S | | | |
-- | | RAM | |
-- | ______________ | 64-bit port | |
-- | | | | Byte | |
-- | | IRQ | | Granularity | |
-- | | Generator | | | |
-- | | | | | |
-- | | | | | |
-- | | | |______________| |
-- | | | |
-- | |______________| |
-- |____________________________________________|
--
-- The RAM is a single port ram, 64 bit wide with byte granularity.
-- The INT_COUNT and FREQ registers are mapped in the location 0x00 of the
-- RAM memory, but these two 32 bit registers are outside the RAM because
-- they are used to generate the interrupt requests and some logic has been
-- added around these registers.
-- INT_COUNT --> address: 0x000
-- FREQ --> address: 0x004
-- The address above mentioned are the offsett VME address of the two registers
-- WB LOGIC: some process add to generate the acknowledge and stall signals.
-- IRQ Generator: this component sends an Interrupt request (pulse) to the
-- IRQ Controller --> Necessary to test the boards.
--______________________________________________________________________________
-- Authors:
-- Pablo Alvarez Sanchez (Pablo.Alvarez.Sanchez@cern.ch)
-- Davide Pedretti (Davide.Pedretti@cern.ch)
-- Date 06/2012
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.gnu.org/licenses/lgpl-2.1.html
---------------------------------------------------------------------------------------
--
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
library work;
use work.genram_pkg.all;
use work.wishbone_pkg.all;
entity xwb_ram is
generic(
g_size : natural := 256;
g_init_file : string := "";
g_must_have_init_file : boolean := false;
g_slave1_interface_mode : t_wishbone_interface_mode;
g_slave1_granularity : t_wishbone_address_granularity
);
port(
clk_sys_i : in std_logic;
rst_n_i : in std_logic;
INT_ack : in std_logic;
slave1_i : in t_wishbone_slave_in;
slave1_o : out t_wishbone_slave_out
);
end xwb_ram;
architecture struct of xwb_ram is
function f_zeros(size : integer)
return std_logic_vector is
begin
return std_logic_vector(to_unsigned(0, size));
end f_zeros;
signal s_wea : std_logic;
signal s_bwea : std_logic_vector(c_wishbone_data_width/8-1 downto 0);
signal slave1_in : t_wishbone_slave_in;
signal slave1_out : t_wishbone_slave_out;
signal s_cyc : std_logic;
signal s_stb : std_logic;
COMPONENT IRQ_generator
PORT(
clk_i : in std_logic;
reset : in std_logic;
Freq : in std_logic_vector(31 downto 0);
Int_Count_i : in std_logic_vector(31 downto 0);
Read_Int_Count : in std_logic;
INT_ack : in std_logic;
IRQ_o : out std_logic;
Int_Count_o : out std_logic_vector(31 downto 0)
);
END COMPONENT;
signal s_INT_COUNT : std_logic_vector(31 downto 0);
signal s_FREQ : std_logic_vector(31 downto 0);
signal s_q_o : std_logic_vector(63 downto 0);
signal s_q_o1 : std_logic_vector(63 downto 0);
signal s_en_Freq : std_logic;
signal s_sel_IntCount : std_logic;
signal s_Int_Count_o : std_logic_vector(31 downto 0);
signal s_Int_Count_o1 : std_logic_vector(31 downto 0);
signal s_Read_IntCount : std_logic;
signal s_rst : std_logic;
signal s_stall : std_logic;
begin
-- reset
s_rst <= not(rst_n_i);
-- IRQ Generator, INT_COUNT and FREQ logic:
s_q_o1 <= s_INT_COUNT & s_FREQ;
s_en_Freq <= '1' when (unsigned(slave1_i.adr(f_log2_size(g_size)-1 downto 0)) = 0
and s_bwea = "00001111") else '0';
s_Int_Count_o1 <= slave1_i.dat(63 downto 32) when (s_bwea = "11110000" and
(unsigned(slave1_i.adr(f_log2_size(g_size)-1 downto 0))) = 0)
else s_Int_Count_o;
s_Read_IntCount <= '1' when (slave1_i.we = '0' and slave1_i.sel = "11110000" and
(unsigned(slave1_i.adr(f_log2_size(g_size)-1 downto 0))) = 0 and
slave1_out.ack = '1') else '0';
-- Reg INT_COUNT
INT_COUNT : entity work.Reg32bit
port map(
reset => s_rst,
enable => '1',
di => s_Int_Count_o1,
do => s_INT_COUNT,
clk_i => clk_sys_i
);
-- Reg FREQ
FREQ : entity work.Reg32bit
port map(
reset => s_rst,
enable => s_en_Freq,
di => slave1_i.dat(31 downto 0),
do => s_FREQ,
clk_i => clk_sys_i
);
-- IRQ Generator
Inst_IRQ_generator: IRQ_generator PORT MAP(
clk_i => clk_sys_i,
reset => s_rst,
Freq => s_FREQ,
Int_Count_i => s_INT_COUNT,
Read_Int_Count => s_Read_IntCount,
INT_ack => INT_ack,
IRQ_o => slave1_o.int,
Int_Count_o => s_Int_Count_o
);
-- RAM memory
U_DPRAM : entity work.spram
generic map(
-- standard parameters
g_data_width => 64,
g_size => 256,
g_with_byte_enable => true,
g_init_file => "",
g_addr_conflict_resolution => "read_first"
)
port map(
clk_i => clk_sys_i,
bwe_i => s_bwea,
a_i => slave1_i.adr(f_log2_size(g_size)-1 downto 0),
d_i => slave1_i.dat,
q_o => s_q_o
);
-- WB Logic:
s_bwea <= slave1_i.sel when s_wea = '1' else f_zeros(c_wishbone_data_width/8);
s_wea <= slave1_i.we and slave1_i.cyc and slave1_i.stb and (not s_stall);
process(clk_sys_i)
begin
if(rising_edge(clk_sys_i)) then
if(s_rst = '0') then
slave1_out.ack <= '0';
else
if(slave1_out.ack = '1' and g_slave1_interface_mode = CLASSIC) then
slave1_out.ack <= '0';
else
slave1_out.ack <= slave1_i.cyc and slave1_i.stb and (not s_stall) ;
end if;
end if;
end if;
end process;
process(clk_sys_i)
begin
if(rising_edge(clk_sys_i)) then
if(s_rst = '0') or slave1_out.ack = '1' then
s_stall <= '1';
elsif slave1_i.cyc = '1' then
s_stall <= '0';
end if;
end if;
end process;
slave1_o.dat <= s_q_o1 when unsigned(slave1_i.adr(f_log2_size(g_size)-1 downto 0)) = 0
else s_q_o;
slave1_o.stall <= s_stall;
slave1_o.err <= '0';
slave1_o.rty <= '0';
slave1_o.ack <= slave1_out.ack;
end struct;
......@@ -64,7 +64,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......@@ -76,8 +77,8 @@
---------------------------------------------------------------------------------------
-- uncomment to use the PLL
-- Library UNISIM;
-- use UNISIM.vcomponents.all;
Library UNISIM;
use UNISIM.vcomponents.all;
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.numeric_std.all;
......@@ -113,8 +114,6 @@ port(
VME_DATA_OE_N_o : out std_logic;
VME_ADDR_DIR_o : out std_logic;
VME_ADDR_OE_N_o : out std_logic;
-- not used
RST_i : in std_logic;
-- for debug:
leds : out std_logic_vector(7 downto 0)
);
......@@ -133,7 +132,6 @@ COMPONENT VME64xCore_Top
VME_AM_i : in std_logic_vector(5 downto 0);
VME_DS_n_i : in std_logic_vector(1 downto 0);
VME_GA_i : in std_logic_vector(5 downto 0);
VME_BBSY_n_i : in std_logic;
VME_IACKIN_n_i : in std_logic;
VME_IACK_n_i : in std_logic;
VME_LWORD_n_b_i : in std_logic;
......@@ -154,7 +152,6 @@ COMPONENT VME64xCore_Top
VME_ADDR_DIR_o : out std_logic;
VME_ADDR_OE_N_o : out std_logic;
-- WB signals
RST_i : in std_logic;
DAT_i : in std_logic_vector(63 downto 0);
ERR_i : in std_logic;
RTY_i : in std_logic;
......@@ -204,6 +201,7 @@ signal WbWe_o : std_logic;
signal WbStall_i : std_logic;
signal WbIrq_i : std_logic;
signal Rst : std_logic;
signal clk_in_buf : std_logic;
signal clk_in : std_logic;
signal s_locked : std_logic;
signal s_fb : std_logic;
......@@ -235,7 +233,6 @@ Inst_VME64xCore_Top: VME64xCore_Top PORT MAP(
VME_ADDR_b_o => s_VME_ADDR_b_o,
VME_DATA_b_i => VME_DATA_b,
VME_DATA_b_o => s_VME_DATA_b_o,
VME_BBSY_n_i => VME_BBSY_n_i,
VME_IRQ_n_o => VME_IRQ_n_o,
VME_IACKIN_n_i => VME_IACKIN_n_i,
VME_IACK_n_i => VME_IACK_n_i,
......@@ -245,7 +242,6 @@ Inst_VME64xCore_Top: VME64xCore_Top PORT MAP(
VME_DATA_OE_N_o => VME_DATA_OE_N_o,
VME_ADDR_DIR_o => s_VME_ADDR_DIR,
VME_ADDR_OE_N_o => VME_ADDR_OE_N_o,
RST_i => RST_i,
DAT_i => WbDat_i,
DAT_o => WbDat_o,
ADR_o => WbAdr_o,
......@@ -300,60 +296,64 @@ Inst_xwb_ram: xwb_ram
-- Outputs:
VME_ADDR_DIR_o <= s_VME_ADDR_DIR;
VME_DATA_DIR_o <= s_VME_DATA_DIR;
---------------------------------------------------------------------------------
-- uncomment to use the PLL:
-- PLL_BASE_inst : PLL_BASE
-- generic map (
-- BANDWIDTH => "OPTIMIZED", -- "HIGH", "LOW" or "OPTIMIZED"
-- CLKFBOUT_MULT => 30, -- Multiply value for all CLKOUT clock outputs (1-64)
-- CLKFBOUT_PHASE => 0.000, -- Phase offset in degrees of the clock feedback output
-- -- (0.0-360.0).
-- CLKIN_PERIOD => 50.000, -- Input clock period in ns to ps resolution (i.e. 33.333 is 30
-- -- MHz).
-- -- CLKOUT0_DIVIDE - CLKOUT5_DIVIDE: Divide amount for CLKOUT# clock output (1-128)
-- CLKOUT0_DIVIDE => 12,
-- CLKOUT1_DIVIDE => 1,
-- CLKOUT2_DIVIDE => 1,
-- CLKOUT3_DIVIDE => 1,
-- CLKOUT4_DIVIDE => 1,
-- CLKOUT5_DIVIDE => 1,
-- -- CLKOUT0_DUTY_CYCLE - CLKOUT5_DUTY_CYCLE:
-- -- Duty cycle for CLKOUT# clock output (0.01-0.99).
-- CLKOUT0_DUTY_CYCLE => 0.500,
-- CLKOUT1_DUTY_CYCLE => 0.500,
-- CLKOUT2_DUTY_CYCLE => 0.500,
-- CLKOUT3_DUTY_CYCLE => 0.500,
-- CLKOUT4_DUTY_CYCLE => 0.500,
-- CLKOUT5_DUTY_CYCLE => 0.500,
-- -- CLKOUT0_PHASE - CLKOUT5_PHASE:
-- -- Output phase relationship for CLKOUT# clock output (-360.0-360.0).
-- CLKOUT0_PHASE => 0.000,
-- CLKOUT1_PHASE => 0.000,
-- CLKOUT2_PHASE => 0.000,
-- CLKOUT3_PHASE => 0.000,
-- CLKOUT4_PHASE => 0.000,
-- CLKOUT5_PHASE => 0.000,
-- CLK_FEEDBACK => "CLKFBOUT",
-- COMPENSATION => "SYSTEM_SYNCHRONOUS",
-- DIVCLK_DIVIDE => 1, -- Division value for all output clocks (1-52)
-- REF_JITTER => 0.1, -- Reference Clock Jitter in UI (0.000-0.999).
-- RESET_ON_LOSS_OF_LOCK => FALSE -- Must be set to FALSE
-- )
-- port map (
-- CLKFBOUT => s_fb, -- 1-bit output: PLL_BASE feedback output
-- -- CLKOUT0 - CLKOUT5: 1-bit (each) output: Clock outputs
-- CLKOUT0 => clk_in, --clk 50 MHz
-- CLKOUT1 => open,
-- CLKOUT2 => open,
-- CLKOUT3 => open,
-- CLKOUT4 => open,
-- CLKOUT5 => open,
-- LOCKED => s_locked, -- 1-bit output: PLL_BASE lock status output
-- CLKFBIN => s_fb, -- 1-bit input: Feedback clock input
-- CLKIN => clk_i, -- 1-bit input: Clock input
-- RST => '0' -- 1-bit input: Reset input
-- );
PLL_BASE_inst : PLL_BASE
generic map (
BANDWIDTH => "OPTIMIZED", -- "HIGH", "LOW" or "OPTIMIZED"
CLKFBOUT_MULT => 20, -- Multiply value for all CLKOUT clock outputs (1-64)
CLKFBOUT_PHASE => 0.000, -- Phase offset in degrees of the clock feedback output
-- (0.0-360.0).
CLKIN_PERIOD => 50.000, -- Input clock period in ns to ps resolution (i.e. 33.333 is 30
-- MHz).
-- CLKOUT0_DIVIDE - CLKOUT5_DIVIDE: Divide amount for CLKOUT# clock output (1-128)
CLKOUT0_DIVIDE => 5,
CLKOUT1_DIVIDE => 1,
CLKOUT2_DIVIDE => 1,
CLKOUT3_DIVIDE => 1,
CLKOUT4_DIVIDE => 1,
CLKOUT5_DIVIDE => 1,
-- CLKOUT0_DUTY_CYCLE - CLKOUT5_DUTY_CYCLE:
-- Duty cycle for CLKOUT# clock output (0.01-0.99).
CLKOUT0_DUTY_CYCLE => 0.500,
CLKOUT1_DUTY_CYCLE => 0.500,
CLKOUT2_DUTY_CYCLE => 0.500,
CLKOUT3_DUTY_CYCLE => 0.500,
CLKOUT4_DUTY_CYCLE => 0.500,
CLKOUT5_DUTY_CYCLE => 0.500,
-- CLKOUT0_PHASE - CLKOUT5_PHASE:
-- Output phase relationship for CLKOUT# clock output (-360.0-360.0).
CLKOUT0_PHASE => 0.000,
CLKOUT1_PHASE => 0.000,
CLKOUT2_PHASE => 0.000,
CLKOUT3_PHASE => 0.000,
CLKOUT4_PHASE => 0.000,
CLKOUT5_PHASE => 0.000,
CLK_FEEDBACK => "CLKFBOUT",
COMPENSATION => "SYSTEM_SYNCHRONOUS",
DIVCLK_DIVIDE => 1, -- Division value for all output clocks (1-52)
REF_JITTER => 0.016, -- Reference Clock Jitter in UI (0.000-0.999).
RESET_ON_LOSS_OF_LOCK => FALSE -- Must be set to FALSE
)
port map (
CLKFBOUT => s_fb, -- 1-bit output: PLL_BASE feedback output
-- CLKOUT0 - CLKOUT5: 1-bit (each) output: Clock outputs
CLKOUT0 => clk_in_buf, --clk 80 MHz
CLKOUT1 => open,
CLKOUT2 => open,
CLKOUT3 => open,
CLKOUT4 => open,
CLKOUT5 => open,
LOCKED => s_locked, -- 1-bit output: PLL_BASE lock status output
CLKFBIN => s_fb, -- 1-bit input: Feedback clock input
CLKIN => clk_i, -- 1-bit input: Clock input
RST => '0' -- 1-bit input: Reset input
);
cmp_clk_dmtd_buf : BUFG
port map
(O => clk_in,
I => clk_in_buf);
-- comment the next line if the PLL is used:
clk_in <= clk_i;
-- clk_in <= clk_i;
end Behavioral;
......@@ -13,7 +13,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
......@@ -15,7 +15,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
......@@ -40,7 +40,7 @@ package VME64x is
Vme64xADDR : Vme64xAddressType;
Vme64xDATA : Vme64xDataType;
--per ora nn gestisco IACKIN e BBSY
end record;
......@@ -144,6 +144,7 @@ constant ADER2_2e_b : std_logic_vector(31 downto 0) := BA(7 downto 3) & "0000000
constant c_MBLT_Endian : std_logic_vector := x"7Ff53";
constant c_IRQ_Vector : std_logic_vector := x"7FF5F";
constant c_IRQ_level : std_logic_vector := x"7FF5B";
constant c_WB32or64 : std_logic_vector := x"7FF33";
-- CR constant
constant c_StartDefinedCR : std_logic_vector := x"00000";
constant c_EndDefinedCR : std_logic_vector := x"00FFF";
......
This diff is collapsed.
......@@ -197,7 +197,7 @@
<property xil_pn:name="Enable External Master Clock spartan6" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Enable Hardware Co-Simulation" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Enable Internal Done Pipe" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Enable Message Filtering" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Enable Message Filtering" xil_pn:value="true" xil_pn:valueState="non-default"/>
<property xil_pn:name="Enable Multi-Pin Wake-Up Suspend Mode spartan6" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Enable Multi-Threading" xil_pn:value="Off" xil_pn:valueState="default"/>
<property xil_pn:name="Enable Multi-Threading par spartan6" xil_pn:value="Off" xil_pn:valueState="default"/>
......@@ -325,7 +325,7 @@
<property xil_pn:name="Overwrite Compiled Libraries" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Overwrite Existing Symbol" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Pack I/O Registers into IOBs" xil_pn:value="Auto" xil_pn:valueState="default"/>
<property xil_pn:name="Pack I/O Registers/Latches into IOBs" xil_pn:value="For Inputs and Outputs" xil_pn:valueState="non-default"/>
<property xil_pn:name="Pack I/O Registers/Latches into IOBs" xil_pn:value="Off" xil_pn:valueState="default"/>
<property xil_pn:name="Package" xil_pn:value="fgg676" xil_pn:valueState="default"/>
<property xil_pn:name="Perform Advanced Analysis" xil_pn:value="false" xil_pn:valueState="default"/>
<property xil_pn:name="Perform Advanced Analysis Post Trace" xil_pn:value="false" xil_pn:valueState="default"/>
......
......@@ -8,8 +8,8 @@
-- Description:
-- This core implements an interface to transfer data between the VMEbus and the WBbus.
-- This core is a Slave in the VME side and Master in the WB side.
-- The main blocks: |
-- |
-- The main blocks:
--
-- ________________________________________________________________
-- | VME64xCore_Top.vhd |
-- |__ ____________________ __________________ |
......@@ -29,11 +29,22 @@
-- | | | | CR | | | |
-- | |____________________| |_______| |_________________| |
-- |________________________________________________________________|
--
-- All the VMEbus's asynchronous signals must be sampled 2 or 3 times to avoid |
-- metastability problem.
-- This core complies with the VME64x specifications and allows "plug and play"
-- configuration of VME crates.
-- The base address is setted by the Geographical lines.
-- The base address can't be setted by hand with the switches on the board.
-- If the core is used in an old VME system without GA lines, the core should be provided of
-- a logic that detects if GA = "11111" and if it is the base address of the module
-- should be derived from the switches on the board.
-- All the VMEbus's asynchronous signals must be sampled 2 or 3 times to avoid
-- metastability problem.
-- All the output signals on the WB bus are registered.
-- The Input signals from the WB bus aren't registered indeed the WB is a synchronous protocol and
-- some registers in the WB side will introduce a delay that make impossible reproduce the
-- WB PIPELINED protocol.
-- The WB Slave application must work at the same frequency of this vme64x core.
-- The main component is the VME_bus on the left of the block diagram. Inside this component
-- you can find the main finite state machine who coordinates all the synchronisms.
-- you can find the main finite state machine that coordinates all the synchronisms.
-- The WB protocol is more faster than the VME protocol so to make independent
-- the two protocols a FIFO memory can be introduced.
-- The FIFO is necessary only during 2eSST access mode.
......@@ -55,6 +66,7 @@
-- Access modes supported:
-- http://www.ohwr.org/projects/vme64x-core/repository/changes/trunk/
-- documentation/user_guides/VFC_access.pdf
-- This core is
--______________________________________________________________________________
--
-- References:
......@@ -69,7 +81,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......@@ -100,14 +113,12 @@
VME_BERR_o : out std_logic;
VME_DTACK_n_o : out std_logic;
VME_RETRY_n_o : out std_logic;
VME_RETRY_OE_o : out std_logic;
VME_LWORD_n_b_i : in std_logic;
VME_LWORD_n_b_o : out std_logic;
VME_ADDR_b_i : in std_logic_vector(31 downto 1);
VME_ADDR_b_o : out std_logic_vector(31 downto 1);
VME_DATA_b_i : in std_logic_vector(31 downto 0);
VME_DATA_b_o : out std_logic_vector(31 downto 0);
VME_BBSY_n_i : in std_logic;
VME_IRQ_n_o : out std_logic_vector(6 downto 0);
VME_IACKIN_n_i : in std_logic;
VME_IACK_n_i : in std_logic;
......@@ -119,9 +130,9 @@
VME_DATA_OE_N_o : out std_logic;
VME_ADDR_DIR_o : out std_logic;
VME_ADDR_OE_N_o : out std_logic;
-- WishBone
RST_i : in std_logic;
VME_RETRY_OE_o : out std_logic;
-- WishBone
DAT_i : in std_logic_vector(63 downto 0);
DAT_o : out std_logic_vector(63 downto 0);
ADR_o : out std_logic_vector(63 downto 0);
......@@ -172,7 +183,6 @@
signal s_INT_Vector : std_logic_vector(7 downto 0);
signal s_VME_IRQ_n_o : std_logic_vector(6 downto 0);
signal s_reset_IRQ : std_logic;
signal s_VME_GA_oversampled : std_logic_vector(5 downto 0);
signal s_CSRData_o : std_logic_vector(7 downto 0);
signal s_CSRData_i : std_logic_vector(7 downto 0);
signal s_CrCsrOffsetAddr : std_logic_vector(18 downto 0);
......@@ -335,7 +345,6 @@ begin
VME_DATA_DIR_o => s_VME_DATA_DIR_VMEbus,
VME_DATA_OE_N_o => VME_DATA_OE_N_o,
VME_AM_i => VME_AM_oversampled,
VME_BBSY_n_i => VME_BBSY_n_i, -- not used
VME_IACK_n_i => VME_IACK_n_oversampled,
-- WB
memReq_o => STB_o,
......@@ -365,7 +374,6 @@ begin
CRAMwea_o => s_CRAMwea,
CRaddr_o => s_CRaddr,
CRdata_i => s_CRdata,
VME_GA_oversampled_o => s_VME_GA_oversampled,
en_wr_CSR => s_en_wr_CSR,
CrCsrOffsetAddr => s_CrCsrOffsetAddr,
CSRData_o => s_CSRData_o,
......@@ -426,7 +434,7 @@ begin
VME_DTACK_n_o => s_VME_DTACK_IRQ,
VME_DTACK_OE_o => s_VME_DTACK_OE_IRQ,
VME_DATA_o => s_VME_DATA_IRQ,
DataDir => s_VME_DATA_DIR_IRQ
VME_DATA_DIR_o => s_VME_DATA_DIR_IRQ
);
s_reset_IRQ <= not(s_reset);
......@@ -443,7 +451,7 @@ begin
CRAM_Wen => s_CRAMwea,
en_wr_CSR => s_en_wr_CSR,
CrCsrOffsetAddr => s_CrCsrOffsetAddr,
VME_GA_oversampled => s_VME_GA_oversampled,
VME_GA_oversampled => VME_GA_oversampled,
locDataIn => s_CSRData_o,
s_err_flag => s_err_flag,
s_reset_flag => s_reset_flag,
......
......@@ -117,7 +117,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
......@@ -25,7 +25,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
......@@ -52,6 +52,8 @@
-- IRQ_level --> 0x7FF5B _|
--
-- MBLT_Endian --> 0x7FF53 --> for the swapper
--
-- WB32or64 --> 0x7FF33 --> if the bit 0 is '1' it means that the WB data bus is 32 bit
-- _
-- TIME0_ns --> 0x7FF4f |
-- TIME1_ns --> 0x7FF4b |
......@@ -60,7 +62,7 @@
-- TIME4_ns --> 0x7FF3f |
-- BYTES0 --> 0x7FF3b |
-- BYTES1 --> 0x7FF37 _|
--
--
-- CRAM memory Added. How to use the CRAM:
-- 1) The Master read the CRAM_OWNER Register location 0x7fff3; if 0 the CRAM is free
-- 2) The Master write his ID in the CRAM_OWNER Register location 0x7fff3
......@@ -98,7 +100,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......@@ -163,8 +166,19 @@ architecture Behavioral of VME_CR_CSR_Space is
signal s_CrCsrOffsetAddr : unsigned(18 downto 0);
signal s_locDataIn : unsigned(7 downto 0);
signal s_CrCsrOffsetAderIndex : unsigned(18 downto 0);
signal s_odd_parity : std_logic;
signal s_BARerror : std_logic;
signal s_BAR_o : std_logic_vector(4 downto 0);
begin
-- check the parity:
s_odd_parity <= VME_GA_oversampled(5) xor VME_GA_oversampled(4) xor
VME_GA_oversampled(3) xor VME_GA_oversampled(2) xor
VME_GA_oversampled(1) xor VME_GA_oversampled(0);
-- If the crate is not driving the GA lines or the parity is odd the BAR register
-- is set to 0x00 and the following flag is asserted; the board will not answer if the
-- master accesses its CR/CSR space and we can see a time out error in the VME bus.
s_BARerror <= not(s_BAR_o(4) or s_BAR_o(3)or s_BAR_o(2) or s_BAR_o(1) or s_BAR_o(0));
--------------------------------------------------------------------------------
-- CR
process(clk_i)
......@@ -187,11 +201,13 @@ begin
for i in 254 downto WB32or64 loop -- Initialization of the CSR memory
s_CSRarray(i) <= c_csr_array(i);
end loop;
elsif s_bar_written = '0' then
elsif s_bar_written = '0' and s_odd_parity = '1' then
-- initialization of BAR reg to access the CR/CSR space
s_CSRarray(BAR)(7 downto 3) <= unsigned(not VME_GA_oversampled(4 downto 0));
s_CSRarray(BAR)(2 downto 0) <= "000";
s_bar_written <= '1';
s_bar_written <= '1';
elsif s_odd_parity = '0' then
s_CSRarray(BAR) <= (others => '0');
elsif (en_wr_CSR = '1') then
case to_integer(s_CrCsrOffsetAddr) is
when to_integer("00" & c_BAR_addr(18 downto 2)) =>
......@@ -350,8 +366,9 @@ begin
ModuleEnable <= s_CSRarray(BIT_SET_CLR_REG)(4);
MBLT_Endian_o <= std_logic_vector(s_CSRarray(MBLT_Endian)(2 downto 0));
Sw_Reset <= s_CSRarray(BIT_SET_CLR_REG)(7);
W32 <= s_CSRarray(WB32or64)(0);
BAR_o <= std_logic_vector(s_CSRarray(BAR)(7 downto 3));
W32 <= s_CSRarray(WB32or64)(0);
BAR_o <= s_BAR_o;
s_BAR_o <= std_logic_vector(s_CSRarray(BAR)(7 downto 3));
---------------------------------------------------------------------------------------------------------------
-- CRAM:
CRAM_1 : dpblockram
......
......@@ -7,7 +7,7 @@
--______________________________________________________________________________________
-- Description: ROM memory (CR space)
--______________________________________________________________________________
-- Authors: Erik Van der Bij (Erik.Van.der.Bij@cern.ch)
-- Authors:
-- Pablo Alvarez Sanchez (Pablo.Alvarez.Sanchez@cern.ch)
-- Davide Pedretti (Davide.Pedretti@cern.ch)
-- Date 06/2012
......@@ -15,6 +15,7 @@
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
......@@ -7,14 +7,15 @@
--________________________________________________________________________________________________
-- Description: This file defines the default configuration of the CSR space after power-up or software reset.
--______________________________________________________________________________
-- Authors: Erik Van der Bij (Erik.Van.der.Bij@cern.ch)
-- Authors:
-- Pablo Alvarez Sanchez (Pablo.Alvarez.Sanchez@cern.ch)
-- Davide Pedretti (Davide.Pedretti@cern.ch)
-- Date 06/2012
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......@@ -35,7 +36,7 @@ package VME_CSR_pack is
constant c_csr_array : t_CSRarray :=
(
BAR => x"00", --CR/CSR BAR
BIT_SET_CLR_REG => x"10", --Bit set register -- 0x10=module enable
BIT_SET_CLR_REG => x"00", --Bit set register -- 0x10=module enable
USR_BIT_SET_CLR_REG => x"00", --Bit clear register
CRAM_OWNER => x"00", --CRAM_OWNER
......@@ -77,7 +78,7 @@ FUNC6_ADER_3 =>x"00",
IRQ_Vector =>x"00", --"00" because each Slot has a different IRQ Vector
-- and the VME Master should set this value
IRQ_level =>x"02",
WB32or64 =>x"00",
WB32or64 =>x"01", -- 32 bit WB of default
others => (others => '0'));
end VME_CSR_pack;
......
......@@ -146,7 +146,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
......@@ -75,11 +75,12 @@
-- Authors:
-- Pablo Alvarez Sanchez (Pablo.Alvarez.Sanchez@cern.ch)
-- Davide Pedretti (Davide.Pedretti@cern.ch)
-- Date 06/2012
-- Version v0.01
-- Date 06/2012
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......@@ -111,7 +112,7 @@ entity VME_IRQ_Controller is
VME_DTACK_n_o : out std_logic;
VME_DTACK_OE_o : out std_logic;
VME_DATA_o : out std_logic_vector (31 downto 0);
DataDir : out std_logic);
VME_DATA_DIR_o : out std_logic);
end VME_IRQ_Controller;
architecture Behavioral of VME_IRQ_Controller is
......@@ -120,6 +121,7 @@ architecture Behavioral of VME_IRQ_Controller is
--output signals
signal s_DTACK : std_logic;
signal s_DTACK_OE : std_logic;
signal s_DTACK_OE_o : std_logic;
signal s_DataDir : std_logic;
signal s_IACKOUT : std_logic;
signal s_IACKOUT_o : std_logic;
......@@ -178,7 +180,7 @@ begin
DataDirOutputSample : FlipFlopD
port map(
sig_i => s_DataDir,
sig_o => DataDir,
sig_o => VME_DATA_DIR_o,
clk_i => clk_i,
reset => '0',
enable => '1'
......@@ -191,6 +193,14 @@ begin
reset => '0',
enable => '1'
);
DTACKOEOutputSample : FlipFlopD
port map(
sig_i => s_DTACK_OE,
sig_o => s_DTACK_OE_o,
clk_i => clk_i,
reset => '0',
enable => '1'
);
process(clk_i)
begin
......@@ -222,7 +232,7 @@ begin
end if;
end process;
-- Update next state
process(currs,INT_Req_sample,VME_AS_n_i,VME_DS_n_i,s_ack_int,VME_IACKIN_n_i)
process(currs,INT_Req_sample,VME_AS_n_i,VME_DS_n_i,s_ack_int,VME_IACKIN_n_i,AS_RisingEdge)
begin
case currs is
when IDLE =>
......@@ -295,7 +305,7 @@ begin
end process;
-- Update Outputs
process(currs,AS_RisingEdge)
process(currs,VME_AS1_n_i)
begin
case currs is
when IDLE =>
......@@ -447,7 +457,7 @@ begin
s_Data <= x"000000" & INT_Vector;
s_enable <= VME_IACKIN_n_i and s_IACKOUT_o;
-- the INT_Vector is in the D0:7 lines (byte3 in big endian order)
VME_DTACK_OE_o <= s_DTACK_OE;
VME_DTACK_OE_o <= s_DTACK_OE_o;
VME_IACKOUT_n_o <= s_IACKOUT_o;
end Behavioral;
......
......@@ -13,7 +13,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.gnu.org/licenses/lgpl-2.1.html
---------------------------------------------------------------------------------------
library IEEE;
use IEEE.STD_LOGIC_1164.all;
......
......@@ -3,7 +3,7 @@
--
-- CERN,BE/CO-HT
--___________________________________________________________________________________
-- File: Wb_master.vhd
-- File: VME_Wb_master.vhd
--___________________________________________________________________________________
-- Description:
-- This component implements the WB master side in the vme64x core.
......@@ -246,13 +246,15 @@ begin
s_cardSel = '1' and s_sel = "11111111" and W32 = '0' else
(others => '0');
process(W32,s_rel_locAddr)
process(clk_i)
begin
if rising_edge(clk_i) then
if W32 = '0' then
locAddr_o <= b"000" & s_rel_locAddr(63 downto 3);
else
locAddr_o <= b"00" & s_rel_locAddr(63 downto 2);
end if;
end if;
end process;
err <= err_i;
......
This diff is collapsed.
......@@ -17,7 +17,8 @@
-- Version v0.01
--______________________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......
......@@ -12,7 +12,8 @@
-- Version v0.01
--_______________________________________________________________________
-- GNU LESSER GENERAL PUBLIC LICENSE
-- ------------------------------------
-- ------------------------------------
-- Copyright (c) 2009 - 2011 CERN
-- 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.
......@@ -61,7 +62,7 @@ package vme64x_pack is
-- Constants:
constant DFS : integer := 2; -- for accessing at the ADEM's bit 2
constant XAM_MODE : integer := 0; -- for accessing at the ADER's bit 0
constant clk_period : std_logic_vector(19 downto 0) := "00000000000000110010";
constant clk_period : std_logic_vector(19 downto 0) := "00000000000000001101";
--AM table:
constant c_A24_S_sup : std_logic_vector(5 downto 0) := "111101";
constant c_A24_S : std_logic_vector(5 downto 0) := "111001";
......@@ -164,7 +165,7 @@ package vme64x_pack is
FUNC_XAMCAP => (add => 16#088#, len => 256),
FUNC_ADEM => (add => 16#188#, len => 32));
-- Main Finite State machine signals defoult:
-- Main Finite State machine signals default:
-- When the S_FPGA detects the magic sequency, it erases the A_FPGA so
-- I don't need to drive the s_dtackOE, s_dataOE, s_addrOE, s_addrDir, s_dataDir
-- to 'Z' in the default configuration.
......@@ -360,7 +361,6 @@ package vme64x_pack is
VME_ADDR_b_i : in std_logic_vector(31 downto 1);
VME_DATA_b_i : in std_logic_vector(31 downto 0);
VME_AM_i : in std_logic_vector(5 downto 0);
VME_BBSY_n_i : in std_logic;
VME_IACK_n_i : in std_logic;
memAckWB_i : in std_logic;
wbData_i : in std_logic_vector(63 downto 0);
......@@ -412,7 +412,6 @@ package vme64x_pack is
CRAMdata_o : out std_logic_vector(7 downto 0);
CRAMwea_o : out std_logic;
CRaddr_o : out std_logic_vector(11 downto 0);
VME_GA_oversampled_o : out std_logic_vector(5 downto 0);
en_wr_CSR : out std_logic;
CrCsrOffsetAddr : out std_logic_vector(18 downto 0);
CSRData_o : out std_logic_vector(7 downto 0);
......@@ -534,7 +533,7 @@ package vme64x_pack is
Ader7 : out std_logic_vector(31 downto 0);
ModuleEnable : out std_logic;
Sw_Reset : out std_logic;
W32 : out std_logic;
W32 : out std_logic;
numBytes : in std_logic_vector(12 downto 0);
transfTime : in std_logic_vector(39 downto 0);
MBLT_Endian_o : out std_logic_vector(2 downto 0);
......@@ -546,37 +545,37 @@ package vme64x_pack is
COMPONENT VME_Am_Match
PORT(
clk_i : in std_logic;
s_reset : in std_logic;
s_mainFSMreset : in std_logic;
Ader0 : in std_logic_vector(31 downto 0);
Ader1 : in std_logic_vector(31 downto 0);
Ader2 : in std_logic_vector(31 downto 0);
Ader3 : in std_logic_vector(31 downto 0);
Ader4 : in std_logic_vector(31 downto 0);
Ader5 : in std_logic_vector(31 downto 0);
Ader6 : in std_logic_vector(31 downto 0);
Ader7 : in std_logic_vector(31 downto 0);
AmCap0 : in std_logic_vector(63 downto 0);
AmCap1 : in std_logic_vector(63 downto 0);
AmCap2 : in std_logic_vector(63 downto 0);
AmCap3 : in std_logic_vector(63 downto 0);
AmCap4 : in std_logic_vector(63 downto 0);
AmCap5 : in std_logic_vector(63 downto 0);
AmCap6 : in std_logic_vector(63 downto 0);
AmCap7 : in std_logic_vector(63 downto 0);
XAmCap0 : in std_logic_vector(255 downto 0);
XAmCap1 : in std_logic_vector(255 downto 0);
XAmCap2 : in std_logic_vector(255 downto 0);
XAmCap3 : in std_logic_vector(255 downto 0);
XAmCap4 : in std_logic_vector(255 downto 0);
XAmCap5 : in std_logic_vector(255 downto 0);
XAmCap6 : in std_logic_vector(255 downto 0);
XAmCap7 : in std_logic_vector(255 downto 0);
Am : in std_logic_vector(5 downto 0);
XAm : in std_logic_vector(7 downto 0);
DFS_i : in std_logic_vector(7 downto 0);
s_decode : in std_logic;
clk_i : in std_logic;
s_reset : in std_logic;
s_mainFSMreset : in std_logic;
Ader0 : in std_logic_vector(31 downto 0);
Ader1 : in std_logic_vector(31 downto 0);
Ader2 : in std_logic_vector(31 downto 0);
Ader3 : in std_logic_vector(31 downto 0);
Ader4 : in std_logic_vector(31 downto 0);
Ader5 : in std_logic_vector(31 downto 0);
Ader6 : in std_logic_vector(31 downto 0);
Ader7 : in std_logic_vector(31 downto 0);
AmCap0 : in std_logic_vector(63 downto 0);
AmCap1 : in std_logic_vector(63 downto 0);
AmCap2 : in std_logic_vector(63 downto 0);
AmCap3 : in std_logic_vector(63 downto 0);
AmCap4 : in std_logic_vector(63 downto 0);
AmCap5 : in std_logic_vector(63 downto 0);
AmCap6 : in std_logic_vector(63 downto 0);
AmCap7 : in std_logic_vector(63 downto 0);
XAmCap0 : in std_logic_vector(255 downto 0);
XAmCap1 : in std_logic_vector(255 downto 0);
XAmCap2 : in std_logic_vector(255 downto 0);
XAmCap3 : in std_logic_vector(255 downto 0);
XAmCap4 : in std_logic_vector(255 downto 0);
XAmCap5 : in std_logic_vector(255 downto 0);
XAmCap6 : in std_logic_vector(255 downto 0);
XAmCap7 : in std_logic_vector(255 downto 0);
Am : in std_logic_vector(5 downto 0);
XAm : in std_logic_vector(7 downto 0);
DFS_i : in std_logic_vector(7 downto 0);
s_decode : in std_logic;
AmMatch : out std_logic_vector(7 downto 0)
);
END COMPONENT;
......@@ -728,7 +727,7 @@ package vme64x_pack is
reset : in std_logic;
VME_IACKIN_n_i : in std_logic;
VME_AS_n_i : in std_logic;
VME_AS1_n_i : in std_logic;
VME_AS1_n_i : in std_logic;
VME_DS_n_i : in std_logic_vector(1 downto 0);
VME_LWORD_n_i : in std_logic;
VME_ADDR_123 : in std_logic_vector(2 downto 0);
......@@ -740,7 +739,7 @@ package vme64x_pack is
VME_DTACK_n_o : out std_logic;
VME_DTACK_OE_o : out std_logic;
VME_DATA_o : out std_logic_vector(31 downto 0);
DataDir : out std_logic
VME_DATA_DIR_o : out std_logic
);
END COMPONENT;
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment