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

Subversion Repositories igor

Compare Revisions

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

Rev 1 → Rev 2

/trunk/processor/mc/addr_decoder.vhd
0,0 → 1,50
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
use work.whisk_constants.all;
--use work.leval_package.all;
 
entity addr_decoder is
port(
clk : in std_logic;
leval_addr : in std_logic_vector(ADDR_BITS - 1 downto 0);
avr_irq : out std_logic;
mem_wait : out std_logic;
mem_ce : out std_logic_vector(1 downto 0);
read_s : in std_logic;
write_s : in std_logic);
end entity;
 
-- PERIOD = 32.25 ns
-- MEMORY ACCESS LATENCY = 55 ns
-- WAIT 8 clock cycles
 
architecture rtl of addr_decoder is
signal t_count : integer := 0;
begin
timer : process(clk)
begin
if rising_edge(clk) then
-- increment timer while communicating with memory
if ((leval_addr < X"3FFFF00") and ((write_s or read_s) = '1')) then
if t_count < 8 then
t_count <= t_count + 1;
end if;
else -- reset timer otherwise
t_count <= 0;
end if;
end if;
end process timer;
 
-- set RDY flag low after 8 cycles
mem_wait <= '0' when t_count = 8 else '1';
 
-- set CE flag for memory based on address we're reading
mem_ce <= "10" when ((leval_addr < X"0080000") and ((write_s or read_s) = '1')) else
"01" when ((leval_addr < X"0100000") and ((write_s or read_s) = '1')) else "11";
--mem_ce <= '0' when ((leval_addr < X"3FFFF00") and ((write_s or read_s) = '1')) else '1';
 
-- set IRQ flag for AVR
avr_irq <= '0' when ((leval_addr >= X"3FFFF00") and ((write_s or read_s) = '1')) else '1';
 
end architecture;
/trunk/processor/mc/leval.vhd
0,0 → 1,257
library ieee;
use ieee.std_logic_1164.all;
use work.leval_package.all;
 
entity leval is
port(
rst : in std_logic; -- convert to synchronous
clk : in std_logic;
data_in : in std_logic_vector(BUS_SIZE - 1 downto 0);
data_out : out std_logic_vector(BUS_SIZE - 1 downto 0);
addr_bus : out std_logic_vector(ADDR_SIZE-1 downto 0);
wait_s : in std_logic;
sync : in std_logic;
read : out std_logic;
write : out std_logic;
led : out std_logic_vector(7 downto 0));
-- pc_out : out std_logic_vector(MC_ADDR_SIZE-1 downto 0);
-- state_out : out std_logic_vector(3 downto 0);
-- status_out : out std_logic_vector(STATUS_REG_SIZE-1 downto 0);
-- pc_write_out : out std_logic);
end entity;
 
architecture rtl of leval is
component pc_incer is
port(
clk : in std_logic;
rst : in std_logic;
pause : in std_logic;
offset : in std_logic_vector(MC_ADDR_SIZE - 1 downto 0);
branch : in std_logic;
pc_next : out std_logic_vector(MC_ADDR_SIZE - 1 downto 0) );
end component pc_incer;
component inst_mem is
port (
clk : in std_logic;
addr : in std_logic_vector(MC_ADDR_SIZE - 1 downto 0);
dout : out std_logic_vector(MC_INSTR_SIZE - 1 downto 0);
din : in std_logic_vector(MC_INSTR_SIZE - 1 downto 0);
we : in std_logic);
end component inst_mem;
 
component alu is
port (
in_a : in std_logic_vector(OBJECT_SIZE-1 downto 0);
in_b : in std_logic_vector(OBJECT_SIZE-1 downto 0);
funct : in std_logic_vector(FUNCT_SIZE-1 downto 0);
status : out std_logic_vector(STATUS_REG_SIZE-1 downto 0);
output : out std_logic_vector(OBJECT_SIZE-1 downto 0));
end component alu;
 
component reg_mem is
port (
clk : in std_logic;
we : in std_logic;
a : in std_logic_vector(SCRATCH_ADDR_SIZE - 1 downto 0);
b : in std_logic_vector(SCRATCH_ADDR_SIZE - 1 downto 0);
dia : in std_logic_vector(WORD_SIZE - 1 downto 0);
doa : out std_logic_vector(WORD_SIZE - 1 downto 0);
dob : out std_logic_vector(WORD_SIZE - 1 downto 0));
end component reg_mem;
 
component control is
port(
clk : in std_logic;
rst : in std_logic;
status_in : in std_logic_vector(STATUS_REG_SIZE - 1 downto 0);
data_rdy : in std_logic;
sync : in std_logic;
opcode : in std_logic_vector(OPCODE_SIZE - 1 downto 0);
breakpoint : in std_logic;
debug_en : in std_logic;
break_mask : in std_logic_vector(STATUS_REG_SIZE - 1 downto 0);
break_flags : in std_logic_vector(STATUS_REG_SIZE - 1 downto 0);
indir_reg1 : in std_logic;
indir_reg2 : in std_logic;
write_reg_en : out std_logic;
indir_reg1_sel : out std_logic;
indir_reg2_sel : out std_logic;
alu_func : out std_logic_vector(FUNCT_SIZE-1 downto 0);
alu_op1_sel : out std_logic;
alu_op2_sel : out std_logic;
status_reg_w_en : out std_logic_vector(STATUS_REG_SIZE-1 downto 0);
pc_write_en : out std_logic;
branch_taken : out std_logic;
write : out std_logic;
read : out std_logic;
mem_to_reg_sel : out std_logic;
write_indir_addr_wr_en : out std_logic);
-- state_out : out std_logic_vector(3 downto 0));
end component control;
 
signal instr : std_logic_vector(MC_INSTR_SIZE-1 downto 0);
signal pc_write_en : std_logic;
-- Skratch memory input lines
signal r1_addr : std_logic_vector(SCRATCH_ADDR_SIZE-1 downto 0);
signal r2_addr : std_logic_vector(SCRATCH_ADDR_SIZE-1 downto 0);
signal scratch_we : std_logic; -- Enable register writing
signal wr_value : std_logic_vector(WORD_SIZE-1 downto 0);
 
-- from SCRATCH
signal r1_value : std_logic_vector(WORD_SIZE-1 downto 0);
signal r2_value : std_logic_vector(WORD_SIZE-1 downto 0);
-- to ALU
signal alu_func : std_logic_vector(FUNCT_SIZE-1 downto 0);
signal alu_op1_val : std_logic_vector(WORD_SIZE-1 downto 0);
signal alu_op2_val : std_logic_vector(WORD_SIZE-1 downto 0);
-- from ALU
signal alu_status : std_logic_vector(STATUS_REG_SIZE-1 downto 0);
signal alu_out : std_logic_vector(WORD_SIZE-1 downto 0);
-- to CONTROL
-- from CONTROL
signal alu_op2_sel : std_logic;
signal branch : std_logic;
signal SRWriteEnable : std_logic_vector(STATUS_REG_SIZE-1 downto 0);
signal r1_in_mux, r2_in_mux : std_logic;
signal write_s, read_s : std_logic;
signal mem_to_reg : std_logic;
 
-- instruction
signal opcode : std_logic_vector(OPCODE_SIZE-1 downto 0);
signal db_enable, b_point : std_logic;
signal imm : std_logic_vector(WORD_SIZE-1 downto 0);
signal r1_indir, r2_indir : std_logic; -- Indirection bits (set if indirect)
signal bmask_s, bflags_s : std_logic_vector(7 downto 0);
signal inst_r1_addr : std_logic_vector(SCRATCH_ADDR_SIZE-1 downto 0);--Reg1 addr
signal inst_r2_addr : std_logic_vector(SCRATCH_ADDR_SIZE-1 downto 0);--Reg2 addr
 
-- registers
signal pc : std_logic_vector(MC_ADDR_SIZE-1 downto 0) := (others => '0');
signal reg1 : std_logic_vector(SCRATCH_ADDR_SIZE-1 downto 0) := (others => '0');
signal reg2 : std_logic_vector(SCRATCH_ADDR_SIZE-1 downto 0) := (others => '0');
signal status : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := (others => '0');
signal alu_op1_sel : std_logic;
signal write_indir_addr_wr_en : std_logic;
begin
-- -- DEBUG signals
-- status_out <= status;
-- pc_out <= pc;
-- pc_write_out <= pc_write_en;
led <= pc(7 downto 0);
-- map memory control signals outside
write <= write_s;
read <= read_s;
 
-- MUX for ALU immidiate/r2 value
alu_op1_val <= r2_value when alu_op1_sel = '1' else r1_value;
alu_op2_val <= imm when alu_op2_sel = '1' else r2_value;
-- MUXes for SCRATCH addresses, select either instruction
-- 's addreses or, if we're indirect, the indirect-regs
r1_addr <= reg1 when r1_in_mux = '1' else inst_r1_addr;
r2_addr <= reg2 when r2_in_mux = '1' else inst_r2_addr;
-- set data out
data_out <= r1_value;
-- MUX for result
wr_value <= data_in when mem_to_reg = '1' else alu_out;
-- Address bus
addr_bus <= alu_out(ADDR_SIZE-1 downto 0);
-- Split fetched instruction into sub-signals
opcode <= instr(47 downto 42); --opcode
db_enable <= instr(41); -- debug bit
b_point <= instr(40); -- break point bit
r1_indir <= instr(39); -- reg1 indirection bit
inst_r1_addr <= instr(38 downto 29); --reg1 address
r2_indir <= instr(28); -- reg2 indir bit
inst_r2_addr <= instr(27 downto 18); --reg2 address
imm <= "000000" & sign_extend_18_26(instr(17 downto 0));
-- Branch instruction signals (branch mask and branch flags)
bflags_s <= instr(20 downto 13);
bmask_s <= instr(28 downto 21);
scrmem : reg_mem
port map (
clk => clk,
we => scratch_we,
a => r1_addr,
b => r2_addr,
dia => wr_value,
doa => r1_value,
dob => r2_value);
alu_inst : alu
port map (
in_a => alu_op1_val,
in_b => alu_op2_val,
funct => alu_func,
status => alu_status,
output => alu_out);
 
instrmem : inst_mem
port map (
clk => clk,
addr => pc,
dout => instr,
din => "000000000000000000000000000000000000000000000000",
we => '0');
 
pc_incer_inst : pc_incer
port map (
clk => clk,
rst => rst,
pause => pc_write_en,
offset => alu_out(MC_ADDR_SIZE-1 downto 0),
branch => branch,
pc_next => pc);
control_unit : control
port map (
clk => clk,
rst => rst,
sync => sync,
status_in => status,
data_rdy=> wait_s,
opcode => opcode,
breakpoint=> b_point,
debug_en=> db_enable,
break_mask=> bmask_s,
break_flags=> bflags_s,
indir_reg1=> r1_indir,
indir_reg2=> r2_indir,
write_reg_en=> scratch_we,
alu_op1_sel => alu_op1_sel,
indir_reg1_sel => r1_in_mux,
indir_reg2_sel => r2_in_mux,
alu_func=> alu_func,
alu_op2_sel=> alu_op2_sel,
status_reg_w_en=> SRWriteEnable,
pc_write_en => pc_write_en,
branch_taken => branch,
write => write_s,
read => read_s,
mem_to_reg_sel => mem_to_reg,
write_indir_addr_wr_en => write_indir_addr_wr_en);
-- state_out => state_out);
 
-- update registers on rising clock edge
update_regs : process(clk, rst)
begin
if rising_edge(clk) then
-- update status register with status from alu masked by SRWriteEnable
status <= (status and (not SRWriteEnable)) or (SRWriteEnable and alu_status);
-- update addresses from indirect registers
if write_indir_addr_wr_en = '1' then
reg1 <= r1_value(SCRATCH_ADDR_SIZE - 1 downto 0);
reg2 <= r2_value(SCRATCH_ADDR_SIZE - 1 downto 0);
end if;
end if;
end process update_regs;
end rtl;
/trunk/processor/mc/bidirbus.vhd
0,0 → 1,37
library IEEE;
use ieee.std_logic_1164.all;
use work.leval_package.all;
 
entity bidirbus is
port (
bidir : inout std_logic_vector(WORD_SIZE - 1 downto 0);
oe : in std_logic;
clk : in std_logic;
inp : in std_logic_vector(WORD_SIZE - 1 downto 0);
outp : out std_logic_vector(WORD_SIZE - 1 downto 0)
);
end entity;
 
architecture rtl of bidirbus is
signal a : std_logic_vector(WORD_SIZE - 1 downto 0);
signal b : std_logic_vector(WORD_SIZE - 1 downto 0);
begin
busback : process(clk)
begin
if rising_edge(clk) then
a <= inp;
outp <= b;
end if;
end process;
process(oe, bidir, a)
begin
if oe = '0' then -- write operation
bidir <= (others => 'Z');
b <= bidir;
else
bidir <= a;
b <= bidir;
end if;
end process;
end architecture;
/trunk/processor/mc/fpu_mul.vhd
0,0 → 1,128
--------------------------------------------------------------------------------
-- This file is owned and controlled by Xilinx and must be used --
-- solely for design, simulation, implementation and creation of --
-- design files limited to Xilinx devices or technologies. Use --
-- with non-Xilinx devices or technologies is expressly prohibited --
-- and immediately terminates your license. --
-- --
-- XILINX IS PROVIDING THIS DESIGN, CODE, OR INFORMATION "AS IS" --
-- SOLELY FOR USE IN DEVELOPING PROGRAMS AND SOLUTIONS FOR --
-- XILINX DEVICES. BY PROVIDING THIS DESIGN, CODE, OR INFORMATION --
-- AS ONE POSSIBLE IMPLEMENTATION OF THIS FEATURE, APPLICATION --
-- OR STANDARD, XILINX IS MAKING NO REPRESENTATION THAT THIS --
-- IMPLEMENTATION IS FREE FROM ANY CLAIMS OF INFRINGEMENT, --
-- AND YOU ARE RESPONSIBLE FOR OBTAINING ANY RIGHTS YOU MAY REQUIRE --
-- FOR YOUR IMPLEMENTATION. XILINX EXPRESSLY DISCLAIMS ANY --
-- WARRANTY WHATSOEVER WITH RESPECT TO THE ADEQUACY OF THE --
-- IMPLEMENTATION, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OR --
-- REPRESENTATIONS THAT THIS IMPLEMENTATION IS FREE FROM CLAIMS OF --
-- INFRINGEMENT, IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS --
-- FOR A PARTICULAR PURPOSE. --
-- --
-- Xilinx products are not intended for use in life support --
-- appliances, devices, or systems. Use in such applications are --
-- expressly prohibited. --
-- --
-- (c) Copyright 1995-2007 Xilinx, Inc. --
-- All rights reserved. --
--------------------------------------------------------------------------------
-- You must compile the wrapper file fpu_mul.vhd when simulating
-- the core, fpu_mul. When compiling the wrapper file, be sure to
-- reference the XilinxCoreLib VHDL simulation library. For detailed
-- instructions, please refer to the "CORE Generator Help".
 
