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

Subversion Repositories mblite

[/] [mblite/] [trunk/] [hw/] [core/] [decode.vhd] - Diff between revs 6 and 8

Show entire file | Details | Blame | View Log

Rev 6 Rev 8
Line 12... Line 12...
--                           cycle three data values can be read (ra, rb and rd) and one value
--                           cycle three data values can be read (ra, rb and rd) and one value
--                           can be stored.
--                           can be stored.
--
--
----------------------------------------------------------------------------------------------
----------------------------------------------------------------------------------------------
 
 
LIBRARY ieee;
library ieee;
USE ieee.std_logic_1164.ALL;
use ieee.std_logic_1164.all;
USE ieee.std_logic_unsigned.ALL;
use ieee.std_logic_unsigned.all;
 
 
LIBRARY mblite;
library mblite;
USE mblite.config_Pkg.ALL;
use mblite.config_Pkg.all;
USE mblite.core_Pkg.ALL;
use mblite.core_Pkg.all;
USE mblite.std_Pkg.ALL;
use mblite.std_Pkg.all;
 
 
ENTITY decode IS GENERIC
entity decode is generic
(
(
    G_INTERRUPT  : boolean := CFG_INTERRUPT;
    G_INTERRUPT  : boolean := CFG_INTERRUPT;
    G_USE_HW_MUL : boolean := CFG_USE_HW_MUL;
    G_USE_HW_MUL : boolean := CFG_USE_HW_MUL;
    G_USE_BARREL : boolean := CFG_USE_BARREL;
    G_USE_BARREL : boolean := CFG_USE_BARREL;
    G_DEBUG      : boolean := CFG_DEBUG
    G_DEBUG      : boolean := CFG_DEBUG
);
);
PORT
port
(
(
    decode_o : OUT decode_out_type;
    decode_o : out decode_out_type;
    gprf_o   : OUT gprf_out_type;
    gprf_o   : out gprf_out_type;
    decode_i : IN decode_in_type;
    decode_i : in decode_in_type;
    ena_i    : IN std_logic;
    ena_i    : in std_logic;
    rst_i    : IN std_logic;
    rst_i    : in std_logic;
    clk_i    : IN std_logic
    clk_i    : in std_logic
);
);
END decode;
end decode;
 
 
ARCHITECTURE arch OF decode IS
architecture arch of decode is
 
 
    TYPE decode_reg_type IS RECORD
    type decode_reg_type is record
        instruction     : std_logic_vector(CFG_IMEM_WIDTH - 1 DOWNTO 0);
        instruction          : std_logic_vector(CFG_IMEM_WIDTH - 1 downto 0);
        program_counter : std_logic_vector(CFG_IMEM_SIZE - 1 DOWNTO 0);
        program_counter      : std_logic_vector(CFG_IMEM_SIZE - 1 downto 0);
        immediate       : std_logic_vector(15 DOWNTO 0);
        immediate            : std_logic_vector(15 downto 0);
        is_immediate    : std_logic;
        is_immediate    : std_logic;
        msr_interrupt_enable : std_logic;
        msr_interrupt_enable : std_logic;
        interrupt       : std_logic;
        interrupt       : std_logic;
        delay_interrupt : std_logic;
        delay_interrupt : std_logic;
    END RECORD;
    end record;
 
 
    SIGNAL r, rin : decode_out_type;
    signal r, rin     : decode_out_type;
    SIGNAL reg, regin : decode_reg_type;
    signal reg, regin : decode_reg_type;
 
 
    SIGNAL wb_dat_d : std_logic_vector(CFG_DMEM_WIDTH - 1 DOWNTO 0);
    signal wb_dat_d : std_logic_vector(CFG_DMEM_WIDTH - 1 downto 0);
 
 