-- The synthesis directives "translate_off/translate_on" specified
-- below are supported by Xilinx, Mentor Graphics and Synplicity
-- synthesis tools. Ensure they are correct for your synthesis tool(s).
 
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- synthesis translate_off
Library XilinxCoreLib;
-- synthesis translate_on
ENTITY fpu_mul IS
port (
a: IN std_logic_VECTOR(25 downto 0);
b: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
underflow: OUT std_logic;
overflow: OUT std_logic;
invalid_op: OUT std_logic);
END fpu_mul;
 
ARCHITECTURE fpu_mul_a OF fpu_mul IS
-- synthesis translate_off
component wrapped_fpu_mul
port (
a: IN std_logic_VECTOR(25 downto 0);
b: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
underflow: OUT std_logic;
overflow: OUT std_logic;
invalid_op: OUT std_logic);
end component;
 
-- Configuration specification
for all : wrapped_fpu_mul use entity XilinxCoreLib.floating_point_v3_0(behavioral)
generic map(
c_has_b_nd => 0,
c_speed => 2,
c_has_sclr => 0,
c_has_a_rfd => 0,
c_b_fraction_width => 20,
c_has_operation_nd => 0,
c_family => "spartan3",
c_has_exception => 0,
c_a_fraction_width => 20,
c_has_flt_to_fix => 0,
c_has_flt_to_flt => 0,
c_has_fix_to_flt => 0,
c_has_invalid_op => 1,
c_latency => 0,
c_has_divide_by_zero => 0,
c_has_overflow => 1,
c_mult_usage => 0,
c_has_rdy => 0,
c_result_fraction_width => 20,
c_has_divide => 0,
c_has_inexact => 0,
c_has_underflow => 1,
c_has_sqrt => 0,
c_has_add => 0,
c_has_status => 0,
c_has_a_negate => 0,
c_optimization => 1,
c_has_a_nd => 0,
c_has_aclr => 0,
c_has_b_negate => 0,
c_has_subtract => 0,
c_compare_operation => 8,
c_rate => 1,
c_has_compare => 0,
c_has_operation_rfd => 0,
c_has_b_rfd => 0,
c_result_width => 26,
c_b_width => 26,
c_status_early => 0,
c_a_width => 26,
c_has_cts => 0,
c_has_ce => 0,
c_has_multiply => 1);
-- synthesis translate_on
BEGIN
-- synthesis translate_off
U0 : wrapped_fpu_mul
port map (
a => a,
b => b,
clk => clk,
result => result,
underflow => underflow,
overflow => overflow,
invalid_op => invalid_op);
-- synthesis translate_on
 
END fpu_mul_a;
 
/trunk/processor/mc/reg_mem.vhd
0,0 → 1,59
library ieee;
 
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
use work.leval_package.all;
use ieee.numeric_std.all;
use std.textio.all;
 
entity reg_mem is
port (
clk : in std_logic;
we : in std_logic;
a : in std_logic_vector(SCRATCH_ADDR_SIZE - 1 downto 0);
b : in std_logic_vector(SCRATCH_ADDR_SIZE - 1 downto 0);
dia : in std_logic_vector(WORD_SIZE - 1 downto 0);
doa : out std_logic_vector(WORD_SIZE - 1 downto 0);
dob : out std_logic_vector(WORD_SIZE - 1 downto 0)
);
end entity reg_mem;
 
architecture behav of reg_mem is
type ram_type is array (0 to SCRATCH_SIZE - 1) of bit_vector(WORD_SIZE - 1
downto 0);
signal read_a : std_logic_vector(SCRATCH_ADDR_SIZE - 1 downto 0);
signal read_b : std_logic_vector(SCRATCH_ADDR_SIZE - 1 downto 0);
impure function init_ram(filename : in string) return ram_type is
file ramfile : text is in filename;
variable li : line;
variable RAM : ram_type;
begin
for i in ram_type'range loop
readline(ramfile, li);
read(li, RAM(i));
end loop;
return RAM;
end function;
signal RAM : ram_type := init_ram("testing/mc10/regfile.foo");
begin
process(clk)
begin
if rising_edge(clk) then
if (we = '1') then
RAM(to_integer(unsigned(a))) <= to_bitvector(dia);
end if;
read_a <= a;
read_b <= b;
end if;
end process;
doa <= to_stdlogicvector(RAM(to_integer(unsigned(read_a))));
dob <= to_stdlogicvector(RAM(to_integer(unsigned(read_b))));
end behav;
 
 
 
/trunk/processor/mc/divider_tb.vhd
0,0 → 1,107
-- ==============================================================================
-- Generic signed/unsigned restoring divider Testbench
--
-- This library 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 library 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. See http://www.gnu.org/copyleft/lesser.txt
--
-- ------------------------------------------------------------------------------
-- Version Author Date Changes
-- 0.1 Hans Tiggeler 07/18/02 Tested on Modelsim SE 5.6
-- ==============================================================================
 
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_arith.all;
use ieee.std_logic_unsigned.all;
 
entity divider_tb is
generic (width_divider : integer := 8;
width_divisor : integer := 8);
end entity divider_tb;
 
architecture rtl of divider_tb is
 
component divider is
generic (width_divid : integer := 4;
width_divis : integer := 4);
port ( dividend : in std_logic_vector (width_divid-1 downto 0);
divisor : in std_logic_vector (width_divis-1 downto 0);
quotient : out std_logic_vector (width_divid-1 downto 0);
remainder : out std_logic_vector (width_divis-1 downto 0);
twocomp : in std_logic); -- '1'=2's complement, '0'=unsigned
end component divider;
 
 
signal dividend_s : std_logic_vector (width_divider-1 downto 0);
signal divisor_s : std_logic_vector (width_divisor-1 downto 0);
signal quotient_s : std_logic_vector (width_divider-1 downto 0);
signal remainder_s : std_logic_vector (width_divisor-1 downto 0);
signal twocomp_s : std_logic;
 
signal q_s : integer;
signal r_s : integer;
 
 
begin
dut : divider
generic map (width_divid => width_divider,
width_divis => width_divisor)
port map (dividend => dividend_s,
divisor => divisor_s,
quotient => quotient_s,
remainder => remainder_s,
twocomp => twocomp_s);
 
process
begin
twocomp_s <= '0';
dividend_s <= (others => '0');
divisor_s <= (others => '1');
wait for 20 ns;
 
for twocomp_v in 0 to 1 loop
if twocomp_v=0 then
twocomp_s<= '0';report "**** Testing Unsigned Divider ****";
else
twocomp_s<= '1';report "**** Testing Signed Divider ****";
end if;
for i in 0 to (2 ** width_divider - 1) loop
for j in 1 to (2 ** width_divisor - 1) loop
dividend_s <= conv_std_logic_vector(i,width_divider);
divisor_s <= conv_std_logic_vector(j,width_divisor);
 
wait for 10 ns;
if twocomp_s='1' then
q_s <=conv_integer(signed(dividend_s)) / conv_integer(signed(divisor_s));
r_s <=conv_integer(signed(dividend_s)) rem conv_integer(signed(divisor_s));
wait for 1 ns;
if (q_s <= (2**(width_divider-1)-1)) then -- check for overflow -2^(n-1) .. 2^(n-1)-1
assert (q_s=conv_integer(signed(quotient_s))) report "Signed quotient failure" severity note;
assert (r_s=conv_integer(signed(remainder_s))) report "Signed remainder failure" severity note;
else
report "Overflow, Signed divide skipped";
end if;
else
q_s <=conv_integer(dividend_s) / conv_integer(divisor_s);
r_s <=conv_integer(dividend_s) rem conv_integer(divisor_s);
wait for 1 ns;
assert (q_s=conv_integer(quotient_s)) report "Unsigned quotient failure" severity note;
assert (r_s=conv_integer(remainder_s)) report "Unsigned remainder failure" severity note;
end if;
wait for 10 ns;
end loop;
end loop;
end loop;
assert (false) report " end of sim" severity failure;
end process;
 
 
end architecture rtl;
/trunk/processor/mc/inst_mem.vhd
0,0 → 1,56
--------------------------------------------------------------------------------
-- Desc: Asynch ROM
-- Author: Odd Rune
--------------------------------------------------------------------------------
 
library ieee;
 
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
use work.leval_package.all;
use std.textio.all;
use ieee.numeric_std.all;
 
entity inst_mem is
generic ( memsize, addrbits, databits : integer;
initfile : string);
port (
clk : in std_logic;
addr : in std_logic_vector(addrbits - 1 downto 0);
dout : out std_logic_vector(databits - 1 downto 0);
din : in std_logic_vector(databits - 1 downto 0);
we : in std_logic
);
end entity inst_mem;
 
architecture behav of inst_mem is
type rom_type is array(0 to memsize) of bit_vector(databits - 1
downto 0);
 
 
impure function init_rom(filename : in string) return rom_type is
file romfile : text is in filename;
variable li : line;
variable ROM : rom_type;
begin
for i in rom_type'range loop
readline(romfile, li);
read(li, ROM(i));
end loop;
return ROM;
end function;
 
signal ROM : rom_type := init_rom(initfile);
signal read_reg : std_logic_vector(addrbits - 1 downto 0);
begin
process(clk,addr)
begin
if rising_edge(clk) then
if we = '1' then
ROM(to_integer(unsigned(addr))) <= to_bitvector(din);
end if;
read_reg <= addr;
end if;
end process;
dout <= to_stdlogicvector(ROM(to_integer(unsigned(read_reg))));
end architecture behav;
/trunk/processor/mc/memtest.vhd
0,0 → 1,98
library ieee;
use ieee.std_logic_1164.all;
use work.leval_package.all;
 
 
entity memtest is
port(
clk : in std_logic;
rst : in std_logic;
pause : in std_logic;
fpga_data : inout std_logic_vector(WORD_SIZE - 1 downto 0);
fpga_addr : out std_logic_vector(ADDR_SIZE - 1 downto 0);
avr_irq : out std_logic;
wait_f : in std_logic;
read : out std_logic;
write : out std_logic;
led : out std_logic_vector(7 downto 0));
end entity;
 
architecture rtl of memtest is
-- Components:
component leval is
port (
pause : in std_logic;
rst : in std_logic;
clk : in std_logic;
data_bus : inout std_logic_vector(BUS_SIZE-1 downto 0);
addr_bus : out std_logic_vector(ADDR_SIZE-1 downto 0);
wait_s : in std_logic;
read : out std_logic;
write : out std_logic;
led : out std_logic_vector(7 downto 0));
end component;
component addr_decoder is
port (
leval_addr : in std_logic_vector(ADDR_SIZE - 1 downto 0);
avr_irq : out std_logic;
wt : out std_logic
);
end component;
 
component ext_mem is
port(
we : in std_logic;
re : in std_logic;
a : in std_logic_vector(4 downto 0);
d : inout std_logic_vector(WORD_SIZE - 1 downto 0)
);
end component;
 
-- Signals:
signal addr_s : std_logic_vector(ADDR_SIZE - 1 downto 0);
signal data_s : std_logic_vector(WORD_SIZE - 1 downto 0);
signal data_out_s : std_logic_vector(WORD_SIZE - 1 downto 0);
signal data_in_s : std_logic_vector(WORD_SIZE - 1 downto 0);
signal write_s : std_logic;
signal read_s : std_logic;
signal wait_s : std_logic;
signal flash_ce0 : std_logic;
signal flash_ce1 : std_logic := '0';
 
begin
 
LEVAL_CPU : leval
port map(
pause => '0', -- TODO: set to pause
clk => clk,
rst => rst,
data_bus => data_s,
addr_bus => addr_s,
wait_s => wait_s,
read => read_s,
write => write_s,
led => led
);
 
dmem : ext_mem
port map (
we => write_s,
re => read_s,
a => addr_s(4 downto 0),
d => data_s
);
 
ADDR_DEC : addr_decoder
port map (
leval_addr => addr_s,
avr_irq => avr_irq,
wt => wait_s
);
 
 
end architecture rtl;
 
 
/trunk/processor/mc/toplevel_tb.vhd
0,0 → 1,120
library ieee;
use ieee.std_logic_1164.all;
use work.leval_package.all;
use work.avremu_package.all;
 
entity toplevel_tb is
end entity;
 
architecture rtl of toplevel_tb is
 
-- COMPONENTS FOR THIS TEST
 
component avremu is
port (
data : inout databus_t; -- Data bus
addr : in addr_t; -- Address bus
intr : in std_logic; -- Interrupt line
read : in std_logic; -- Read signal
write : in std_logic; -- Write signal
rdy : out std_logic); -- Ready flag
end component avremu;
 
component ext_mem is
port(
we : in std_logic;
re : in std_logic;
a : in std_logic_vector(ADDR_SIZE - 1 downto 0);
d : inout std_logic_vector(WORD_SIZE - 1 downto 0);
ce : in std_logic
);
end component;
 
component toplevel is
port(
clk : in std_logic;
rst_low : in std_logic;
fpga_data : inout std_logic_vector(WORD_SIZE - 1 downto 0);
fpga_addr : out std_logic_vector(ADDR_SIZE - 1 downto 0);
avr_irq : out std_logic;
avr_rdy : in std_logic;
sync : in std_logic;
read : out std_logic;
write : out std_logic;
mem_ce : out std_logic;
led : out std_logic_vector(7 downto 0);
err : in std_logic_vector(1 downto 0));
end component;
 
 
signal dut_clk : std_logic := '1';
signal dut_rst : std_logic := '1';
signal iobus : std_logic_vector(WORD_SIZE - 1 downto 0);
signal ioaddr : std_logic_vector(ADDR_SIZE - 1 downto 0);
signal interrupt : std_logic;
signal rdy : std_logic; -- FROM AVR
signal sync : std_logic := '1'; -- FROM AVR
signal read : std_logic; -- TO MEM/AVR
signal write : std_logic; -- To mem/avr
signal mem_ce : std_logic; -- To mem
signal leds : std_logic_vector(7 downto 0);
 
 
-- Architecture begin
begin
 
-----------------------------------------------------------------------------
-- Design under test
-----------------------------------------------------------------------------
dut : toplevel
port map (
clk => dut_clk,
rst_low => dut_rst,
fpga_data => iobus,
fpga_addr => ioaddr,
avr_irq => interrupt,
avr_rdy => rdy,
sync => sync,
read => read,
write => write,
mem_ce => mem_ce,
led => leds,
err => "00"
);
 
-----------------------------------------------------------------------------
-- Support units
-----------------------------------------------------------------------------
 
-- The AVR
-----------------------------------------------------------------------------
iounit : avremu
port map (
data => iobus,
addr => ioaddr(7 downto 0),
intr => interrupt,
read => read,
write => write,
rdy => rdy
);
 
-- External memory
-----------------------------------------------------------------------------
memory : ext_mem
port map(
we => write,
re => read,
a => ioaddr,
d => iobus,
ce => mem_ce
);
 
-- Clock generator
-----------------------------------------------------------------------------
clock_gen : process(dut_clk)
begin
if dut_clk = '1' then
dut_clk <= '0' after 5 ns, '1' after 10 ns;
end if;
end process;
end architecture;
/trunk/processor/mc/control.vhd
0,0 → 1,384
library ieee;
use ieee.std_logic_1164.all;
use ieee.numeric_std.all;
use ieee.std_logic_signed.all;
use work.leval_package.all;
 
entity control is
port (
clk : in std_logic;
rst : in std_logic;
-- status register
status_in : in std_logic_vector(STATUS_REG_SIZE-1 downto 0);
data_rdy : in std_logic; -- data ready on data bus signal
sync : in std_logic; -- AVR ready signal
-- instruction signals
opcode : in std_logic_vector(OPCODE_SIZE-1 downto 0);
breakpoint : in std_logic;
debug_en : in std_logic;
break_mask : in std_logic_vector(STATUS_REG_SIZE-1 downto 0);
break_flags : in std_logic_vector(STATUS_REG_SIZE-1 downto 0);
indir_reg1 : in std_logic;
indir_reg2 : in std_logic;
-- scrath control signals
write_reg_en : out std_logic; -- enables writing of register file
-- use address from indirect register-registers
indir_reg1_sel : out std_logic;
indir_reg2_sel : out std_logic;
-- ALU
alu_func : out std_logic_vector(FUNCT_SIZE-1 downto 0);
alu_op1_sel : out std_logic; -- use r2 as first operand in ALU
alu_op2_sel : out std_logic; -- when high use immidiate as second argument
-- status register control line
status_reg_w_en : out std_logic_vector(STATUS_REG_SIZE-1 downto 0);
-- PC control
pc_write_en : out std_logic; -- increment program counter
branch_taken : out std_logic; -- take branch
-- memory control signals
write : out std_logic; -- write-signal
read : out std_logic; -- read-signal
-- datapaths
mem_to_reg_sel : out std_logic; -- use databus instead of ALU result
write_indir_addr_wr_en : out std_logic; -- udpate registers with indirect addresses
state_out : out std_logic_vector(3 downto 0)); -- DEBUG SIGNAL
end entity;
 
architecture rtl of control is
-- States
type state_type is (st0_init,st1_fetch,st2_regfetch,st3_load_indir_regs,st4_load_indir_data,
st5_execute,st6_wait_data,st7_wait_done,st8_io_done,st9_halt);
signal state : state_type := st0_init;
signal jump : boolean;
signal stored : boolean := true; -- this is used only on LOAD operations to know if we
-- wrote result into register. So we can use the same
-- register for address and result
begin
 
-- DECODE AND OUTPUT
OUTPUT_DECODE: process (state,opcode,indir_reg1,indir_reg2,jump,stored,data_rdy)
begin
-- default values
write_reg_en <= '0'; -- disable register writing
mem_to_reg_sel <= '0'; -- use ALU's result
alu_op1_sel <= '0'; -- don't write result
indir_reg1_sel <= '0'; -- don't use indir-regs default
indir_reg2_sel <= '0';
alu_func <= (others => '0');
alu_op2_sel <= '0'; -- don't use immidiate default
status_reg_w_en <= (others => '0'); -- don't write status register
branch_taken <= '0'; -- don't branch
write <= '0';
read <= '0';
pc_write_en <= '0'; -- don't change PC
write_indir_addr_wr_en <= '0';
stored <= stored;
case (state) is
when st0_init =>
state_out <= X"0";
when st1_fetch =>
state_out <= X"1";
when st2_regfetch =>
-- do nothing, we're waiting for the registers to load
state_out <= X"2";
when st3_load_indir_regs =>
-- load the indirection registers with the current register-out values
state_out <= X"3";
write_indir_addr_wr_en <= '1';
-- load indirect value
if indir_reg1 = '1' then
indir_reg1_sel <= '1';
end if;
if indir_reg2 = '1' then
indir_reg2_sel <= '1';
end if;
when st4_load_indir_data =>
-- do nothing
state_out <= X"4";
if indir_reg1 = '1' then
indir_reg1_sel <= '1';
end if;
if indir_reg2 = '1' then
indir_reg2_sel <= '1';
end if;
when st5_execute =>
-- main execution state, sets signals according to input and state
state_out <= X"5";
status_reg_w_en <= (others => '1'); -- update status register on each operation
-- if we have load or store, we should wait with updating of PC
if (opcode = LOAD or opcode = STORE) then
pc_write_en <= '0';
else
pc_write_en <= '1';
end if;
-- indirect addressing
if indir_reg1 = '1' then
indir_reg1_sel <= '1';
end if;
if indir_reg2 = '1' then
indir_reg2_sel <= '1';
end if;
case opcode is
-- Arithmetical / Logic functions
when ADD =>
alu_func <= ALU_ADD;
write_reg_en <= '1';
when SUBB =>
alu_func <= ALU_SUB;
write_reg_en <= '1';
when MUL =>
alu_func <= ALU_MUL;
write_reg_en <= '1';
-- -- NOT IMPLEMENTED
-- when DIV =>
-- alu_func <= ALU_DIV;
-- write_reg_en <= '1';
-- when MODULO =>
-- alu_func <= ALU_MOD;
-- write_reg_en <= '1';
when LAND =>
alu_func <= ALU_AND;
write_reg_en <= '1';
when LOR =>
alu_func <= ALU_OR;
write_reg_en <= '1';
when LXOR =>
alu_func <= ALU_XOR;
write_reg_en <= '1';
when LOAD =>
mem_to_reg_sel <= '1'; -- use data bus
alu_func <= ALU_ADD;
alu_op2_sel <= '1';
alu_op1_sel <= '1';
stored <= false;
when STORE =>
alu_func <= ALU_ADD;
alu_op2_sel <= '1';
alu_op1_sel <= '1';
stored <= true;
when BIDX =>
if jump then
alu_func <= ALU_ADD;
branch_taken <= '1';
alu_op2_sel <= '1';
end if;
when GET_TYPE =>
alu_func <= ALU_GET_TYPE;
write_reg_en <= '1';
when SET_TYPE =>
alu_func <= ALU_SET_TYPE;
write_reg_en <= '1';
when SET_TYPE_IMM =>
alu_func <= ALU_SET_TYPE;
write_reg_en <= '1';
alu_op2_sel <= '1';
when SET_DATUM =>
alu_func <= ALU_SET_DATUM;
write_reg_en <= '1';
when SET_DATUM_IMM =>
alu_func <= ALU_SET_DATUM;
write_reg_en <= '1';
alu_op2_sel <= '1';
when SET_GC =>
alu_func <= ALU_SET_GC;
write_reg_en <= '1';
when SET_GC_IMM =>
alu_func <= ALU_SET_GC;
write_reg_en <= '1';
alu_op2_sel <= '1';
when CPY =>
alu_func <= ALU_CPY;
write_reg_en <= '1';
when CMP_TYPE =>
alu_func <= ALU_CMP_TYPE;
when CMP_TYPE_IMM =>
alu_func <= ALU_CMP_TYPE_IMM;
alu_op2_sel <= '1';
when CMP_DATUM =>
alu_func <= ALU_CMP_DATUM;
when CMP_DATUM_IMM =>
alu_func <= ALU_CMP_DATUM;
alu_op2_sel <= '1';
when CMP_GC =>
alu_func <= ALU_CMP_GC;
when CMP_GC_IMM =>
alu_func <= ALU_CMP_GC_IMM;
alu_op2_sel <= '1';
when CMP =>
alu_func <= ALU_CMP;
when SHIFT_L =>
alu_func <= ALU_SL;
write_reg_en <= '1';
when SHIFT_R =>
alu_func <= ALU_SR;
write_reg_en <= '1';
when SETLED =>
alu_func <= ALU_SETLED;
when others =>
-- unknown opcode, do nothing
alu_func <= ALU_PASS;
end case;
when st6_wait_data =>
-- HOLD load or store signals
state_out <= X"6";
if indir_reg1 = '1' then
indir_reg1_sel <= '1';
end if;
if indir_reg2 = '1' then
indir_reg2_sel <= '1';
end if;
alu_op2_sel <= '1'; -- use immediate value
alu_func <= ALU_ADD; --calculate load/store address
alu_op1_sel <= '1'; -- use R2 with immidiate in ALU
if (opcode = LOAD) then
mem_to_reg_sel <= '1'; -- load data from bus
read <= '1'; -- set read control signal
if data_rdy = '0' and stored = false then -- if data is not stored, but ready on the bus
write_reg_en <= '1'; -- enable writing of the register
stored <= true; -- remember that we stored data
end if;
else -- means STORE
stored <= true; -- we don't need to write anything in register memory
write <= '1'; -- set write control signal
end if;
when st7_wait_done =>
-- remove read/write signal and wait till distanation unit clears ready control line
state_out <= X"7";
-- hold address values just to be sure
if indir_reg1 = '1' then
indir_reg1_sel <= '1';
end if;
if indir_reg2 = '1' then
indir_reg2_sel <= '1';
end if;
alu_op2_sel <= '1';
alu_func <= ALU_ADD;
alu_op1_sel <= '1';
when st8_io_done =>
-- one cycle to update PC
state_out <= X"8";
pc_write_en <= '1';
when st9_halt =>
-- HALT state (we can't get out of here unless reset)
state_out <= X"9";
when others =>
-- unknown state
state_out <= X"F";
end case;
end process;
-- NEXT STATE FUNCTION
NEXT_STATE_DECODE: process(clk)
begin
if rising_edge(clk) then
if rst = '1' then
state <= st0_init;
end if;
case (state) is
when st0_init =>
if sync = '1' then
state <= st1_fetch;
end if;
when st1_fetch =>
state <= st2_regfetch;
when st2_regfetch =>
if indir_reg1 = '1' or indir_reg2 = '1' then
-- if we need to load indirect registers
state <= st3_load_indir_regs;
else
state <= st5_execute;
end if;
when st3_load_indir_regs =>
state <= st4_load_indir_data;
when st4_load_indir_data =>
state <= st5_execute;
when st5_execute =>
-- HALT conditions
if breakpoint = '1' or debug_en = '1' or opcode = HALT then
state <= st9_halt;
-- LOAD/STORE
elsif opcode=LOAD or opcode = STORE then
state <= st6_wait_data;
-- otherwise go to fetch next instruction
else
state <= st1_fetch;
end if;
when st6_wait_data =>
if data_rdy = '0' and stored = true then
state <= st7_wait_done;
end if;
when st7_wait_done =>
if data_rdy = '1' then
state <= st8_io_done;
end if;
when st8_io_done =>
state <= st1_fetch;
when st9_halt =>
-- We halt, program is over.
end case;
end if;
end process;
update_branch_evaluator : process(clk)
begin
if rising_edge(clk) then
-- compare status register with branch flags, filtered by branch mask
if (status_in and break_mask) = (break_flags and break_mask) then
jump <= true;
else
jump <= false;
end if;
end if;
end process;
end rtl;
/trunk/processor/mc/external_mem.vhd
0,0 → 1,37
--------------------------------------------------------------------------------
-- This models the external memory
--------------------------------------------------------------------------------
 
library ieee;
use ieee.std_logic_1164.all;
use work.leval_package.all;
use ieee.numeric_std.all;
 
entity ext_mem is
port(
we : in std_logic;
re : in std_logic;
a : in std_logic_vector(ADDR_SIZE - 1 downto 0);
d : inout std_logic_vector(WORD_SIZE - 1 downto 0);
ce : in std_logic
);
end entity;
 
architecture behav of ext_mem is
 
type ram_type is array (0 to 2**10) of std_logic_vector(WORD_SIZE - 1 downto 0);
signal RAM : ram_type := (others => (others => '0'));
begin
process(a,we,re,d, ce)
begin
if to_integer(unsigned(a)) < 2**10 then
if we = '1' and re= '0' then
RAM(to_integer(unsigned(a))) <= d;
elsif re = '1' and we = '0' then
d <= RAM(to_integer(unsigned(a)));
else
d <= (others => 'Z');
end if;
end if;
end process;
end architecture;
/trunk/processor/mc/int_to_fp.vhd
0,0 → 1,116
--------------------------------------------------------------------------------
-- This file is owned and controlled by Xilinx and must be used --
-- solely for design, simulation, implementation and creation of --
-- design files limited to Xilinx devices or technologies. Use --
-- with non-Xilinx devices or technologies is expressly prohibited --
-- and immediately terminates your license. --
-- --
-- XILINX IS PROVIDING THIS DESIGN, CODE, OR INFORMATION "AS IS" --
-- SOLELY FOR USE IN DEVELOPING PROGRAMS AND SOLUTIONS FOR --
-- XILINX DEVICES. BY PROVIDING THIS DESIGN, CODE, OR INFORMATION --
-- AS ONE POSSIBLE IMPLEMENTATION OF THIS FEATURE, APPLICATION --
-- OR STANDARD, XILINX IS MAKING NO REPRESENTATION THAT THIS --
-- IMPLEMENTATION IS FREE FROM ANY CLAIMS OF INFRINGEMENT, --
-- AND YOU ARE RESPONSIBLE FOR OBTAINING ANY RIGHTS YOU MAY REQUIRE --
-- FOR YOUR IMPLEMENTATION. XILINX EXPRESSLY DISCLAIMS ANY --
-- WARRANTY WHATSOEVER WITH RESPECT TO THE ADEQUACY OF THE --
-- IMPLEMENTATION, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OR --
-- REPRESENTATIONS THAT THIS IMPLEMENTATION IS FREE FROM CLAIMS OF --
-- INFRINGEMENT, IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS --
-- FOR A PARTICULAR PURPOSE. --
-- --
-- Xilinx products are not intended for use in life support --
-- appliances, devices, or systems. Use in such applications are --
-- expressly prohibited. --
-- --
-- (c) Copyright 1995-2007 Xilinx, Inc. --
-- All rights reserved. --
--------------------------------------------------------------------------------
-- You must compile the wrapper file int_to_fp.vhd when simulating
-- the core, int_to_fp. When compiling the wrapper file, be sure to
-- reference the XilinxCoreLib VHDL simulation library. For detailed
-- instructions, please refer to the "CORE Generator Help".
 
-- The synthesis directives "translate_off/translate_on" specified
-- below are supported by Xilinx, Mentor Graphics and Synplicity
-- synthesis tools. Ensure they are correct for your synthesis tool(s).
 
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- synthesis translate_off
Library XilinxCoreLib;
-- synthesis translate_on
ENTITY int_to_fp IS
port (
a: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0));
END int_to_fp;
 
ARCHITECTURE int_to_fp_a OF int_to_fp IS
-- synthesis translate_off
component wrapped_int_to_fp
port (
a: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0));
end component;
 