BEGIN
begin
 
 
    decode_o.imm <= r.imm;
    decode_o.imm <= r.imm;
 
 
    decode_o.ctrl_ex <= r.ctrl_ex;
    decode_o.ctrl_ex <= r.ctrl_ex;
    decode_o.ctrl_mem <= r.ctrl_mem;
    decode_o.ctrl_mem <= r.ctrl_mem;
    decode_o.ctrl_wb <= r.ctrl_wb;
    decode_o.ctrl_wrb <= r.ctrl_wrb;
 
 
    decode_o.reg_a <= r.reg_a;
    decode_o.reg_a <= r.reg_a;
    decode_o.reg_b <= r.reg_b;
    decode_o.reg_b <= r.reg_b;
    decode_o.hazard <= r.hazard;
    decode_o.hazard <= r.hazard;
    decode_o.program_counter <= r.program_counter;
    decode_o.program_counter <= r.program_counter;
 
 
    decode_o.fwd_dec_result <= r.fwd_dec_result;
    decode_o.fwd_dec_result <= r.fwd_dec_result;
    decode_o.fwd_dec <= r.fwd_dec;
    decode_o.fwd_dec <= r.fwd_dec;
 
 
    decode_comb: PROCESS(decode_i,decode_i.ctrl_wb,
    decode_comb: process(decode_i,decode_i.ctrl_wrb,
                         decode_i.ctrl_mem_wb,
                         decode_i.ctrl_mem_wrb,
                         decode_i.ctrl_mem_wb.transfer_size,
                         decode_i.instruction,
 
                         decode_i.ctrl_mem_wrb.transfer_size,
                         r,r.ctrl_ex,r.ctrl_mem,
                         r,r.ctrl_ex,r.ctrl_mem,
                         r.ctrl_mem.transfer_size,r.ctrl_wb,
                         r.ctrl_mem.transfer_size,r.ctrl_wrb,
 
                         r.ctrl_wrb.reg_d,
                         r.fwd_dec,reg)
                         r.fwd_dec,reg)
 
 
        VARIABLE v : decode_out_type;
        variable v : decode_out_type;
        VARIABLE v_reg : decode_reg_type;
        variable v_reg : decode_reg_type;
        VARIABLE opcode : std_logic_vector(5 DOWNTO 0);
        variable opcode : std_logic_vector(5 downto 0);
        VARIABLE instruction : std_logic_vector(CFG_IMEM_WIDTH - 1 DOWNTO 0);
        variable instruction : std_logic_vector(CFG_IMEM_WIDTH - 1 downto 0);
        VARIABLE program_counter : std_logic_vector(CFG_IMEM_SIZE - 1 DOWNTO 0);
        variable program_counter : std_logic_vector(CFG_IMEM_SIZE - 1 downto 0);
        VARIABLE mem_result : std_logic_vector(CFG_DMEM_WIDTH - 1 DOWNTO 0);
        variable mem_result : std_logic_vector(CFG_DMEM_WIDTH - 1 downto 0);
 
 
    BEGIN
    begin
        v := r;
        v := r;
        v_reg := reg;
        v_reg := reg;
 
 
        -- Default register values (NOP)
        -- Default register values (NOP)
        v_reg.immediate := (OTHERS => '0');
        v_reg.immediate := (others => '0');
        v_reg.is_immediate := '0';
        v_reg.is_immediate := '0';
        v_reg.program_counter := decode_i.program_counter;
        v_reg.program_counter := decode_i.program_counter;
        v_reg.instruction := decode_i.instruction;
        v_reg.instruction := decode_i.instruction;
 
 
        IF decode_i.ctrl_mem_wb.mem_read = '1' THEN
        if decode_i.ctrl_mem_wrb.mem_read = '1' then
            mem_result := align_mem_load(decode_i.mem_result, decode_i.ctrl_mem_wb.transfer_size, decode_i.alu_result(1 DOWNTO 0));
            mem_result := align_mem_load(decode_i.mem_result, decode_i.ctrl_mem_wrb.transfer_size, decode_i.alu_result(1 downto 0));
        ELSE
        else
            mem_result := decode_i.alu_result;
            mem_result := decode_i.alu_result;
        END IF;
        end if;
 
 
        wb_dat_d <= mem_result;
        wb_dat_d <= mem_result;
 
 
        IF G_INTERRUPT = true THEN
        if G_INTERRUPT = true then
            v_reg.delay_interrupt := '0';
            v_reg.delay_interrupt := '0';
        END IF;
        end if;
 
 
        IF CFG_REG_FWD_WB = true THEN
        if CFG_REG_FWD_WRB = true then
            v.fwd_dec_result    := mem_result;
            v.fwd_dec_result    := mem_result;
            v.fwd_dec           := decode_i.ctrl_wb;
            v.fwd_dec           := decode_i.ctrl_wrb;
        ELSE
        else
            v.fwd_dec_result    := (OTHERS => '0');
            v.fwd_dec_result    := (others => '0');
            v.fwd_dec.reg_d     := (OTHERS => '0');
            v.fwd_dec.reg_d     := (others => '0');
            v.fwd_dec.reg_write := '0';
            v.fwd_dec.reg_write := '0';
        END IF;
        end if;
 
 
        IF (NOT decode_i.flush_id AND r.ctrl_mem.mem_read AND (compare(decode_i.instruction(20 DOWNTO 16), r.ctrl_wb.reg_d) OR compare(decode_i.instruction(15 DOWNTO 11), r.ctrl_wb.reg_d))) = '1' THEN
        if (not decode_i.flush_id and r.ctrl_mem.mem_read and (compare(decode_i.instruction(20 downto 16), r.ctrl_wrb.reg_d) or compare(decode_i.instruction(15 downto 11), r.ctrl_wrb.reg_d))) = '1' then
        -- A hazard occurred on register a or b
        -- A hazard occurred on register a or b
 
 
            -- set current instruction and program counter to 0
            -- set current instruction and program counter to 0
            instruction := (OTHERS => '0');
            instruction := (others => '0');
            program_counter := (OTHERS => '0');
            program_counter := (others => '0');
 
 
            v.hazard := '1';
            v.hazard := '1';
 
 
        ELSIF CFG_MEM_FWD_WB = false AND (NOT decode_i.flush_id AND r.ctrl_mem.mem_read AND compare(decode_i.instruction(25 DOWNTO 21), r.ctrl_wb.reg_d)) = '1' THEN
        elsif CFG_MEM_FWD_WRB = false and (not decode_i.flush_id and r.ctrl_mem.mem_read and compare(decode_i.instruction(25 downto 21), r.ctrl_wrb.reg_d)) = '1' then
        -- A hazard occurred on register d
        -- A hazard occurred on register d
 
 
            -- set current instruction and program counter to 0
            -- set current instruction and program counter to 0
            instruction := (OTHERS => '0');
            instruction := (others => '0');
            program_counter := (OTHERS => '0');
            program_counter := (others => '0');
 
 
            v.hazard := '1';
            v.hazard := '1';
 
 
        ELSIF r.hazard = '1' THEN
        elsif r.hazard = '1' then
        -- Recover from hazard. Insert latched instruction
        -- Recover from hazard. Insert latched instruction
 
 
            instruction := reg.instruction;
            instruction := reg.instruction;
            program_counter := reg.program_counter;
            program_counter := reg.program_counter;
            v.hazard := '0';
            v.hazard := '0';
 
 
        ELSE
        else
 
 
            instruction := decode_i.instruction;
            instruction := decode_i.instruction;
            program_counter := decode_i.program_counter;
            program_counter := decode_i.program_counter;
            v.hazard := '0';
            v.hazard := '0';
 
 
        END IF;
        end if;
 
 
        v.program_counter := program_counter;
        v.program_counter := program_counter;
        opcode := instruction(31 DOWNTO 26);
        opcode := instruction(31 downto 26);
        v.ctrl_wb.reg_d := instruction(25 DOWNTO 21);
        v.ctrl_wrb.reg_d := instruction(25 downto 21);
        v.reg_a := instruction(20 DOWNTO 16);
        v.reg_a := instruction(20 downto 16);
        v.reg_b := instruction(15 DOWNTO 11);
        v.reg_b := instruction(15 downto 11);
 
 
        -- SET IMM value
        -- SET IMM value
        IF reg.is_immediate = '1' THEN
        if reg.is_immediate = '1' then
            v.imm := reg.immediate & instruction(15 DOWNTO 0);
            v.imm := reg.immediate & instruction(15 downto 0);
        ELSE
        else
            v.imm := sign_extend(instruction(15 DOWNTO 0), instruction(15), 32);
            v.imm := sign_extend(instruction(15 downto 0), instruction(15), 32);
        END IF;
        end if;
 
 
        -- Register if an interrupt occurs
        -- Register if an interrupt occurs
        IF G_INTERRUPT = true THEN
        if G_INTERRUPT = true then
            IF v_reg.msr_interrupt_enable = '1' AND decode_i.interrupt = '1' THEN
            if v_reg.msr_interrupt_enable = '1' and decode_i.interrupt = '1' then
                v_reg.interrupt := '1';
                v_reg.interrupt := '1';
                v_reg.msr_interrupt_enable := '0';
                v_reg.msr_interrupt_enable := '0';
            END IF;
            end if;
        END IF;
        end if;
 
 
        v.ctrl_ex.alu_op := ALU_ADD;
        v.ctrl_ex.alu_op := ALU_ADD;
        v.ctrl_ex.alu_src_a := ALU_SRC_REGA;
        v.ctrl_ex.alu_src_a := ALU_SRC_REGA;
        v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
        v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
        v.ctrl_ex.operation := '0';
        v.ctrl_ex.operation := '0';
        v.ctrl_ex.carry := CARRY_ZERO;
        v.ctrl_ex.carry := CARRY_ZERO;
        v.ctrl_ex.carry_keep := CARRY_NOT_KEEP;
        v.ctrl_ex.carry_keep := CARRY_KEEP;
        v.ctrl_ex.delay := '0';
        v.ctrl_ex.delay := '0';
        v.ctrl_ex.branch_cond := NOP;
        v.ctrl_ex.branch_cond := NOP;
        v.ctrl_mem.mem_write := '0';
        v.ctrl_mem.mem_write := '0';
        v.ctrl_mem.transfer_size := WORD;
        v.ctrl_mem.transfer_size := WORD;
        v.ctrl_mem.mem_read := '0';
        v.ctrl_mem.mem_read := '0';
        v.ctrl_wb.reg_write := '0';
        v.ctrl_wrb.reg_write := '0';
 
 
        IF G_INTERRUPT = true AND (v_reg.interrupt = '1' AND reg.delay_interrupt = '0' AND decode_i.flush_id = '0' AND v.hazard = '0' AND r.ctrl_ex.delay = '0' AND reg.is_immediate = '0') THEN
        if G_INTERRUPT = true and (v_reg.interrupt = '1' and reg.delay_interrupt = '0' and decode_i.flush_id = '0' and v.hazard = '0' and r.ctrl_ex.delay = '0' and reg.is_immediate = '0') then
        -- IF an interrupt occured
        -- IF an interrupt occured
        --    AND the current instruction is not a branch or return instruction,
        --    AND the current instruction is not a branch or return instruction,
        --    AND the current instruction is not in a delay slot,
        --    AND the current instruction is not in a delay slot,
        --    AND this is instruction is not preceded by an IMM instruction, than handle the interrupt.
        --    AND this is instruction is not preceded by an IMM instruction, than handle the interrupt.
            v_reg.msr_interrupt_enable := '0';
            v_reg.msr_interrupt_enable := '0';
            v_reg.interrupt := '0';
            v_reg.interrupt := '0';
 
 
            v.reg_a := (OTHERS => '0');
            v.reg_a := (others => '0');
            v.reg_b := (OTHERS => '0');
            v.reg_b := (others => '0');
 
 
            v.imm   := X"00000010";
            v.imm   := X"00000010";
            v.ctrl_wb.reg_d := "01110";
            v.ctrl_wrb.reg_d := "01110";
 
 
            v.ctrl_ex.branch_cond := BNC;
            v.ctrl_ex.branch_cond := BNC;
            v.ctrl_ex.alu_src_a := ALU_SRC_ZERO;
            v.ctrl_ex.alu_src_a := ALU_SRC_ZERO;
            v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            v.ctrl_wb.reg_write := '1';
            v.ctrl_wrb.reg_write := '1';
 
 
        ELSIF (decode_i.flush_id OR v.hazard) = '1' THEN
        elsif (decode_i.flush_id or v.hazard) = '1' then
            -- clearing these registers is not necessary, but facilitates debugging.
            -- clearing these registers is not necessary, but facilitates debugging.
            -- On the other hand performance improves when disabled.
            -- On the other hand performance improves when disabled.
            IF G_DEBUG = true THEN
            if G_DEBUG = true then
                v.program_counter := (OTHERS => '0');
                v.program_counter := (others => '0');
                v.ctrl_wb.reg_d   := (OTHERS => '0');
                v.ctrl_wrb.reg_d  := (others => '0');
                v.reg_a           := (OTHERS => '0');
                v.reg_a           := (others => '0');
                v.reg_b           := (OTHERS => '0');
                v.reg_b           := (others => '0');
                v.imm             := (OTHERS => '0');
                v.imm             := (others => '0');
            END IF;
            end if;
 
 
        ELSIF is_zero(opcode(5 DOWNTO 4)) = '1' THEN
        elsif is_zero(opcode(5 downto 4)) = '1' then
        -- ADD, SUBTRACT OR COMPARE
        -- ADD, SUBTRACT OR COMPARE
 
 
            -- Alu operation
            -- Alu operation
            v.ctrl_ex.alu_op := ALU_ADD;
            v.ctrl_ex.alu_op := ALU_ADD;
 
 
            -- Source operand A
            -- Source operand A
            IF opcode(0) = '1' THEN
            if opcode(0) = '1' then
                v.ctrl_ex.alu_src_a := ALU_SRC_NOT_REGA;
                v.ctrl_ex.alu_src_a := ALU_SRC_NOT_REGA;
            ELSE
            else
                v.ctrl_ex.alu_src_a := ALU_SRC_REGA;
                v.ctrl_ex.alu_src_a := ALU_SRC_REGA;
            END IF;
            end if;
 
 
            -- Source operand B
            -- Source operand B
            IF opcode(3) = '1' THEN
            if opcode(3) = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            ELSE
            else
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
            END IF;
            end if;
 
 
            IF (compare(opcode, "000101") AND instruction(1)) = '1' THEN
            if (compare(opcode, "000101") and instruction(1)) = '1' then
                v.ctrl_ex.operation := '1';
                v.ctrl_ex.operation := '1';
            END IF;
            end if;
 
 
            -- Carry
            -- Carry
            CASE opcode(1 DOWNTO 0) IS
            case opcode(1 downto 0) is
                WHEN "00" => v.ctrl_ex.carry := CARRY_ZERO;
                when "00" => v.ctrl_ex.carry := CARRY_ZERO;
                WHEN "01" => v.ctrl_ex.carry := CARRY_ONE;
                when "01" => v.ctrl_ex.carry := CARRY_ONE;
                WHEN OTHERS => v.ctrl_ex.carry := CARRY_ALU;
                when others => v.ctrl_ex.carry := CARRY_ALU;
            END CASE;
            end case;
 
 
            -- Carry keep
            -- Carry keep
            IF opcode(2) = '1' THEN
            if opcode(2) = '1' then
                v.ctrl_ex.carry_keep := CARRY_KEEP;
                v.ctrl_ex.carry_keep := CARRY_KEEP;
            ELSE
            else
                v.ctrl_ex.carry_keep := CARRY_NOT_KEEP;
                v.ctrl_ex.carry_keep := CARRY_NOT_KEEP;
            END IF;
            end if;
 
 
            -- Flag writeback if reg_d != 0
            -- Flag writeback if reg_d != 0
            v.ctrl_wb.reg_write := is_not_zero(v.ctrl_wb.reg_d);
            v.ctrl_wrb.reg_write := is_not_zero(v.ctrl_wrb.reg_d);
 
 
        ELSIF (compare(opcode(5 DOWNTO 2), "1000") OR compare(opcode(5 DOWNTO 2), "1010")) = '1' THEN
        elsif (compare(opcode(5 downto 2), "1000") or compare(opcode(5 downto 2), "1010")) = '1' then
        -- OR, AND, XOR, ANDN
        -- OR, AND, XOR, ANDN
        -- ORI, ANDI, XORI, ANDNI
        -- ORI, ANDI, XORI, ANDNI
            CASE opcode(1 DOWNTO 0) IS
            case opcode(1 downto 0) is
                WHEN "00" => v.ctrl_ex.alu_op := ALU_OR;
                when "00" => v.ctrl_ex.alu_op := ALU_OR;
                WHEN "10" => v.ctrl_ex.alu_op := ALU_XOR;
                when "10" => v.ctrl_ex.alu_op := ALU_XOR;
                WHEN OTHERS => v.ctrl_ex.alu_op := ALU_AND;
                when others => v.ctrl_ex.alu_op := ALU_AND;
            END CASE;
            end case;
 
 
            IF opcode(3) = '1' AND compare(opcode(1 DOWNTO 0), "11") = '1' THEN
            if opcode(3) = '1' and compare(opcode(1 downto 0), "11") = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_NOT_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_NOT_IMM;
            ELSIF opcode(3) = '1' THEN
            elsif opcode(3) = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            ELSIF opcode(3) = '0' AND compare(opcode(1 DOWNTO 0), "11") = '1' THEN
            elsif opcode(3) = '0' and compare(opcode(1 downto 0), "11") = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_NOT_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_NOT_REGB;
            ELSE
            else
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
            END IF;
            end if;
 
 
            -- Flag writeback if reg_d != 0
            -- Flag writeback if reg_d != 0
            v.ctrl_wb.reg_write := is_not_zero(v.ctrl_wb.reg_d);
            v.ctrl_wrb.reg_write := is_not_zero(v.ctrl_wrb.reg_d);
 
 
        ELSIF compare(opcode, "101100") = '1' THEN
        elsif compare(opcode, "101100") = '1' then
        -- IMM instruction
        -- IMM instruction
            v_reg.immediate := instruction(15 DOWNTO 0);
            v_reg.immediate := instruction(15 downto 0);
            v_reg.is_immediate := '1';
            v_reg.is_immediate := '1';
 
 
        ELSIF compare(opcode, "100100") = '1' THEN
        elsif compare(opcode, "100100") = '1' then
        -- SHIFT, SIGN EXTEND
        -- SHIFT, SIGN EXTEND
            IF compare(instruction(6 DOWNTO 5), "11") = '1' THEN
            if compare(instruction(6 downto 5), "11") = '1' then
                IF instruction(0) = '1' THEN
                if instruction(0) = '1' then
                    v.ctrl_ex.alu_op:= ALU_SEXT16;
                    v.ctrl_ex.alu_op:= ALU_SEXT16;
                ELSE
                else
                    v.ctrl_ex.alu_op:= ALU_SEXT8;
                    v.ctrl_ex.alu_op:= ALU_SEXT8;
                END IF;
                end if;
            ELSE
            else
                v.ctrl_ex.alu_op:= ALU_SHIFT;
                v.ctrl_ex.alu_op:= ALU_SHIFT;
                CASE instruction(6 DOWNTO 5) IS
                v.ctrl_ex.carry_keep := CARRY_NOT_KEEP;
                    WHEN "10"   => v.ctrl_ex.carry := CARRY_ZERO;
                case instruction(6 downto 5) is
                    WHEN "01"   => v.ctrl_ex.carry := CARRY_ALU;
                    when "10"   => v.ctrl_ex.carry := CARRY_ZERO;
                    WHEN OTHERS => v.ctrl_ex.carry := CARRY_ARITH;
                    when "01"   => v.ctrl_ex.carry := CARRY_ALU;
                END CASE;
                    when others => v.ctrl_ex.carry := CARRY_ARITH;
            END IF;
                end case;
 
            end if;
 
 
            -- Flag writeback if reg_d != 0
            -- Flag writeback if reg_d != 0
            v.ctrl_wb.reg_write := is_not_zero(v.ctrl_wb.reg_d);
            v.ctrl_wrb.reg_write := is_not_zero(v.ctrl_wrb.reg_d);
 
 
        ELSIF (compare(opcode, "100110") OR compare(opcode, "101110")) = '1' THEN
        elsif (compare(opcode, "100110") or compare(opcode, "101110")) = '1' then
        -- BRANCH UNCONDITIONAL
        -- BRANCH UNCONDITIONAL
 
 
            v.ctrl_ex.branch_cond := BNC;
            v.ctrl_ex.branch_cond := BNC;
 
 
            IF opcode(3) = '1' THEN
            if opcode(3) = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            ELSE
            else
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
            END IF;
            end if;
 
 
            -- WRITE THE RESULT ALSO TO REGISTER D
            -- WRITE THE RESULT ALSO TO REGISTER D
            IF v.reg_a(2) = '1' THEN
            if v.reg_a(2) = '1' then
                -- Flag writeback if reg_d != 0
                -- Flag writeback if reg_d != 0
                v.ctrl_wb.reg_write := is_not_zero(v.ctrl_wb.reg_d);
                v.ctrl_wrb.reg_write := is_not_zero(v.ctrl_wrb.reg_d);
            END IF;
            end if;
 
 
            IF v.reg_a(3) = '1' THEN
            if v.reg_a(3) = '1' then
                v.ctrl_ex.alu_src_a := ALU_SRC_ZERO;
                v.ctrl_ex.alu_src_a := ALU_SRC_ZERO;
            ELSE
            else
                v.ctrl_ex.alu_src_a := ALU_SRC_PC;
                v.ctrl_ex.alu_src_a := ALU_SRC_PC;
            END IF;
            end if;
 
 
            IF G_INTERRUPT = true THEN
            if G_INTERRUPT = true then
                v_reg.delay_interrupt := '1';
                v_reg.delay_interrupt := '1';
            END IF;
            end if;
            v.ctrl_ex.delay := v.reg_a(4);
            v.ctrl_ex.delay := v.reg_a(4);
 
 
        ELSIF (compare(opcode, "100111") OR compare(opcode, "101111")) = '1' THEN
        elsif (compare(opcode, "100111") or compare(opcode, "101111")) = '1' then
        -- BRANCH CONDITIONAL
        -- BRANCH CONDITIONAL
            v.ctrl_ex.alu_op := ALU_ADD;
            v.ctrl_ex.alu_op := ALU_ADD;
            v.ctrl_ex.alu_src_a := ALU_SRC_PC;
            v.ctrl_ex.alu_src_a := ALU_SRC_PC;
 
 
            IF opcode(3) = '1' THEN
            if opcode(3) = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            ELSE
            else
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
            END IF;
            end if;
 
 
            CASE v.ctrl_wb.reg_d(2 DOWNTO 0) IS
            case v.ctrl_wrb.reg_d(2 downto 0) is
                WHEN "000"  => v.ctrl_ex.branch_cond := BEQ;
                when "000"  => v.ctrl_ex.branch_cond := BEQ;
                WHEN "001"  => v.ctrl_ex.branch_cond := BNE;
                when "001"  => v.ctrl_ex.branch_cond := BNE;
                WHEN "010"  => v.ctrl_ex.branch_cond := BLT;
                when "010"  => v.ctrl_ex.branch_cond := BLT;
                WHEN "011"  => v.ctrl_ex.branch_cond := BLE;
                when "011"  => v.ctrl_ex.branch_cond := BLE;
                WHEN "100"  => v.ctrl_ex.branch_cond := BGT;
                when "100"  => v.ctrl_ex.branch_cond := BGT;
                WHEN OTHERS => v.ctrl_ex.branch_cond := BGE;
                when others => v.ctrl_ex.branch_cond := BGE;
            END CASE;
            end case;
 
 
            IF G_INTERRUPT = true THEN
            if G_INTERRUPT = true then
                v_reg.delay_interrupt := '1';
                v_reg.delay_interrupt := '1';
            END IF;
            end if;
            v.ctrl_ex.delay := v.ctrl_wb.reg_d(4);
            v.ctrl_ex.delay := v.ctrl_wrb.reg_d(4);
 
 
        ELSIF compare(opcode, "101101") = '1' THEN
        elsif compare(opcode, "101101") = '1' then
        -- RETURN
        -- RETURN
 
 
            v.ctrl_ex.branch_cond := BNC;
            v.ctrl_ex.branch_cond := BNC;
            v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            v.ctrl_ex.delay := '1';
            v.ctrl_ex.delay := '1';
 
 
            IF G_INTERRUPT = true THEN
            if G_INTERRUPT = true then
                IF v.ctrl_wb.reg_d(0) = '1' THEN
                if v.ctrl_wrb.reg_d(0) = '1' then
                    v_reg.msr_interrupt_enable := '1';
                    v_reg.msr_interrupt_enable := '1';
                END IF;
                end if;
                v_reg.delay_interrupt := '1';
                v_reg.delay_interrupt := '1';
            END IF;
            end if;
 
 
        ELSIF compare(opcode(5 DOWNTO 4), "11") = '1' THEN
        elsif compare(opcode(5 downto 4), "11") = '1' then
            -- SW, LW
            -- SW, LW
            v.ctrl_ex.alu_op := ALU_ADD;
            v.ctrl_ex.alu_op := ALU_ADD;
            v.ctrl_ex.alu_src_a := ALU_SRC_REGA;
            v.ctrl_ex.alu_src_a := ALU_SRC_REGA;
 
 
            IF opcode(3) = '1' THEN
            if opcode(3) = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            ELSE
            else
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
            END IF;
            end if;
 
 
            v.ctrl_ex.carry := CARRY_ZERO;
            v.ctrl_ex.carry := CARRY_ZERO;
 
 
            IF opcode(2) = '1' THEN
            if opcode(2) = '1' then
                -- Store
                -- Store
                v.ctrl_mem.mem_write := '1';
                v.ctrl_mem.mem_write := '1';
                v.ctrl_mem.mem_read := '0';
                v.ctrl_mem.mem_read := '0';
                v.ctrl_wb.reg_write := '0';
                v.ctrl_wrb.reg_write := '0';
            ELSE
            else
                -- Load
                -- Load
                v.ctrl_mem.mem_write := '0';
                v.ctrl_mem.mem_write := '0';
                v.ctrl_mem.mem_read := '1';
                v.ctrl_mem.mem_read := '1';
                v.ctrl_wb.reg_write := is_not_zero(v.ctrl_wb.reg_d);
                v.ctrl_wrb.reg_write := is_not_zero(v.ctrl_wrb.reg_d);
            END IF;
            end if;
 
 
            CASE opcode(1 DOWNTO 0) IS
            case opcode(1 downto 0) is
                WHEN "00" => v.ctrl_mem.transfer_size := BYTE;
                when "00" => v.ctrl_mem.transfer_size := BYTE;
                WHEN "01" => v.ctrl_mem.transfer_size := HALFWORD;
                when "01" => v.ctrl_mem.transfer_size := HALFWORD;
                WHEN OTHERS => v.ctrl_mem.transfer_size := WORD;
                when others => v.ctrl_mem.transfer_size := WORD;
            END CASE;
            end case;
 
 
            v.ctrl_ex.delay := '0';
            v.ctrl_ex.delay := '0';
 
 
        ELSIF G_USE_HW_MUL = true AND (compare(opcode, "010000") OR compare(opcode, "011000")) = '1' THEN
        elsif G_USE_HW_MUL = true and (compare(opcode, "010000") or compare(opcode, "011000")) = '1' then
 
 
            v.ctrl_ex.alu_op := ALU_MUL;
            v.ctrl_ex.alu_op := ALU_MUL;
 
 
            IF opcode(3) = '1' THEN
            if opcode(3) = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            ELSE
            else
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
            END IF;
            end if;
 
 
            v.ctrl_wb.reg_write := is_not_zero(v.ctrl_wb.reg_d);
            v.ctrl_wrb.reg_write := is_not_zero(v.ctrl_wrb.reg_d);
 
 
        ELSIF G_USE_BARREL = true AND (compare(opcode, "010001") OR compare(opcode, "011001")) = '1' THEN
        elsif G_USE_BARREL = true and (compare(opcode, "010001") or compare(opcode, "011001")) = '1' then
 
 
            v.ctrl_ex.alu_op := ALU_BS;
            v.ctrl_ex.alu_op := ALU_BS;
 
 
            IF opcode(3) = '1' THEN
            if opcode(3) = '1' then
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
                v.ctrl_ex.alu_src_b := ALU_SRC_IMM;
            ELSE
            else
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
                v.ctrl_ex.alu_src_b := ALU_SRC_REGB;
            END IF;
            end if;
 
 
            v.ctrl_wb.reg_write := is_not_zero(v.ctrl_wb.reg_d);
            v.ctrl_wrb.reg_write := is_not_zero(v.ctrl_wrb.reg_d);
 
 
        ELSE
        else
            -- UNKNOWN OPCODE
            -- UNKNOWN OPCODE
            NULL;
            null;
        END IF;
        end if;
 
 
        rin <= v;
        rin <= v;
        regin <= v_reg;
        regin <= v_reg;
 
 
    END PROCESS;
    end process;
 
 
    decode_seq: PROCESS(clk_i)
    decode_seq: process(clk_i)
        PROCEDURE proc_reset_decode IS
        procedure proc_reset_decode is
        BEGIN
        begin
            r.reg_a                     <= (OTHERS => '0');
            r.reg_a                  <= (others => '0');
            r.reg_b                     <= (OTHERS => '0');
            r.reg_b                  <= (others => '0');
            r.imm                       <= (OTHERS => '0');
            r.imm                    <= (others => '0');
            r.program_counter           <= (OTHERS => '0');
            r.program_counter        <= (others => '0');
            r.hazard                    <= '0';
            r.hazard                    <= '0';
            r.ctrl_ex.alu_op            <= ALU_ADD;
            r.ctrl_ex.alu_op            <= ALU_ADD;
            r.ctrl_ex.alu_src_a         <= ALU_SRC_REGA;
            r.ctrl_ex.alu_src_a         <= ALU_SRC_REGA;
            r.ctrl_ex.alu_src_b         <= ALU_SRC_REGB;
            r.ctrl_ex.alu_src_b         <= ALU_SRC_REGB;
            r.ctrl_ex.operation         <= '0';
            r.ctrl_ex.operation         <= '0';