-- Configuration specification
for all : wrapped_int_to_fp use entity XilinxCoreLib.floating_point_v3_0(behavioral)
generic map(
c_has_b_nd => 0,
c_speed => 2,
c_has_sclr => 0,
c_has_a_rfd => 0,
c_b_fraction_width => 0,
c_has_operation_nd => 0,
c_family => "spartan3",
c_has_exception => 0,
c_a_fraction_width => 0,
c_has_flt_to_fix => 0,
c_has_flt_to_flt => 0,
c_has_fix_to_flt => 1,
c_has_invalid_op => 0,
c_latency => 0,
c_has_divide_by_zero => 0,
c_has_overflow => 0,
c_mult_usage => 0,
c_has_rdy => 0,
c_result_fraction_width => 20,
c_has_divide => 0,
c_has_inexact => 0,
c_has_underflow => 0,
c_has_sqrt => 0,
c_has_add => 0,
c_has_status => 0,
c_has_a_negate => 0,
c_optimization => 1,
c_has_a_nd => 0,
c_has_aclr => 0,
c_has_b_negate => 0,
c_has_subtract => 0,
c_compare_operation => 8,
c_rate => 1,
c_has_compare => 0,
c_has_operation_rfd => 0,
c_has_b_rfd => 0,
c_result_width => 26,
c_b_width => 26,
c_status_early => 0,
c_a_width => 26,
c_has_cts => 0,
c_has_ce => 0,
c_has_multiply => 0);
-- synthesis translate_on
BEGIN
-- synthesis translate_off
U0 : wrapped_int_to_fp
port map (
a => a,
clk => clk,
result => result);
-- synthesis translate_on
 
END int_to_fp_a;
 
/trunk/processor/mc/fp_to_int.vhd
0,0 → 1,122
--------------------------------------------------------------------------------
-- This file is owned and controlled by Xilinx and must be used --
-- solely for design, simulation, implementation and creation of --
-- design files limited to Xilinx devices or technologies. Use --
-- with non-Xilinx devices or technologies is expressly prohibited --
-- and immediately terminates your license. --
-- --
-- XILINX IS PROVIDING THIS DESIGN, CODE, OR INFORMATION "AS IS" --
-- SOLELY FOR USE IN DEVELOPING PROGRAMS AND SOLUTIONS FOR --
-- XILINX DEVICES. BY PROVIDING THIS DESIGN, CODE, OR INFORMATION --
-- AS ONE POSSIBLE IMPLEMENTATION OF THIS FEATURE, APPLICATION --
-- OR STANDARD, XILINX IS MAKING NO REPRESENTATION THAT THIS --
-- IMPLEMENTATION IS FREE FROM ANY CLAIMS OF INFRINGEMENT, --
-- AND YOU ARE RESPONSIBLE FOR OBTAINING ANY RIGHTS YOU MAY REQUIRE --
-- FOR YOUR IMPLEMENTATION. XILINX EXPRESSLY DISCLAIMS ANY --
-- WARRANTY WHATSOEVER WITH RESPECT TO THE ADEQUACY OF THE --
-- IMPLEMENTATION, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OR --
-- REPRESENTATIONS THAT THIS IMPLEMENTATION IS FREE FROM CLAIMS OF --
-- INFRINGEMENT, IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS --
-- FOR A PARTICULAR PURPOSE. --
-- --
-- Xilinx products are not intended for use in life support --
-- appliances, devices, or systems. Use in such applications are --
-- expressly prohibited. --
-- --
-- (c) Copyright 1995-2007 Xilinx, Inc. --
-- All rights reserved. --
--------------------------------------------------------------------------------
-- You must compile the wrapper file fp_to_int.vhd when simulating
-- the core, fp_to_int. When compiling the wrapper file, be sure to
-- reference the XilinxCoreLib VHDL simulation library. For detailed
-- instructions, please refer to the "CORE Generator Help".
 
-- The synthesis directives "translate_off/translate_on" specified
-- below are supported by Xilinx, Mentor Graphics and Synplicity
-- synthesis tools. Ensure they are correct for your synthesis tool(s).
 
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- synthesis translate_off
Library XilinxCoreLib;
-- synthesis translate_on
ENTITY fp_to_int IS
port (
a: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
overflow: OUT std_logic;
invalid_op: OUT std_logic);
END fp_to_int;
 
ARCHITECTURE fp_to_int_a OF fp_to_int IS
-- synthesis translate_off
component wrapped_fp_to_int
port (
a: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
overflow: OUT std_logic;
invalid_op: OUT std_logic);
end component;
 
-- Configuration specification
for all : wrapped_fp_to_int use entity XilinxCoreLib.floating_point_v3_0(behavioral)
generic map(
c_has_b_nd => 0,
c_speed => 2,
c_has_sclr => 0,
c_has_a_rfd => 0,
c_b_fraction_width => 20,
c_has_operation_nd => 0,
c_family => "spartan3",
c_has_exception => 0,
c_a_fraction_width => 20,
c_has_flt_to_fix => 1,
c_has_flt_to_flt => 0,
c_has_fix_to_flt => 0,
c_has_invalid_op => 1,
c_latency => 0,
c_has_divide_by_zero => 0,
c_has_overflow => 1,
c_mult_usage => 0,
c_has_rdy => 0,
c_result_fraction_width => 0,
c_has_divide => 0,
c_has_inexact => 0,
c_has_underflow => 0,
c_has_sqrt => 0,
c_has_add => 0,
c_has_status => 0,
c_has_a_negate => 0,
c_optimization => 1,
c_has_a_nd => 0,
c_has_aclr => 0,
c_has_b_negate => 0,
c_has_subtract => 0,
c_compare_operation => 8,
c_rate => 1,
c_has_compare => 0,
c_has_operation_rfd => 0,
c_has_b_rfd => 0,
c_result_width => 26,
c_b_width => 26,
c_status_early => 0,
c_a_width => 26,
c_has_cts => 0,
c_has_ce => 0,
c_has_multiply => 0);
-- synthesis translate_on
BEGIN
-- synthesis translate_off
U0 : wrapped_fp_to_int
port map (
a => a,
clk => clk,
result => result,
overflow => overflow,
invalid_op => invalid_op);
-- synthesis translate_on
 
END fp_to_int_a;
 
/trunk/processor/mc/alu.vhd
0,0 → 1,226
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
use ieee.numeric_std.all;
use work.leval_package.all;
 
entity alu is
port (
in_a : in std_logic_vector(OBJECT_SIZE-1 downto 0);
in_b : in std_logic_vector(OBJECT_SIZE-1 downto 0);
funct : in std_logic_vector(FUNCT_SIZE-1 downto 0);
status : out std_logic_vector(STATUS_REG_SIZE-1 downto 0);
output : out std_logic_vector(OBJECT_SIZE-1 downto 0));
end entity alu;
 
architecture rtl of alu is
-- DIVIDER IS TOO SLOW, DISABLED
-- component divider is
-- GENERIC(WIDTH_DIVID : Integer := 32; -- Width Dividend
-- WIDTH_DIVIS : Integer := 16); -- Width Divisor
-- port(dividend : in std_logic_vector (WIDTH_DIVID-1 downto 0);
-- divisor : in std_logic_vector (WIDTH_DIVIS-1 downto 0);
-- quotient : out std_logic_vector (WIDTH_DIVID-1 downto 0);
-- remainder : out std_logic_vector (WIDTH_DIVIS-1 downto 0));
-- end component divider;
signal mul_res : std_logic_vector(DATUM_SIZE*2-3 downto 0);
signal type_a : std_logic_vector(TYPE_SIZE-1 downto 0);
signal gc_flag_a : std_logic;
signal datum_a : std_logic_vector(DATUM_SIZE-1 downto 0);
signal type_b : std_logic_vector(TYPE_SIZE-1 downto 0);
signal gc_flag_b : std_logic;
signal datum_b : std_logic_vector(DATUM_SIZE-1 downto 0);
signal type_r : std_logic_vector(TYPE_SIZE-1 downto 0);
signal gc_flag_r : std_logic;
signal datum_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal div_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal mod_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal fti_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal itf_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal fad_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal fml_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal fdv_r : std_logic_vector(DATUM_SIZE-1 downto 0);
-- signal fti_v, fti_a : std_logic;
-- signal fad_v, fad_u, fad_a : std_logic;
-- signal fml_v, fml_u, fml_a : std_logic;
-- signal fdv_v, fdv_u, fdv_a, fdv_zero : std_logic;
begin
 
-- divider_inst : divider
-- generic map (26,26)
-- port map (
-- dividend => datum_a,
-- divisor => datum_b,
-- quotient => div_r,
-- remainder => mod_r);
--
 
-- Decode inputs
type_a <= in_a(OBJECT_SIZE-1 downto 27);
gc_flag_a <= in_a(26);
datum_a <= in_a(25 downto 0);
type_b <= in_b(OBJECT_SIZE-1 downto 27);
gc_flag_b <= in_b(26);
datum_b <= in_b(25 downto 0);
-- SET STATUS FLAGS
-- Overflow
status(OVERFLOW) <= '0' when (mul_res(49 downto 25) = (mul_res(49 downto 25) xor mul_res(49 downto 25))) else '1';
-- negative
status(NEG) <= datum_r(25);
-- zero
status(ZERO) <= '1' when datum_r = (datum_r xor datum_r) else '0';
-- type error
status(TYP) <= '0' when type_a = type_b else '1';
-- io-error
status(IO) <= '0';
--unused
status(1) <= '0';
status(6) <= '0';
status(7) <= '0';
mul_res <= (datum_a(24 downto 0) * datum_b(24 downto 0));
-- set output to result
output <= type_r & gc_flag_r & datum_r;
process(funct, type_a, type_b, gc_flag_a, gc_flag_b, datum_a, datum_b, mul_res)
begin
type_r <= (others => '0');
gc_flag_r <= '0';
datum_r <= (others => '0');
case funct is
when ALU_ADD =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= datum_a + datum_b;
when ALU_SUB =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= datum_a - datum_b;
when ALU_MUL =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r(24 downto 0) <= mul_res(24 downto 0);
datum_r(25) <= datum_a(25) xor datum_b(25);
-- when ALU_DIV =>
-- type_r <= type_a;
-- gc_flag_r <= gc_flag_a;
-- datum_r <= div_r;
--
-- when ALU_MOD =>
-- type_r <= type_a;
-- gc_flag_r <= gc_flag_a;
-- datum_r <= mod_r;
when ALU_AND =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= datum_a and datum_b;
when ALU_OR =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= datum_a or datum_b;
when ALU_XOR =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= datum_a xor datum_b;
when ALU_GET_TYPE =>
type_r <= DT_INT;
gc_flag_r <= '0';
datum_r(TYPE_SIZE - 1 downto 0) <= type_b;
datum_r(DATUM_SIZE - 1 downto TYPE_SIZE) <= (others => '0');
when ALU_SET_TYPE =>
type_r <= datum_b(TYPE_SIZE-1 downto 0);
gc_flag_r <= '0';
datum_r <= datum_a;
when ALU_SET_DATUM =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= datum_b;
when ALU_SET_GC =>
type_r <= type_a;
gc_flag_r <= datum_b(0);
datum_r <= datum_a;
when ALU_GET_GC =>
type_r <= DT_INT;
gc_flag_r <= '0';
datum_r(0) <= gc_flag_b;
datum_r(DATUM_SIZE - 1 downto 1) <= (others => '0');
when ALU_CPY =>
type_r <= type_b;
gc_flag_r <= gc_flag_b;
datum_r <= datum_b;
-- shift right
when ALU_SR =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= std_logic_vector(shift_right(unsigned(datum_a),
to_integer(unsigned(datum_b))));
-- shift left
when ALU_SL =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= std_logic_vector(shift_left(unsigned(datum_a),
to_integer(unsigned(datum_b))));
when ALU_CMP_DATUM =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= datum_a - datum_b;
when ALU_CMP_TYPE =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= "000000000000000000000" & (type_a - type_b);
when ALU_CMP_TYPE_IMM =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= "000000000000000000000" & (type_a - datum_b(TYPE_SIZE - 1 downto 0));
when ALU_CMP_GC =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= "0000000000000000000000000"&(gc_flag_a xor gc_flag_b);
when ALU_CMP_GC_IMM =>
type_r <= type_a;
gc_flag_r <= gc_flag_a;
datum_r <= "0000000000000000000000000"&(gc_flag_a xor datum_b(0));
when ALU_CMP =>
if type_a = type_b and
datum_a = datum_b then -- we have equivalent objects
datum_r <= (others => '0');
else
datum_r(DATUM_SIZE-1 downto DATUM_SIZE-4) <= "1111";
datum_r(DATUM_SIZE-5 downto 0) <= (others => '0'); -- not same
end if;
when others =>
type_r <= (others => '0');
gc_flag_r <= '0';
datum_r <= (others => '0');
end case;
end process;
end rtl;
/trunk/processor/mc/p_leval.vhd
0,0 → 1,226
-------------------------------------------------------------------------------
-- LEVAL TYPES
-------------------------------------------------------------------------------
-- Package defines types for the LevaL CPU.
-------------------------------------------------------------------------------
-- Created: 28th of August 2008 [lykkebo]
-------------------------------------------------------------------------------
library ieee;
use ieee.std_logic_1164.all, ieee.numeric_std.all;
 
package leval_package is
-- CLEANING UP --
constant WORD_SIZE : integer := 32; -- Size of general word
constant ADDR_SIZE : integer := 26; -- Address bus size
constant SCRATCH_SIZE : integer := 1024; -- Number of registers in scratch memory
constant SCRATCH_ADDR_SIZE : integer := 10; -- Bus size for register address
constant STATUS_REG_SIZE : integer := 8; -- size of stat. reg
-- microcode
constant MC_ADDR_SIZE : integer := 13; -- Microcode memory address bus size
constant MC_INSTR_SIZE : integer := 48; -- Microcode instruction size
constant OPCODE_SIZE : integer := 6;
constant TYPE_SIZE : integer := 5;
constant REG1_S : integer := 39;
constant REG1_E : integer := 29;
constant REG2_S : integer := 28;
constant REG2_E : integer := 18;
constant REG3_S : integer := 17;
constant REG3_E : integer := 7;
-- nR: 47 46 45 44 43 42 41 40 39 38 37 36 35 34 33 32 31 30 29 28 27 26 25 24 23 22 21 20 19 18 17 16 15 14 13 12 11 10 09 08 07 06 05 04 03 02 01 00
-- 1R: OP OP OP OP OP OP DE BP R1 R1 R1 R1 R1 R1 R1 R1 R1 R1 R1 IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM
-- 2R: OP OP OP OP OP OP DE BP R1 R1 R1 R1 R1 R1 R1 R1 R1 R1 R1 R2 R2 R2 R2 R2 R2 R2 R2 R2 R2 R2 IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM IM
-- Branch instructions
-- 0R: OP OP OP OP OP OP DE BP -- -- -- -- -- -- -- -- -- -- -- MK MK MK MK MK MK MK MK FG FG FG FG FG FG FG FG AD AD AD AD AD AD AD AD AD AD AD AD AD
-- 1R: OP OP OP OP OP OP DE BP R1 R1 R1 R1 R1 R1 R1 R1 R1 R1 R1 MK MK MK MK MK MK MK MK FG FG FG FG FG FG FG FG AD AD AD AD AD AD AD AD AD AD AD AD AD
 