Line 455... Line 458...
            r.ctrl_ex.delay             <= '0';
            r.ctrl_ex.delay             <= '0';
            r.ctrl_ex.branch_cond       <= NOP;
            r.ctrl_ex.branch_cond       <= NOP;
            r.ctrl_mem.mem_write        <= '0';
            r.ctrl_mem.mem_write        <= '0';
            r.ctrl_mem.transfer_size    <= WORD;
            r.ctrl_mem.transfer_size    <= WORD;
            r.ctrl_mem.mem_read         <= '0';
            r.ctrl_mem.mem_read         <= '0';
            r.ctrl_wb.reg_d             <= (OTHERS => '0');
            r.ctrl_wrb.reg_d          <= (others => '0');
            r.ctrl_wb.reg_write         <= '0';
            r.ctrl_wrb.reg_write      <= '0';
            r.fwd_dec_result            <= (OTHERS => '0');
            r.fwd_dec_result         <= (others => '0');
            r.fwd_dec.reg_d             <= (OTHERS => '0');
            r.fwd_dec.reg_d          <= (others => '0');
            r.fwd_dec.reg_write         <= '0';
            r.fwd_dec.reg_write         <= '0';
            reg.instruction             <= (OTHERS => '0');
            reg.instruction          <= (others => '0');
            reg.program_counter         <= (OTHERS => '0');
            reg.program_counter      <= (others => '0');
            reg.immediate               <= (OTHERS => '0');
            reg.immediate            <= (others => '0');
            reg.is_immediate            <= '0';
            reg.is_immediate            <= '0';
            reg.msr_interrupt_enable    <= '1';
            reg.msr_interrupt_enable    <= '1';
            reg.interrupt               <= '0';
            reg.interrupt               <= '0';
            reg.delay_interrupt         <= '0';
            reg.delay_interrupt         <= '0';
        END PROCEDURE proc_reset_decode;
        end procedure proc_reset_decode;
    BEGIN
    begin
        IF rising_edge(clk_i) THEN
        if rising_edge(clk_i) then
            IF rst_i = '1' THEN
            if rst_i = '1' then
                proc_reset_decode;
                proc_reset_decode;
            ELSIF ena_i = '1' THEN
            elsif ena_i = '1' then
                r <= rin;
                r <= rin;
                reg <= regin;
                reg <= regin;
            END IF;
            end if;
        END IF;
        end if;
    END PROCESS;
    end process;
 
 
    gprf0 : gprf PORT MAP
    gprf0 : gprf port map
    (
    (
        gprf_o         => gprf_o,
        gprf_o         => gprf_o,
        gprf_i.adr_a_i => rin.reg_a,
        gprf_i.adr_a_i => rin.reg_a,
        gprf_i.adr_b_i => rin.reg_b,
        gprf_i.adr_b_i => rin.reg_b,
        gprf_i.adr_d_i => rin.ctrl_wb.reg_d,
        gprf_i.adr_d_i => rin.ctrl_wrb.reg_d,
        gprf_i.dat_w_i => wb_dat_d,
        gprf_i.dat_w_i => wb_dat_d,
        gprf_i.adr_w_i => decode_i.ctrl_wb.reg_d,
        gprf_i.adr_w_i => decode_i.ctrl_wrb.reg_d,
        gprf_i.wre_i   => decode_i.ctrl_wb.reg_write,
        gprf_i.wre_i   => decode_i.ctrl_wrb.reg_write,
        ena_i          => ena_i,
        ena_i          => ena_i,
        clk_i          => clk_i
        clk_i          => clk_i
    );
    );
END arch;
end arch;
 
 
 No newline at end of file
 No newline at end of file

powered by: WebSVN 2.1.0

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