-- Status flags
constant ZERO : integer := 3;
constant TYP : integer := 4;
constant OVERFLOW : integer := 0;
constant NEG : integer := 2;
constant IO : integer := 5;
 
-- ALU operations
constant ALU_PASS : std_logic_vector(5 downto 0) := "000000";
constant ALU_ADD : std_logic_vector(5 downto 0) := "000001";
constant ALU_GET_TYPE : std_logic_vector(5 downto 0) := "000010";
constant ALU_SET_TYPE : std_logic_vector(5 downto 0) := "000011";
constant ALU_SET_DATUM : std_logic_vector(5 downto 0) := "000100";
constant ALU_GET_DATUM : std_logic_vector(5 downto 0) := "000101";
constant ALU_SET_GC : std_logic_vector(5 downto 0) := "001110";
constant ALU_GET_GC : std_logic_vector(5 downto 0) := "000110";
constant ALU_SUB : std_logic_vector(5 downto 0) := "000111";
constant ALU_CMP_TYPE : std_logic_vector(5 downto 0) := "001000";
constant ALU_AND : std_logic_vector(5 downto 0) := "001001";
constant ALU_OR : std_logic_vector(5 downto 0) := "001010";
constant ALU_XOR : std_logic_vector(5 downto 0) := "001011";
constant ALU_MUL : std_logic_vector(5 downto 0) := "001100";
constant ALU_DIV : std_logic_vector(5 downto 0) := "001101";
constant ALU_MOD : std_logic_vector(5 downto 0) := "001111";
constant ALU_SL : std_logic_Vector(5 downto 0) := "010000";
constant ALU_SR : std_logic_Vector(5 downto 0) := "010001";
constant ALU_SETLED : std_logic_Vector(5 downto 0) := "010010";
-- opcodes
-- compare operations
constant ALU_CMP_DATUM : std_logic_vector(5 downto 0) := "010111";
constant ALU_CMP_GC : std_logic_vector(5 downto 0) := "011111";
constant ALU_CMP : std_logic_vector(5 downto 0) := "100000";
constant ALU_CMP_TYPE_IMM : std_logic_vector(5 downto 0) := "010010";
constant ALU_CMP_DATUM_IMM : std_logic_vector(5 downto 0) := "010011";
constant ALU_CMP_GC_IMM : std_logic_vector(5 downto 0) := "010100";
-- set operation
constant ALU_CPY : std_logic_vector(5 downto 0) := "010101";
-- system operations
constant NOP : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000000";
constant HALT : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000001";
-- integer instructions
constant ADD : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000010";
constant SUBB : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000011";
constant MUL : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000100";
constant DIV : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000101";
constant MODULO : std_logic_vector(OPCODE_SIZE-1 downto 0) := "001011";
constant SHIFT_L : std_logic_vector(OPCODE_SIZE-1 downto 0) := "001010";
constant SHIFT_R : std_logic_vector(OPCODE_SIZE-1 downto 0) := "001100";
-- logical instructions
constant LAND : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000110";
constant LOR : std_logic_vector(OPCODE_SIZE-1 downto 0) := "000111";
constant LXOR : std_logic_vector(OPCODE_SIZE-1 downto 0) := "001000";
-- memory instructions
constant LOAD : std_logic_vector(OPCODE_SIZE-1 downto 0) := "010000";
constant STORE : std_logic_vector(OPCODE_SIZE-1 downto 0) := "010001";
-- branch instructions
constant BIDX : std_logic_vector(OPCODE_SIZE-1 downto 0) := "010110";
-- data manipulation
constant GET_TYPE : std_logic_vector(OPCODE_SIZE-1 downto 0) := "100000";
constant SET_TYPE : std_logic_vector(OPCODE_SIZE-1 downto 0) := "100001";
constant SET_DATUM : std_logic_vector(OPCODE_SIZE-1 downto 0) := "100011";
constant GET_GC : std_logic_vector(OPCODE_SIZE-1 downto 0) := "100101";
constant SET_GC : std_logic_vector(OPCODE_SIZE-1 downto 0) := "100110";
constant CPY : std_logic_vector(OPCODE_SIZE-1 downto 0) := "101000";
constant SET_TYPE_IMM : std_logic_vector(OPCODE_SIZE-1 downto 0) := "100010";
constant SET_DATUM_IMM: std_logic_vector(OPCODE_SIZE-1 downto 0) := "100100";
constant SET_GC_IMM : std_logic_vector(OPCODE_SIZE-1 downto 0) := "100111";
-- compare functions
constant CMP_TYPE : std_logic_vector(OPCODE_SIZE-1 downto 0) := "101001";
constant CMP_TYPE_IMM: std_logic_vector(OPCODE_SIZE-1 downto 0) := "101010";
constant CMP_DATUM : std_logic_vector(OPCODE_SIZE-1 downto 0) := "101011";
constant CMP_DATUM_IMM: std_logic_vector(OPCODE_SIZE-1 downto 0) := "101100";
constant CMP_GC : std_logic_vector(OPCODE_SIZE-1 downto 0) := "101101";
constant CMP_GC_IMM : std_logic_vector(OPCODE_SIZE-1 downto 0) := "101110";
constant CMP : std_logic_vector(OPCODE_SIZE-1 downto 0) := "101111";
constant SETLED : std_logic_vector(OPCODE_SIZE-1 downto 0) := "111111";
-- status masks
constant SM_INT : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "11110110";
constant SM_LOG : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "11000110";
constant SM_FPO : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "11111110";
constant SM_SYS : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "00000000";
constant SM_MEM : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "00000110";
constant SM_BR : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "00000000";
constant SM_SGO : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "00000000"; -- set get operations
--constant SM_CMP : std_logic_vector(STATUS_REG_SIZE-1 downto 0) := "11111110";
-- data types
constant DT_NONE : std_logic_vector(TYPE_SIZE-1 downto 0) := "00000";
constant DT_INT : std_logic_vector(TYPE_SIZE-1 downto 0) := "00001";
constant DT_FLOAT : std_logic_vector(TYPE_SIZE-1 downto 0) := "00010";
constant DT_CONS : std_logic_vector(TYPE_SIZE-1 downto 0) := "00011";
constant DT_SNOC : std_logic_vector(TYPE_SIZE-1 downto 0) := "00100";
constant DT_PTR : std_logic_vector(TYPE_SIZE-1 downto 0) := "00101";
constant DT_ARRAY : std_logic_vector(TYPE_SIZE-1 downto 0) := "00110";
constant DT_NIL : std_logic_vector(TYPE_SIZE-1 downto 0) := "00111";
constant DT_T : std_logic_vector(TYPE_SIZE-1 downto 0) := "01000";
constant DT_CHAR : std_logic_vector(TYPE_SIZE-1 downto 0) := "01001";
constant DT_SYMBOL : std_logic_vector(TYPE_SIZE-1 downto 0) := "01010";
constant DT_FUNCTION : std_logic_vector(TYPE_SIZE-1 downto 0) := "01011";
constant IMM_SIZE : integer :=10;
-- Constants for internal typing
constant OBJECT_SIZE : integer := 32;
constant DATUM_SIZE : integer := 26;
constant GC_SIZE : integer := 1;
constant TYPE_START : integer := OBJECT_SIZE - TYPE_SIZE;
constant GC_BIT : integer := 26;
 
-- Typing ... types, uhrm.
subtype object is std_logic_vector(OBJECT_SIZE - 1 downto 0);
subtype object_type is std_logic_vector(TYPE_SIZE - 1 downto 0);
subtype object_datum is std_logic_vector(DATUM_SIZE - 1 downto 0);
subtype object_gc is std_logic_vector(GC_SIZE - 1 downto 0);
 
-- Type constants
constant TYPE_INT : object_type := "00010";
 
-- Garbage collection constants
constant GC_TRUE : object_gc := "1";
constant GC_FALSE : object_gc := "0";
-- General constants
constant GENERATE_TRACE : boolean := false;
constant MC_ROM_SIZE : integer := 16384; -- instruction mem
constant SCRATCH_MEM_SIZE : integer := 1024; -- size of scratch
 
 
-- Instruction word constants
constant IN_OP_SIZE : integer := 6;
constant FUNCT_SIZE : integer :=6; -- Size of function word for ALU
constant BUS_SIZE : integer := 32;
constant SCRATCH_DEPTH : integer := 10;
 
-- Clock freq in MHz
constant LEVAL_FREQ : std_logic_vector(7 downto 0) := X"40";
--constant MEMORY_LATENCY : integer := 52; --ms
 
 
-- Types relating to micro-code
subtype mc_inst is std_logic_vector(MC_INSTR_SIZE - 1 downto 0); -- instructions
 
subtype mc_addr is natural range 0 to MC_ROM_SIZE;
type mc_rom is array(mc_addr) of mc_inst;
 
subtype mc_opcode is std_logic_vector(IN_OP_SIZE - 1 downto 0);-- size of opcode
 
-- Types relating to the core
subtype scratch_addr is natural range 0 to SCRATCH_MEM_SIZE;
type scratch_mem is array(scratch_addr) of object;
function sign_extend_18_26(bus_18 : std_logic_vector(17 downto 0))return std_logic_vector;
function mask_flags_match(mask,flags : in std_logic_vector(7 downto 0)) return boolean;
end package;
package body leval_package is
-- Utility
function sign_extend_18_26(bus_18 : std_logic_vector(17 downto 0))
return std_logic_vector is
variable output : std_logic_vector(25 downto 0);
begin
output(17 downto 0) := bus_18(17 downto 0);
output(25 downto 18) := (others => bus_18(17));
return output;
end function;
 
function mask_flags_match(mask, flags : in std_logic_vector(7 downto 0)) return boolean is
begin
if (mask(0) = flags(0)) or
(mask(1) = flags(1)) or
(mask(2) = flags(2)) or
(mask(3) = flags(3)) or
(mask(4) = flags(4)) or
(mask(5) = flags(5)) or
(mask(6) = flags(6)) or
(mask(7) = flags(7))
then
return true;
else
return false;
end if;
end function;
end leval_package;
/trunk/processor/mc/pc_incer.vhd
0,0 → 1,36
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
use work.leval_package.all;
 
entity pc_incer is
port(
clk : in std_logic;
rst : in std_logic;
pause : in std_logic;
offset : in std_logic_vector(MC_ADDR_SIZE - 1 downto 0);
branch : in std_logic;
pc_next : out std_logic_vector(MC_ADDR_SIZE - 1 downto 0) );
end entity;
 
architecture behav of pc_incer is
signal pc_reg : std_logic_vector(MC_ADDR_SIZE-1 downto 0) := (others => '0');
begin
pc_next <= pc_reg;
pc_inc : process(clk, rst)
begin
if rising_edge(clk) then
if rst = '1' then
pc_reg <= (others => '0');
elsif pause = '1' then
if branch = '1' then
pc_reg <= offset;
elsif pc_reg > "1010111111111" then
pc_reg <= (others => '0');
else
pc_reg <= pc_reg + 1;
end if;
end if;
end if;
end process pc_inc;
end architecture behav;
/trunk/processor/mc/toplevel.ucf
0,0 → 1,106
# CLOCK
NET "clk" LOC = "P183";
NET "clk" PERIOD = 32.25ns HIGH 50%;
 
# RESET
NET "rst_low" LOC = "P140";
 
# BUS CONTROL SIGNALS
NET "read" LOC = "P144" | SLEW = SLOW;
NET "write" LOC = "P145" | SLEW = SLOW;
NET "avr_rdy" LOC = "P146";
NET "sync" LOC = "P120";
 
# FOR DEBUG PERPOUSES ONLY
#PC out
#NET "PC<0>" LOC = "P55";
#NET "PC<1>" LOC = "P60";
#NET "PC<2>" LOC = "P61";
#NET "PC<3>" LOC = "P102";
#NET "PC<4>" LOC = "P106";
#NET "PC<5>" LOC = "P107";
#NET "PC<6>" LOC = "P108";
#NET "PC<7>" LOC = "P109";
#NET "PC<8>" LOC = "P126";
#NET "PC<9>" LOC = "P127";
#NET "PC<10>" LOC = "P128";
#NET "PC<11>" LOC = "P129";
#NET "PC<12>" LOC = "P138";
 
 
# MEM CE/AVR_IRQ
NET "mem_ce<0>" LOC = "P132" | SLEW = SLOW;
NET "mem_ce<1>" LOC = "P153" | SLEW = SLOW;
#UNUSED
#NET "mem_ce<2>" LOC = "P134" | SLEW = SLOW;
#NET "mem_ce<3>" LOC = "P135" | SLEW = SLOW;
NET "avr_irq" LOC = "P137" | SLEW = SLOW;
 
# DATA BUS
NET "fpga_data<0>" LOC = "P196" | SLEW = SLOW;
NET "fpga_data<1>" LOC = "P197" | SLEW = SLOW;
NET "fpga_data<2>" LOC = "P199" | SLEW = SLOW;
NET "fpga_data<3>" LOC = "P202" | SLEW = SLOW;
NET "fpga_data<4>" LOC = "P203" | SLEW = SLOW;
NET "fpga_data<5>" LOC = "P205" | SLEW = SLOW;
NET "fpga_data<6>" LOC = "P2" | SLEW = SLOW;
NET "fpga_data<7>" LOC = "P3" | SLEW = SLOW;
NET "fpga_data<8>" LOC = "P4" | SLEW = SLOW;
NET "fpga_data<9>" LOC = "P8" | SLEW = SLOW;
NET "fpga_data<10>" LOC = "P9" | SLEW = SLOW;
NET "fpga_data<11>" LOC = "P11" | SLEW = SLOW;
NET "fpga_data<12>" LOC = "P12" | SLEW = SLOW;
NET "fpga_data<13>" LOC = "P15" | SLEW = SLOW;
NET "fpga_data<14>" LOC = "P16" | SLEW = SLOW;
NET "fpga_data<15>" LOC = "P18" | SLEW = SLOW;
NET "fpga_data<16>" LOC = "P19" | SLEW = SLOW;
NET "fpga_data<17>" LOC = "P22" | SLEW = SLOW;
NET "fpga_data<18>" LOC = "P23" | SLEW = SLOW;
NET "fpga_data<19>" LOC = "P24" | SLEW = SLOW;
NET "fpga_data<20>" LOC = "P25" | SLEW = SLOW;
NET "fpga_data<21>" LOC = "P28" | SLEW = SLOW;
NET "fpga_data<22>" LOC = "P29" | SLEW = SLOW;
NET "fpga_data<23>" LOC = "P30" | SLEW = SLOW;
NET "fpga_data<24>" LOC = "P33" | SLEW = SLOW;
NET "fpga_data<25>" LOC = "P34" | SLEW = SLOW;
NET "fpga_data<26>" LOC = "P35" | SLEW = SLOW;
NET "fpga_data<27>" LOC = "P36" | SLEW = SLOW;
NET "fpga_data<28>" LOC = "P39" | SLEW = SLOW;
NET "fpga_data<29>" LOC = "P40" | SLEW = SLOW;
NET "fpga_data<30>" LOC = "P41" | SLEW = SLOW;
NET "fpga_data<31>" LOC = "P42" | SLEW = SLOW;
 
# ADDRESS BUS
NET "fpga_addr<0>" LOC = "P62" | SLEW = SLOW;
NET "fpga_addr<1>" LOC = "P63" | SLEW = SLOW;
NET "fpga_addr<2>" LOC = "P64" | SLEW = SLOW;
NET "fpga_addr<3>" LOC = "P65" | SLEW = SLOW;
NET "fpga_addr<4>" LOC = "P68" | SLEW = SLOW;
NET "fpga_addr<5>" LOC = "P69" | SLEW = SLOW;
NET "fpga_addr<6>" LOC = "P74" | SLEW = SLOW;
NET "fpga_addr<7>" LOC = "P75" | SLEW = SLOW;
NET "fpga_addr<8>" LOC = "P76" | SLEW = SLOW;
NET "fpga_addr<9>" LOC = "P77" | SLEW = SLOW;
NET "fpga_addr<10>" LOC = "P78" | SLEW = SLOW;
NET "fpga_addr<11>" LOC = "P82" | SLEW = SLOW;
NET "fpga_addr<12>" LOC = "P83" | SLEW = SLOW;
NET "fpga_addr<13>" LOC = "P89" | SLEW = SLOW; ### WRONG? P100
NET "fpga_addr<14>" LOC = "P90" | SLEW = SLOW; ### WRONG? P93
NET "fpga_addr<15>" LOC = "P94" | SLEW = SLOW;
NET "fpga_addr<16>" LOC = "P96" | SLEW = SLOW;
NET "fpga_addr<17>" LOC = "P97" | SLEW = SLOW;
NET "fpga_addr<18>" LOC = "P99" | SLEW = SLOW;
## ERROR CORRECTION
NET "err<0>" LOC = "P100";
NET "err<1>" LOC = "P93";
 
# LED
NET "led<0>" LOC = "P160" | SLEW = SLOW;
NET "led<1>" LOC = "P161" | SLEW = SLOW;
NET "led<2>" LOC = "P162" | SLEW = SLOW;
NET "led<3>" LOC = "P164" | SLEW = SLOW;
NET "led<4>" LOC = "P165" | SLEW = SLOW;
NET "led<5>" LOC = "P167" | SLEW = SLOW;
NET "led<6>" LOC = "P171" | SLEW = SLOW;
NET "led<7>" LOC = "P172" | SLEW = SLOW;
 
/trunk/processor/mc/divider.vhd
0,0 → 1,92
-- ==============================================================================
-- Generic signed/unsigned restoring divider
--
-- This library 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 library 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. See http://www.gnu.org/copyleft/lesser.txt
--
-- ------------------------------------------------------------------------------
-- Version Author Date Changes
-- 0.1 Hans Tiggeler 07/18/02 Tested on Modelsim SE 5.6
-- ==============================================================================
library ieee;
use ieee.std_logic_1164.all;
use ieee.std_logic_unsigned.all;
 
entity divider is
GENERIC(WIDTH_DIVID : Integer := 32; -- Width Dividend
WIDTH_DIVIS : Integer := 16); -- Width Divisor
port(dividend : in std_logic_vector (WIDTH_DIVID-1 downto 0);
divisor : in std_logic_vector (WIDTH_DIVIS-1 downto 0);
quotient : out std_logic_vector (WIDTH_DIVID-1 downto 0);
remainder : out std_logic_vector (WIDTH_DIVIS-1 downto 0);
twocomp : in std_logic); -- '1' = 2's Complement,
end divider ; -- '0' = Unsigned
 
architecture rtl of divider is
type stdarray is array(WIDTH_DIVID downto 0) of std_logic_vector(WIDTH_DIVIS downto 0);
signal addsub_s : stdarray;
signal dividend_s : std_logic_vector(WIDTH_DIVID-1 downto 0);
signal didi_s : std_logic_vector(WIDTH_DIVID-1 downto 0);
signal divisor_s : std_logic_vector(WIDTH_DIVIS downto 0);
signal disi_s : std_logic_vector(WIDTH_DIVIS downto 0);
signal divn_s : std_logic_vector(WIDTH_DIVIS downto 0);
signal div_s : std_logic_vector(WIDTH_DIVIS downto 0);
signal signquot_s : std_logic;
signal signremain_s : std_logic;
signal remain_s : std_logic_vector(WIDTH_DIVIS+1 downto 0);
signal remainder_s : std_logic_vector(WIDTH_DIVIS+1 downto 0);
signal quot_s : std_logic_vector(WIDTH_DIVID-1 downto 0);
signal quotient_s : std_logic_vector(WIDTH_DIVID-1 downto 0);
begin
-- Sign Quotient
signquot_s <= (dividend(WIDTH_DIVID-1) xor divisor(WIDTH_DIVIS-1)) and twocomp;
-- Sign Remainder
signremain_s <= (signquot_s xor divisor(WIDTH_DIVIS-1)) and twocomp;
 
-- Rectify Dividend
didi_s <= not(dividend) when (dividend(WIDTH_DIVID-1) and twocomp)='1' else dividend;
dividend_s <= didi_s + (dividend(WIDTH_DIVID-1) and twocomp);
 
-- Rectify Divisor
disi_s <= not('1'&divisor) when (divisor(WIDTH_DIVIS-1) and twocomp)='1' else ('0'&divisor);
divisor_s <= disi_s + (divisor(WIDTH_DIVIS-1) and twocomp);
 
-- Create 2-Complement negative divisor
divn_s <= not(divisor_s) + '1';
 
-- Positive Divisor
div_s <= divisor_s;
 
-- Note first stage dividend_s(WIDTH_DIVID-1) is always '0'
addsub_s(WIDTH_DIVID) <= divn_s;
 
stages : for i in WIDTH_DIVID-1 downto 0 generate
addsub_s(i) <= ((addsub_s(i+1)(WIDTH_DIVIS-1 downto 0) & dividend_s(i)) + div_s) when addsub_s(i+1)(WIDTH_DIVIS)='1' else
((addsub_s(i+1)(WIDTH_DIVIS-1 downto 0) & dividend_s(i)) + divn_s);
end generate;
 
remain_s <= ((addsub_s(0)(WIDTH_DIVIS)&addsub_s(0)) + ('0'&div_s)) when addsub_s(0)(WIDTH_DIVIS)='1' else '0'&addsub_s(0);
 
-- Quotient
outstage : for i in WIDTH_DIVID-1 downto 0 generate
quot_s(i) <= not(addsub_s(i)(WIDTH_DIVIS));
end generate;
 
remainder_s <= ((not(remain_s)) + '1') when signremain_s='1' else remain_s; -- correct remainder sign
 
quotient_s <= ((not(quot_s)) + '1') when signquot_s='1' else quot_s; -- correct quotient sign
 
remainder <= remainder_s(WIDTH_DIVIS-1 downto 0) when twocomp='1' else
(remainder_s(WIDTH_DIVIS-1 downto 0)+remainder_s(WIDTH_DIVIS+1));
 
quotient <= quotient_s;
/trunk/processor/mc/leval_tb.vhd
0,0 → 1,102
library ieee;
 
use ieee.std_logic_1164.all;
use work.leval_package.all;
use work.avremu_package.all;
 
entity leval_tb is
end entity;
 
architecture rtl of leval_tb is
-- Components:
component leval is
port (
rst : in std_logic;
clk : in std_logic;
data_bus : inout std_logic_vector(BUS_SIZE-1 downto 0);
addr_bus : out std_logic_vector(ADDR_SIZE-1 downto 0);
wait_s : in std_logic;
read : out std_logic;
write : out std_logic;
sync : in std_logic;
led : out std_logic_vector(7 downto 0));
end component;
component addr_decoder is
port (
clk : in std_logic;
leval_addr : in std_logic_vector(ADDR_SIZE - 1 downto 0);
avr_irq : out std_logic;
mem_wait : out std_logic;
mem_ce : out std_logic;
read_s : in std_logic;
write_s : in std_logic
);
end component;
 
-- Signals:
signal addr_s : std_logic_vector(ADDR_SIZE - 1 downto 0);
signal mem_wait_s : std_logic;
signal wait_s : std_logic;
signal write_s : std_logic;
signal read_s : std_logic;
signal rst : std_logic;
signal flash_ce0 : std_logic;
signal flash_ce1 : std_logic := '0';
signal clk : std_logic;
signal rst_low : std_logic;
signal fpga_data : std_logic_vector(WORD_SIZE - 1 downto 0);
signal fpga_addr : std_logic_vector(ADDR_SIZE - 1 downto 0);
signal avr_irq : std_logic;
signal wait_f : std_logic;
signal read : std_logic;
signal write : std_logic;
signal mem_ce : std_logic;
signal sync_s : std_logic;
signal led : std_logic_vector(7 downto 0);
signal err : std_logic_vector(1 downto 0);
begin
rst <= not rst_low;
fpga_addr <= addr_s;
--wait_s <= mem_wait_s and wait_f;
read <= not read_s;
write <= not write_s;
 
LEVAL_CPU : leval
port map(
clk => clk,
rst => rst,
data_bus => fpga_data,
addr_bus => addr_s,
wait_s => wait_s,
read => read_s,
write => write_s,
led => led,
sync => sync_s
);
 
ADDR_DEC : addr_decoder
port map (
clk => clk,
leval_addr => addr_s,
avr_irq => avr_irq,
mem_wait => mem_wait_s,
mem_ce => mem_ce,
read_s => read_s,
write_s => write_s
);
 
 
testproc : process
begin
sync_s <= '1';
-- pause_pc <= '0';
rst_low <= '1';
 
wait;
end process;
 
end architecture;
/trunk/processor/mc/fpu_adder.vhd
0,0 → 1,128
--------------------------------------------------------------------------------
-- This file is owned and controlled by Xilinx and must be used --
-- solely for design, simulation, implementation and creation of --
-- design files limited to Xilinx devices or technologies. Use --
-- with non-Xilinx devices or technologies is expressly prohibited --
-- and immediately terminates your license. --
-- --
-- XILINX IS PROVIDING THIS DESIGN, CODE, OR INFORMATION "AS IS" --
-- SOLELY FOR USE IN DEVELOPING PROGRAMS AND SOLUTIONS FOR --
-- XILINX DEVICES. BY PROVIDING THIS DESIGN, CODE, OR INFORMATION --
-- AS ONE POSSIBLE IMPLEMENTATION OF THIS FEATURE, APPLICATION --
-- OR STANDARD, XILINX IS MAKING NO REPRESENTATION THAT THIS --
-- IMPLEMENTATION IS FREE FROM ANY CLAIMS OF INFRINGEMENT, --
-- AND YOU ARE RESPONSIBLE FOR OBTAINING ANY RIGHTS YOU MAY REQUIRE --
-- FOR YOUR IMPLEMENTATION. XILINX EXPRESSLY DISCLAIMS ANY --
-- WARRANTY WHATSOEVER WITH RESPECT TO THE ADEQUACY OF THE --
-- IMPLEMENTATION, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OR --
-- REPRESENTATIONS THAT THIS IMPLEMENTATION IS FREE FROM CLAIMS OF --
-- INFRINGEMENT, IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS --
-- FOR A PARTICULAR PURPOSE. --
-- --
-- Xilinx products are not intended for use in life support --
-- appliances, devices, or systems. Use in such applications are --
-- expressly prohibited. --
-- --
-- (c) Copyright 1995-2007 Xilinx, Inc. --
-- All rights reserved. --
--------------------------------------------------------------------------------
-- You must compile the wrapper file fpu_adder.vhd when simulating
-- the core, fpu_adder. When compiling the wrapper file, be sure to
-- reference the XilinxCoreLib VHDL simulation library. For detailed
-- instructions, please refer to the "CORE Generator Help".
 
-- The synthesis directives "translate_off/translate_on" specified
-- below are supported by Xilinx, Mentor Graphics and Synplicity
-- synthesis tools. Ensure they are correct for your synthesis tool(s).
 
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- synthesis translate_off
Library XilinxCoreLib;
-- synthesis translate_on
ENTITY fpu_adder IS
port (
a: IN std_logic_VECTOR(25 downto 0);
b: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
underflow: OUT std_logic;
overflow: OUT std_logic;
invalid_op: OUT std_logic);
END fpu_adder;
 
ARCHITECTURE fpu_adder_a OF fpu_adder IS
-- synthesis translate_off
component wrapped_fpu_adder
port (
a: IN std_logic_VECTOR(25 downto 0);
b: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
underflow: OUT std_logic;
overflow: OUT std_logic;
invalid_op: OUT std_logic);
end component;
 
-- Configuration specification
for all : wrapped_fpu_adder use entity XilinxCoreLib.floating_point_v3_0(behavioral)
generic map(
c_has_b_nd => 0,
c_speed => 2,
c_has_sclr => 0,
c_has_a_rfd => 0,
c_b_fraction_width => 20,
c_has_operation_nd => 0,
c_family => "spartan3",
c_has_exception => 0,
c_a_fraction_width => 20,
c_has_flt_to_fix => 0,
c_has_flt_to_flt => 0,
c_has_fix_to_flt => 0,
c_has_invalid_op => 1,
c_latency => 0,
c_has_divide_by_zero => 0,
c_has_overflow => 1,
c_mult_usage => 0,
c_has_rdy => 0,
c_result_fraction_width => 20,
c_has_divide => 0,
c_has_inexact => 0,
c_has_underflow => 1,
c_has_sqrt => 0,
c_has_add => 1,
c_has_status => 0,
c_has_a_negate => 0,
c_optimization => 1,
c_has_a_nd => 0,
c_has_aclr => 0,
c_has_b_negate => 0,
c_has_subtract => 0,
c_compare_operation => 8,
c_rate => 1,
c_has_compare => 0,
c_has_operation_rfd => 0,
c_has_b_rfd => 0,
c_result_width => 26,
c_b_width => 26,
c_status_early => 0,
c_a_width => 26,
c_has_cts => 0,
c_has_ce => 0,
c_has_multiply => 0);
-- synthesis translate_on
BEGIN
-- synthesis translate_off
U0 : wrapped_fpu_adder
port map (
a => a,
b => b,
clk => clk,
result => result,
underflow => underflow,
overflow => overflow,
invalid_op => invalid_op);
-- synthesis translate_on
 
END fpu_adder_a;
 
/trunk/processor/mc/toplevel.vhd
0,0 → 1,203
library ieee;
use ieee.std_logic_1164.all;
use work.leval_package.all;
 
entity toplevel is
port(
clk : in std_logic;
rst_low : in std_logic;
fpga_data : inout std_logic_vector(WORD_SIZE - 1 downto 0);
fpga_addr : out std_logic_vector(ADDR_SIZE - 1 downto 0);
avr_irq : out std_logic;
avr_rdy : in std_logic;
sync : in std_logic;
read : out std_logic;
write : out std_logic;
mem_ce : out std_logic_vector(1 downto 0);
led : out std_logic_vector(7 downto 0);
err : in std_logic_vector(1 downto 0));
end entity;
 
architecture rtl of toplevel is
-- Components:
component leval is
port (
rst : in std_logic;
clk : in std_logic;
data_in : in std_logic_vector(BUS_SIZE - 1 downto 0);
data_out : out std_logic_vector(BUS_SIZE - 1 downto 0);
addr_bus : out std_logic_vector(ADDR_SIZE-1 downto 0);
wait_s : in std_logic;
read : out std_logic;
write : out std_logic;
sync : in std_logic;
led : out std_logic_vector(7 downto 0));
-- DEBUG SIGNALS
-- pc_out : out std_logic_vector(MC_ADDR_SIZE-1 downto 0);
-- state_out : out std_logic_vector(3 downto 0);
-- status_out : out std_logic_vector(STATUS_REG_SIZE-1 downto 0);
-- pc_write_out : out std_logic);
end component;
component addr_decoder is
port (
clk : in std_logic;
leval_addr : in std_logic_vector(ADDR_SIZE - 1 downto 0);
avr_irq : out std_logic;
mem_wait : out std_logic;
mem_ce : out std_logic_vector(1 downto 0);
read_s : in std_logic;
write_s : in std_logic);
end component;
component synchronizer is
port (
clk : in std_logic;
ws : in std_logic;
wso : out std_logic);
end component;
 
-- Tristate bus
component bidirbus is
port (
bidir : inout std_logic_vector(WORD_SIZE - 1 downto 0);
oe : in std_logic;
clk : in std_logic;
inp : in std_logic_vector(WORD_SIZE - 1 downto 0);
outp : out std_logic_vector(WORD_SIZE - 1 downto 0));
end component;
-- -- CHIPSCOPE MODULES:
-- component icon
-- port (
-- control0 : out std_logic_vector(35 downto 0);
-- control1 : out std_logic_vector(35 downto 0));
-- end component;
--
-- component ila
-- port (
-- control : in std_logic_vector(35 downto 0);
-- clk : in std_logic;
-- trig0 : in std_logic_vector(47 downto 0));
-- end component;
--
-- component vio
-- port (
-- control : in std_logic_vector(35 downto 0);
-- clk : in std_logic;
-- sync_in : in std_logic_vector(47 downto 0);
-- sync_out : out std_logic_vector(47 downto 0));
-- end component;
--
-- -- CHIPSCOPE SIGNALS:
-- signal trig0 : std_logic_vector(47 downto 0);
-- signal control1 : std_logic_vector(35 downto 0);
-- signal sync_in : std_logic_vector(47 downto 0);
-- signal sync_out : std_logic_vector(47 downto 0);
-- signal control0 : std_logic_vector(35 downto 0);
-- -- END OF CHIPSCOPE COMPONENTS
 
-- -- DEBUG SIGNALS:
-- signal pc_out : std_logic_vector(MC_ADDR_SIZE-1 downto 0);
-- signal state_out : std_logic_vector(3 downto 0);
-- signal pc_write_out : std_logic;
-- signal status_out : std_logic_vector(STATUS_REG_SIZE-1 downto 0);
-- signal op1, op2 : std_logic_vector(WORD_SIZE-1 downto 0);
 
-- Tristatebus signals
-- From bidirbus to synchro
signal t_bus_data_out : std_logic_vector(BUS_SIZE - 1 downto 0);
-- Synchronizer signals
-- From synchronizer
signal sync_ws_out : std_logic;
 
-- These give way for flip-flops
signal read_s_delayed : std_logic;
signal write_s_delayed : std_logic;
signal avr_irq_s_delayed : std_logic;
signal mem_ce_s_delayed : std_logic_vector(1 downto 0);
signal addr_s_delayed : std_logic_vector(ADDR_SIZE - 1 downto 0);
 
-- This is from leval out to the world
signal leval_data_out : std_logic_vector(BUS_SIZE - 1 downto 0);
 
-- Signals:
signal addr_s : std_logic_vector(ADDR_SIZE - 1 downto 0);
signal mem_wait_s : std_logic;
signal mem_wait_and_avr_rdy : std_logic;
signal write_s : std_logic;
signal read_s : std_logic;
signal rst : std_logic;
signal avr_irq_s : std_logic;
signal mem_ce_s : std_logic_vector(1 downto 0);
-- Clock control signals:
signal leval_clk : std_logic := '0';
 
begin
 
rst <= not rst_low;
fpga_addr <= addr_s_delayed;
read <= not read_s_delayed;
write <= not write_s_delayed;
avr_irq <= avr_irq_s_delayed;
mem_ce <= mem_ce_s_delayed;
mem_wait_and_avr_rdy <= mem_wait_s and avr_rdy;
leval_clk <= clk;
-- -- DEBUG SIGNALS
-- pc <= pc_out;
 
synchronizer_inst : synchronizer
port map(
clk => leval_clk,
ws => mem_wait_and_avr_rdy, --connect the RDY/WAIT signal directly to synchronizer
wso => sync_ws_out); -- connect the synched RDY/WAIT to leval
 
bidirbus_inst : bidirbus
port map(
clk => leval_clk,
oe => write_s,
bidir => fpga_data,
inp => leval_data_out, -- from leval into bidirbus
outp => t_bus_data_out); -- from bidirbus to leval
leval_inst : leval
port map(
clk => leval_clk,
rst => rst,
sync => sync,
data_out => leval_data_out,
data_in => t_bus_data_out, --connect Tristatebus to data in
addr_bus => addr_s,
wait_s => sync_ws_out,
read => read_s,
write => write_s,
led => led);
-- status_out => status_out,
-- pc_out => pc_out,
-- state_out => state_out,
-- pc_write_out => pc_write_out);
 
addr_decoder_inst : addr_decoder
port map (
clk => leval_clk,
leval_addr => addr_s,
avr_irq => avr_irq_s,
mem_wait => mem_wait_s,
mem_ce => mem_ce_s,
read_s => read_s_delayed,
write_s => write_s_delayed
);
 
flank_delay : process(clk)
begin
if rising_edge(clk) then
read_s_delayed <= read_s;
write_s_delayed <= write_s;
avr_irq_s_delayed <= avr_irq_s;
mem_ce_s_delayed <= mem_ce_s;
addr_s_delayed <= addr_s;
end if;
end process;
 
end architecture rtl;
/trunk/processor/mc/lcdlevel.vhd
0,0 → 1,573
library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.STD_LOGIC_ARITH.ALL;
use IEEE.STD_LOGIC_UNSIGNED.ALL;
 
---- Uncomment the following library declaration if instantiating
---- any Xilinx primitives in this code.
--library UNISIM;
--use UNISIM.VComps1nts.all;
 
entity lcd is
port(
clk, reset, reset_leval : in std_logic;
sw : in std_logic_vector(3 downto 0); -- slide switch
SF_D : out std_logic_vector(3 downto 0);
LCD_E, LCD_RS, LCD_RW, SF_CE0 : out std_logic;
LED : out std_logic_vector(7 downto 0)
);
end lcd;
 
architecture behavior of lcd is
 
type display_state is (init, function_set, s1, entry_set, s2, set_display, s3, clr_display, s4, pause, set_addr, s5, update, s6, done);
signal cur_state : display_state := init;
 
signal SF_D0, SF_D1 : std_logic_vector(3 downto 0);
signal LCD_E0, LCD_E1 : std_logic;
signal mux : std_logic;
 
type tx_sequence is (high_setup, high_hold, oneus, low_setup, low_hold, fortyus, done);
signal tx_state : tx_sequence := done;
signal tx_byte : std_logic_vector(7 downto 0);
signal tx_init : std_logic := '0';
signal tx_rdy : std_logic := '0';
 
type init_sequence is (idle, fifteenms, s1, s2, s3, s4, s5, s6, s7, s8, done);
signal init_state : init_sequence := idle;
signal init_init, init_done : std_logic := '0';
 
signal i : integer range 0 to 750000 := 0;
signal i2 : integer range 0 to 2000 := 0;
signal i3 : integer range 0 to 82000 := 0;
signal i4 : integer range 0 to 50000000 := 0;
 
signal num : std_logic_vector(3 downto 0);
 
signal l_pos : std_logic_vector(4 downto 0);
signal var : std_logic_vector(7 downto 0);
 
constant CHAR_SPACE : std_logic_vector(7 downto 0) := "00100000";
constant CHAR_COLON : std_logic_vector(7 downto 0) := "00111010";
constant CHAR_0 : std_logic_vector(7 downto 0) := "00110000";
constant CHAR_1 : std_logic_vector(7 downto 0) := "00110001";
constant CHAR_2 : std_logic_vector(7 downto 0) := "00110010";
constant CHAR_3 : std_logic_vector(7 downto 0) := "00110011";
constant CHAR_4 : std_logic_vector(7 downto 0) := "00110100";
constant CHAR_5 : std_logic_vector(7 downto 0) := "00110101";
constant CHAR_6 : std_logic_vector(7 downto 0) := "00110110";
constant CHAR_7 : std_logic_vector(7 downto 0) := "00110111";
constant CHAR_8 : std_logic_vector(7 downto 0) := "00111000";
constant CHAR_9 : std_logic_vector(7 downto 0) := "00111001";
constant CHAR_A : std_logic_vector(7 downto 0) := "01000001";
constant CHAR_B : std_logic_vector(7 downto 0) := "01000010";
constant CHAR_C : std_logic_vector(7 downto 0) := "01000011";
constant CHAR_D : std_logic_vector(7 downto 0) := "01000100";
constant CHAR_E : std_logic_vector(7 downto 0) := "01000101";
constant CHAR_F : std_logic_vector(7 downto 0) := "01000110";
constant CHAR_G : std_logic_vector(7 downto 0) := "01000111";
constant CHAR_H : std_logic_vector(7 downto 0) := "01001000";
constant CHAR_I : std_logic_vector(7 downto 0) := "01001001";
constant CHAR_J : std_logic_vector(7 downto 0) := "01001010";
constant CHAR_K : std_logic_vector(7 downto 0) := "01001011";
constant CHAR_L : std_logic_vector(7 downto 0) := "01001100";
constant CHAR_M : std_logic_vector(7 downto 0) := "01001101";
constant CHAR_N : std_logic_vector(7 downto 0) := "01001110";
constant CHAR_O : std_logic_vector(7 downto 0) := "01001111";
constant CHAR_P : std_logic_vector(7 downto 0) := "01010000";
constant CHAR_Q : std_logic_vector(7 downto 0) := "01010001";
constant CHAR_R : std_logic_vector(7 downto 0) := "01010010";
constant CHAR_S : std_logic_vector(7 downto 0) := "01010011";
constant CHAR_T : std_logic_vector(7 downto 0) := "01010100";
constant CHAR_U : std_logic_vector(7 downto 0) := "01010101";
constant CHAR_V : std_logic_vector(7 downto 0) := "01010110";
constant CHAR_W : std_logic_vector(7 downto 0) := "01010111";
constant CHAR_X : std_logic_vector(7 downto 0) := "01011000";
constant CHAR_Y : std_logic_vector(7 downto 0) := "01011001";
constant CHAR_Z : std_logic_vector(7 downto 0) := "01011010";
 
type lcd_char is array(0 to 31) of std_logic_vector(7 downto 0);
signal lcd_char_set : lcd_char;
-- Signals to top level
signal leval_clk : std_logic := '0';
signal leval_rst : std_logic;
--signal pause is uneeded
signal leval_bus_addr : std_logic_vector(31 downto 0);
signal leval_bus_data : std_logic_vector(31 downto 0);
signal leval_pc : std_logic_vector(15 downto 0) := "0000000000000000";
signal leval_rd : std_logic;
signal leval_wr : std_logic;
 
function lcd_bin_to_hex(input : std_logic_vector(3 downto 0))
return std_logic_vector is
variable output : std_logic_vector(7 downto 0);
begin
if input > "1001" then
output := "0100"&(input-"1001");
else
output := "0011"&input;
end if;
return output;
end function;
-- LEVAL declaration
component leval is
port(
-- Inputs
pause : in std_logic;
rst : in std_logic; -- convert to synchronous
clk : in std_logic;
-- Bus communication
data_bus : inout std_logic_vector(31 downto 0);
addr_bus : out std_logic_vector(25 downto 0);
wait_s : in std_logic;
read : out std_logic;
write : out std_logic;
led : out std_logic_vector(7 downto 0);
pc_out : out std_logic_vector(12 downto 0));
end component leval;
 
begin
-- Initiate CPU and connect signal
leval_inst : leval
port map (
pause => '0',
rst => leval_rst,
clk => leval_clk,
data_bus => leval_bus_data,
addr_bus => leval_bus_addr(25 downto 0),
read => leval_rd,
write => leval_wr,
wait_s => sw(1),
pc_out => leval_pc(12 downto 0));
leval_pc(15 downto 13) <= (others => '0');
leval_bus_addr(31 downto 26) <= (others => '0');
leval_rst <= reset_leval;
LED <= leval_wr&leval_rd&leval_pc(3 downto 0)&leval_rst&leval_clk;
--LED <= tx_byte; --for diagnostic purposes
--- Writing code. Letters on the left side will be written to address on the left side
with l_pos select
var <=
CHAR_P when "00000",
CHAR_C when "00001",
CHAR_COLON when "00010",
lcd_char_set(3) when "00011",
lcd_char_set(4) when "00100",
lcd_char_set(5) when "00101",
lcd_char_set(6) when "00110",
lcd_char_set(7) when "00111",
CHAR_A when "01000",
CHAR_D when "01001",
CHAR_R when "01010",
CHAR_COLON when "01011",
lcd_char_set(12) when "01100",
lcd_char_set(13) when "01101",
lcd_char_set(14) when "01110",
lcd_char_set(15) when "01111",
CHAR_D when "10000",
CHAR_A when "10001",
CHAR_T when "10010",
CHAR_A when "10011",
CHAR_COLON when "10100",
lcd_char_set(21) when "10101",
lcd_char_set(22) when "10110",
lcd_char_set(23) when "10111",
lcd_char_set(24) when "11000",
lcd_char_set(25) when "11001",
lcd_char_set(26) when "11010",
lcd_char_set(27) when "11011",
lcd_char_set(28) when "11100",
lcd_char_set(29) when "11101",
lcd_char_set(30) when "11110",
lcd_char_set(31) when "11111",
"00100000" when others;
 
SF_CE0 <= '1'; --disable intel strataflash
LCD_RW <= '0'; --write only
 
--when to transmit a command/data and when not to
with cur_state select
tx_init <= '1' when function_set | entry_set | set_display | clr_display | set_addr | update,
'0' when others;
 
--control the bus
with cur_state select
mux <= '1' when init,
'0' when others;
 
--control the initialization sequence
with cur_state select
init_init <= '1' when init,
'0' when others;
--register select
with cur_state select
LCD_RS <= '0' when s1|s2|s3|s4|s5,
'1' when others;
 
with cur_state select
tx_byte <= "00101000" when s1,
"00000110" when s2,
"00001100" when s3,
"00000001" when s4,
"1"&l_pos(4)&"00"&l_pos(3 downto 0) when s5,
var when s6,
"00000000" when others;
counter: process(clk, reset)
begin
if(reset = '1') then
i4 <= 0;
num <= "0000";
leval_clk <= '0';
for i in 0 to 31 loop
lcd_char_set(i) <= "00100000";
end loop;
elsif(clk='1' and clk'event and sw(0)='1') then
lcd_char_set(0) <= "0011"&num;
if(i4 = 25000000) then
leval_clk <= not leval_clk;
end if;
if(i4 = 50000000) then
leval_clk <= not leval_clk;
i4 <= 0;
if(num = "1001") then
num <= "0000";
else
num <= num + '1';
end if;
else
i4 <= i4 + 1;
end if;
-- Update chars on LCD
-- Program Counter
lcd_char_set(3) <= lcd_bin_to_hex(leval_pc(15 downto 12));
lcd_char_set(4) <= lcd_bin_to_hex(leval_pc(11 downto 8));
lcd_char_set(5) <= lcd_bin_to_hex(leval_pc(7 downto 4));
lcd_char_set(6) <= lcd_bin_to_hex(leval_pc(3 downto 0));
-- Address Bus
lcd_char_set(12) <= lcd_bin_to_hex(leval_bus_addr(15 downto 12));
lcd_char_set(13) <= lcd_bin_to_hex(leval_bus_addr(11 downto 8));
lcd_char_set(14) <= lcd_bin_to_hex(leval_bus_addr(7 downto 4));
lcd_char_set(15) <= lcd_bin_to_hex(leval_bus_addr(3 downto 0));
-- Data Bus
lcd_char_set(21) <= lcd_bin_to_hex(leval_bus_data(31 downto 28));
lcd_char_set(22) <= lcd_bin_to_hex(leval_bus_data(27 downto 24));
lcd_char_set(23) <= lcd_bin_to_hex(leval_bus_data(23 downto 20));
lcd_char_set(24) <= lcd_bin_to_hex(leval_bus_data(19 downto 16));
lcd_char_set(25) <= lcd_bin_to_hex(leval_bus_data(15 downto 12));
lcd_char_set(26) <= lcd_bin_to_hex(leval_bus_data(11 downto 8));
lcd_char_set(27) <= lcd_bin_to_hex(leval_bus_data(7 downto 4));
lcd_char_set(28) <= lcd_bin_to_hex(leval_bus_data(3 downto 0));
end if;
end process counter;
--main state machine
display: process(clk, reset)
begin
if(reset='1') then
cur_state <= init;
elsif(clk='1' and clk'event) then
case cur_state is
when init =>
if(init_done = '1') then
cur_state <= function_set;
else
cur_state <= init;
end if;
 
when function_set =>
cur_state <= s1;
 
when s1 =>
if(tx_rdy = '1') then
cur_state <= entry_set;
else
cur_state <= s1;
end if;
when entry_set =>
cur_state <= s2;
when s2 =>
if(tx_rdy = '1') then
cur_state <= set_display;
else
cur_state <= s2;
end if;
when set_display =>
cur_state <= s3;
when s3 =>
if(tx_rdy = '1') then
cur_state <= clr_display;
else
cur_state <= s3;
end if;
when clr_display =>
cur_state <= s4;
 
when s4 =>
i3 <= 0;
if(tx_rdy = '1') then
cur_state <= pause;
else
cur_state <= s4;
end if;
 
when pause =>
if(i3 = 82000) then
cur_state <= set_addr;
i3 <= 0;
else
cur_state <= pause;
i3 <= i3 + 1;
end if;
 
when set_addr =>
cur_state <= s5;
 
when s5 =>
if(tx_rdy = '1') then
cur_state <= update;
else
cur_state <= s5;
end if;
when update =>
cur_state <= s6;
when s6 =>
if(tx_rdy = '1') then
cur_state <= set_addr;
l_pos <= l_pos + '1';
else
cur_state <= s6;
end if;
when done =>
cur_state <= done;
 
end case;
end if;
end process display;
 
with mux select
SF_D <= SF_D0 when '0', --transmit
SF_D1 when others; --initialize
with mux select
LCD_E <= LCD_E0 when '0', --transmit
LCD_E1 when others; --initialize
 
with tx_state select
tx_rdy <= '1' when done,
'0' when others;
 
with tx_state select
LCD_E0 <= '0' when high_setup | oneus | low_setup | fortyus | done,
'1' when high_hold | low_hold;
 
with tx_state select
SF_D0 <= tx_byte(7 downto 4) when high_setup | high_hold | oneus,
tx_byte(3 downto 0) when low_setup | low_hold | fortyus | done;
 
 
--specified by datasheet
transmit : process(clk, reset, tx_init)
begin
if(reset='1') then
tx_state <= done;
elsif(clk='1' and clk'event) then
case tx_state is
when high_setup => --40ns
if(i2 = 2) then
tx_state <= high_hold;
i2 <= 0;
else
tx_state <= high_setup;
i2 <= i2 + 1;
end if;
 
when high_hold => --230ns
if(i2 = 12) then
tx_state <= oneus;
i2 <= 0;
else
tx_state <= high_hold;
i2 <= i2 + 1;
end if;
 
when oneus =>
if(i2 = 50) then
tx_state <= low_setup;
i2 <= 0;
else
tx_state <= oneus;
i2 <= i2 + 1;
end if;
 
when low_setup =>
if(i2 = 2) then
tx_state <= low_hold;
i2 <= 0;
else
tx_state <= low_setup;
i2 <= i2 + 1;
end if;
 
when low_hold =>
if(i2 = 12) then
tx_state <= fortyus;
i2 <= 0;
else
tx_state <= low_hold;
i2 <= i2 + 1;
end if;
 
when fortyus =>
if(i2 = 2000) then
tx_state <= done;
i2 <= 0;
else
tx_state <= fortyus;
i2 <= i2 + 1;
end if;
 
when done =>
if(tx_init = '1') then
tx_state <= high_setup;
i2 <= 0;
else
tx_state <= done;
i2 <= 0;
end if;
 
end case;
end if;
end process transmit;
 
with init_state select
init_done <= '1' when done,
'0' when others;
with init_state select
SF_D1 <= "0011" when s1 | s2 | s3 | s4 | s5 | s6,
"0010" when others;
 
with init_state select
LCD_E1 <= '1' when s1 | s3 | s5 | s7,
'0' when others;
--specified by datasheet
power_on_initialize: process(clk, reset, init_init) --power on initialization sequence
begin
if(reset='1') then
init_state <= idle;
elsif(clk='1' and clk'event) then
case init_state is
when idle =>
if(init_init = '1') then
init_state <= fifteenms;
i <= 0;
else
init_state <= idle;
i <= i + 1;
end if;
when fifteenms =>
if(i = 750000) then
init_state <= s1;
i <= 0;
else
init_state <= fifteenms;
i <= i + 1;
end if;
 
when s1 =>
if(i = 11) then
init_state<=s2;
i <= 0;
else
init_state<=s1;
i <= i + 1;
end if;
 
when s2 =>
if(i = 205000) then
init_state<=s3;
i <= 0;
else
init_state<=s2;
i <= i + 1;
end if;
 
when s3 =>
if(i = 11) then
init_state<=s4;
i <= 0;
else
init_state<=s3;
i <= i + 1;
end if;
 
when s4 =>
if(i = 5000) then
init_state<=s5;
i <= 0;
else
init_state<=s4;
i <= i + 1;
end if;
 
when s5 =>
if(i = 11) then
init_state<=s6;
i <= 0;
else
init_state<=s5;
i <= i + 1;
end if;
 
when s6 =>
if(i = 2000) then
init_state<=s7;
i <= 0;
else
init_state<=s6;
i <= i + 1;
end if;
 
when s7 =>
if(i = 11) then
init_state<=s8;
i <= 0;
else
init_state<=s7;
i <= i + 1;
end if;
 
when s8 =>
if(i = 2000) then
init_state<=done;
i <= 0;
else
init_state<=s8;
i <= i + 1;
end if;
 
when done =>
init_state <= done;
 
end case;
 
end if;
end process power_on_initialize;
 
end behavior;
 
/trunk/processor/mc/fpu_div.vhd
0,0 → 1,131
--------------------------------------------------------------------------------
-- This file is owned and controlled by Xilinx and must be used --
-- solely for design, simulation, implementation and creation of --
-- design files limited to Xilinx devices or technologies. Use --
-- with non-Xilinx devices or technologies is expressly prohibited --
-- and immediately terminates your license. --
-- --
-- XILINX IS PROVIDING THIS DESIGN, CODE, OR INFORMATION "AS IS" --
-- SOLELY FOR USE IN DEVELOPING PROGRAMS AND SOLUTIONS FOR --
-- XILINX DEVICES. BY PROVIDING THIS DESIGN, CODE, OR INFORMATION --
-- AS ONE POSSIBLE IMPLEMENTATION OF THIS FEATURE, APPLICATION --
-- OR STANDARD, XILINX IS MAKING NO REPRESENTATION THAT THIS --
-- IMPLEMENTATION IS FREE FROM ANY CLAIMS OF INFRINGEMENT, --
-- AND YOU ARE RESPONSIBLE FOR OBTAINING ANY RIGHTS YOU MAY REQUIRE --
-- FOR YOUR IMPLEMENTATION. XILINX EXPRESSLY DISCLAIMS ANY --
-- WARRANTY WHATSOEVER WITH RESPECT TO THE ADEQUACY OF THE --
-- IMPLEMENTATION, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OR --
-- REPRESENTATIONS THAT THIS IMPLEMENTATION IS FREE FROM CLAIMS OF --
-- INFRINGEMENT, IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS --
-- FOR A PARTICULAR PURPOSE. --
-- --
-- Xilinx products are not intended for use in life support --
-- appliances, devices, or systems. Use in such applications are --
-- expressly prohibited. --
-- --
-- (c) Copyright 1995-2007 Xilinx, Inc. --
-- All rights reserved. --
--------------------------------------------------------------------------------
-- You must compile the wrapper file fpu_div.vhd when simulating
-- the core, fpu_div. When compiling the wrapper file, be sure to
-- reference the XilinxCoreLib VHDL simulation library. For detailed
-- instructions, please refer to the "CORE Generator Help".
 
-- The synthesis directives "translate_off/translate_on" specified
-- below are supported by Xilinx, Mentor Graphics and Synplicity
-- synthesis tools. Ensure they are correct for your synthesis tool(s).
 
LIBRARY ieee;
USE ieee.std_logic_1164.ALL;
-- synthesis translate_off
Library XilinxCoreLib;
-- synthesis translate_on
ENTITY fpu_div IS
port (
a: IN std_logic_VECTOR(25 downto 0);
b: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
underflow: OUT std_logic;
overflow: OUT std_logic;
invalid_op: OUT std_logic;
divide_by_zero: OUT std_logic);
END fpu_div;
 
ARCHITECTURE fpu_div_a OF fpu_div IS
-- synthesis translate_off
component wrapped_fpu_div
port (
a: IN std_logic_VECTOR(25 downto 0);
b: IN std_logic_VECTOR(25 downto 0);
clk: IN std_logic;
result: OUT std_logic_VECTOR(25 downto 0);
underflow: OUT std_logic;
overflow: OUT std_logic;
invalid_op: OUT std_logic;
divide_by_zero: OUT std_logic);
end component;
 
-- Configuration specification
for all : wrapped_fpu_div use entity XilinxCoreLib.floating_point_v3_0(behavioral)
generic map(
c_has_b_nd => 0,
c_speed => 2,
c_has_sclr => 0,
c_has_a_rfd => 0,
c_b_fraction_width => 20,
c_has_operation_nd => 0,
c_family => "spartan3",
c_has_exception => 0,
c_a_fraction_width => 20,
c_has_flt_to_fix => 0,
c_has_flt_to_flt => 0,
c_has_fix_to_flt => 0,
c_has_invalid_op => 1,
c_latency => 0,
c_has_divide_by_zero => 1,
c_has_overflow => 1,
c_mult_usage => 0,
c_has_rdy => 0,
c_result_fraction_width => 20,
c_has_divide => 1,
c_has_inexact => 0,
c_has_underflow => 1,
c_has_sqrt => 0,
c_has_add => 0,
c_has_status => 0,
c_has_a_negate => 0,
c_optimization => 1,
c_has_a_nd => 0,
c_has_aclr => 0,
c_has_b_negate => 0,
c_has_subtract => 0,
c_compare_operation => 8,
c_rate => 1,
c_has_compare => 0,
c_has_operation_rfd => 0,
c_has_b_rfd => 0,
c_result_width => 26,
c_b_width => 26,
c_status_early => 0,
c_a_width => 26,
c_has_cts => 0,
c_has_ce => 0,
c_has_multiply => 0);
-- synthesis translate_on
BEGIN
-- synthesis translate_off
U0 : wrapped_fpu_div
port map (
a => a,
b => b,
clk => clk,
result => result,
underflow => underflow,
overflow => overflow,
invalid_op => invalid_op,
divide_by_zero => divide_by_zero);
-- synthesis translate_on
 
END fpu_div_a;
 
/trunk/processor/mc/synchronizer.vhd
0,0 → 1,43
library IEEE;
use ieee.std_logic_1164.all;
use work.leval_package.all;
 
-- THANKS TO SINTEF / DAG ROGNLIEN!
-- --------------------------------
-- This code is based on work by Sintef / Dag Rognlien,
-- and shall not be reused under any circumstances without
-- their permission.
 
entity synchronizer is
port (
clk : in std_logic;
ws : in std_logic;
wso : out std_logic
);
 
attribute KEEP_HIERARCHY : string;
attribute KEEP_HIERARCHY of synchronizer: entity is "yes";
-- Do not create SRL16 for synchrnoization (not real FLIP-FLOPS)
attribute shreg_extract : string;
attribute shreg_extract of synchronizer: entity is "no";
-- Do not move logic in between the FLIP-FLOPS
attribute register_balancing : string;
attribute register_balancing of synchronizer: entity is "no";
-- Do not duplicate O register
attribute register_duplication : string;
attribute register_duplication of synchronizer : entity is "no";
 
end entity;
 
architecture behav of synchronizer is
begin
clock1 : process(clk)
variable wsflop : std_logic;
variable syncflop : std_logic;
begin
if rising_edge(clk) then
wso <= wsflop;
wsflop := ws;
end if;
end process;
end architecture;

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.