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

Subversion Repositories rv01_riscv_core

[/] [rv01_riscv_core/] [trunk/] [VHDL/] [RV01_idec.vhd] - Rev 2

Compare with Previous | Blame | View Log

-----------------------------------------------------------------
--                                                             --
-----------------------------------------------------------------
--                                                             --
-- Copyright (C) 2015 Stefano Tonello                          --
--                                                             --
-- This source file may be used and distributed without        --
-- restriction provided that this copyright statement is not   --
-- removed from the file and that any derivative work contains --
-- the original copyright notice and the associated disclaimer.--
--                                                             --
-- THIS SOFTWARE IS PROVIDED ``AS IS'' AND WITHOUT ANY         --
-- EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED   --
-- TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS   --
-- FOR A PARTICULAR PURPOSE. IN NO EVENT SHALL THE AUTHOR      --
-- OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,         --
-- INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES    --
-- (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE   --
-- GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR        --
-- BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF  --
-- LIABILITY, WHETHER IN  CONTRACT, STRICT LIABILITY, OR TORT  --
-- (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT  --
-- OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE         --
-- POSSIBILITY OF SUCH DAMAGE.                                 --
--                                                             --
-----------------------------------------------------------------
 
---------------------------------------------------------------
-- Instruction decoder (stage 1)
---------------------------------------------------------------
 
library IEEE;
use IEEE.std_logic_1164.all;
use IEEE.numeric_std.all;
 
library work;
use work.RV01_CONSTS_PKG.all;
use work.RV01_TYPES_PKG.all;
use work.RV01_FUNCS_PKG.all;
use work.RV01_ARITH_PKG.all;
use work.RV01_IDEC_PKG.all;
use work.RV01_OP_PKG.all;
use work.RV01_CSR_PKG.all;
 
entity RV01_IDEC is
  port(
    INSTR_i : in std_logic_vector(ILEN-1 downto 0);
    IADR_MIS_i : in std_logic;
    IADR_ERR_i : in std_logic;
 
    OPA_PC_o : out std_logic;
    OPB_IMM_o : out std_logic;
    DEC_INSTR_o : out DEC_INSTR_T
  );
end RV01_IDEC;
 
architecture ARC of RV01_IDEC is
 
  signal OPCODE : std_logic_vector(7-1 downto 0);
  signal FUNCT3 : std_logic_vector(3-1 downto 0);
  signal FUNCT7 : std_logic_vector(7-1 downto 0);
  signal RD,RS1,RS2 : RID_T;
  signal IMNMC : INST_MNEMONIC_T;
  signal WRD,RRS1,RRS2,SU,WRD_NZ,WCSR,WCSR_NZ : std_logic;
  signal ALU_OP : ALU_OP_T;
  signal BJ_OP : BJ_OP_T;
  signal LS_OP : LS_OP_T;
  signal CS_OP : CS_OP_T;
  signal IMM : signed(SDLEN-1 downto 0);
  signal RES_SRC : RES_SRC_T;
  signal P0_ONLY,P1_ONLY : std_logic;
  signal IMM12_I,IMM12_S : std_logic_vector(12-1 downto 0);
  signal IMM12_SB : std_logic_vector(13-1 downto 0);
  signal IMM20_U : std_logic_vector(20-1 downto 0);
  signal IMM20_UJ : std_logic_vector(21-1 downto 0);
  signal B7 : std_logic_vector(4-1 downto 0);
  signal EXCP,ILLG,SEQX : std_logic;
  signal SCALL,SBREAK : std_logic;
  signal ECAUSE : std_logic_vector(5-1 downto 0);
  signal RFTCH : std_logic;
 
begin
 
  -- instruction subfields extraction
  process(INSTR_i)
  begin
 
    -- main opcode
    OPCODE <= INSTR_i(6 downto 0);
 
    -- 3-bit function field
    FUNCT3 <= INSTR_i(14 downto 12);
 
    -- 7-bit function field
    FUNCT7 <= INSTR_i(31 downto 25);
 
    -- register identifiers
    RD <= to_integer(to_unsigned(INSTR_i(11 downto 7)));
    RS1 <= to_integer(to_unsigned(INSTR_i(19 downto 15)));
    RS2 <= to_integer(to_unsigned(INSTR_i(24 downto 20)));
 
    -- I-type immediate
    IMM12_I <= INSTR_i(31 downto 20);
 
    -- S-type immediate
    IMM12_S <= INSTR_i(31 downto 25) & INSTR_i(11 downto 7);
 
    -- SB-type immediate
    IMM12_SB <= INSTR_i(31) & INSTR_i(7) & INSTR_i(30 downto 25) & INSTR_i(11 downto 8) & '0';
 
    -- U-type immediate
    IMM20_U <= INSTR_i(31 downto 12);
 
    -- UJ-type immediate
    IMM20_UJ <= INSTR_i(31) & INSTR_i(19 downto 12)& INSTR_i(20) & INSTR_i(30 downto 21) & '0';
 
    -- 7-th byte (used for fence instructions)
    B7 <= INSTR_i(31 downto 28);
 
  end process;
 
  -- instruction mnemonic and operand flags extraction
  process(OPCODE,FUNCT3,FUNCT7,IMM12_I,B7,RS1,RD)
  begin
 
    IMNMC <= IM_BAD_INSTR; -- instruction mnemonic (unique id).
    WCSR <= '0'; -- write CSR flag
    WRD <= '0'; -- write rd flag
    RRS1 <= '0'; -- read rs1 flag
    RRS2 <= '0'; -- read rs2 flag
    SU <= '1'; -- sign/unsigned selector 
    ALU_OP <= ALU_NIL; -- ALU operation type
    BJ_OP <= BJ_NIL; -- B/J operation type
    LS_OP <= LS_NIL; -- L/S operation type
    CS_OP <= CS_NIL; -- CSR operation type
    RES_SRC <= RS_NIL; -- result source
    P0_ONLY <= '0'; -- (can execute on) slot # 0 only flag 
    P1_ONLY <= '0'; -- (can execute on) slot # 1 only flag (never used)
    SEQX <= '0'; -- sequential execution flag
    ILLG <= '1'; -- illegal instruction flag
 
    -- A Mix of priority-based and parallel muxing
    -- logic is used to try to balance logic tree 
    -- depth between main opcodes with many 
    -- instructions (like OP_ALU) and main opcodes
    -- with few instructions (like OP_JAL).
 
    if(OPCODE = OP_ALU) then
 
        -- ALU instructions
        case FUNCT3 is
          when "000" =>
            case FUNCT7 is
              when "0000000" =>
                -- add rd,rs1,rs2
                IMNMC <= IM_ADD;
                RRS1 <= '1';
                RRS2 <= '1';
                WRD <= '1';
                ALU_OP <= ALU_ADD;
                RES_SRC <= RS_PIPEA;
                --P0_ONLY <= '1';
                ILLG <= '0';
              when "0000001" =>
                -- mul rd,rs1,rs2
                IMNMC <= IM_MUL;
                RRS1 <= '1';
                RRS2 <= '1';
                WRD <= '1';
                ALU_OP <= ALU_MUL;
                RES_SRC <= RS_PIPEB;
                P0_ONLY <= '1';
                ILLG <= '0';
              when "0100000" =>
                -- sub rd,rs1,rs2
                IMNMC <= IM_SUB;
                RRS1 <= '1';
                RRS2 <= '1';
                WRD <= '1';
                ALU_OP <= ALU_SUB;
                RES_SRC <= RS_PIPEB; --A;
                P0_ONLY <= '1';
                ILLG <= '0';
              when others =>
                -- invalid instruction
                IMNMC <= IM_BAD_INSTR;
                ILLG <= '1';
            end case;
          when "010" =>
            if(FUNCT7 = "0000000") then
              -- slt rd,rs1,rs2
              IMNMC <= IM_SLT;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              RES_SRC <= RS_PIPEB; --A;
              ALU_OP <= ALU_SLT;
              P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0000001") then
              -- mulhsu rd,rs1,rs2
              IMNMC <= IM_MULHSU;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              SU <= '0';
              ALU_OP <= ALU_MULHSU;
              RES_SRC <= RS_PIPEB;
              P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end if;
          when "011" =>
            if(FUNCT7 = "0000000") then
              -- sltu rd,rs1,rs2
              IMNMC <= IM_SLTU;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              SU <= '0';
              RES_SRC <= RS_PIPEB; --A;
              ALU_OP <= ALU_SLT;
              P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0000001") then
              -- mulhu rd,rs1,rs2
              IMNMC <= IM_MULHU;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              SU <= '0';
              ALU_OP <= ALU_MULHU;
              RES_SRC <= RS_PIPEB;
              P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end if;
          when "100" =>
            if(FUNCT7 = "0000000") then
              -- xor rd,rs1,rs2
              IMNMC <= IM_XOR;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_XOR;
              RES_SRC <= RS_PIPEA; --B;
              --P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0000001") then
              -- div rd,rs1,rs2
              IMNMC <= IM_DIV;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_DIV;
              RES_SRC <= RS_DIVU;
              P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end if;
          when "110" =>
            if(FUNCT7 = "0000000") then
              -- or rd,rs1,rs2
              IMNMC <= IM_OR;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_OR;
              RES_SRC <= RS_PIPEA; --B;
              --P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0000001") then
              -- rem rd,rs1,rs2
              IMNMC <= IM_REM;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_REM;
              RES_SRC <= RS_DIVU;
              P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end if;
          when "111" =>
            if(FUNCT7 = "0000000") then
              -- and rd,rs1,rs2
              IMNMC <= IM_AND;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_AND;
              RES_SRC <= RS_PIPEA; --B;
              --P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0000001") then
              -- remu rd,rs1,rs2
              IMNMC <= IM_REMU;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              SU <= '0';
              ALU_OP <= ALU_REM;
              RES_SRC <= RS_DIVU;
              P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end if;
          when "001" =>
            if(FUNCT7 = "0000000") then
              -- sll rd,rs1,shamnt
              IMNMC <= IM_SLL;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_SHL;
              RES_SRC <= RS_PIPEA; --B;
              --P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0000001") then
              -- mulh rd,rs1,rs2
              IMNMC <= IM_MULH;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_MULH;
              RES_SRC <= RS_PIPEB;
              P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end if;
          when "101" =>
            if(FUNCT7 = "0000000") then
              -- srl rd,rs1,shamnt
              IMNMC <= IM_SRL;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              SU <= '0';
              ALU_OP <= ALU_SHR;
              RES_SRC <= RS_PIPEA; --B;
              --P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0000001") then
              -- divu rd,rs1,rs2
              IMNMC <= IM_DIVU;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              SU <= '0';
              ALU_OP <= ALU_DIV;
              RES_SRC <= RS_DIVU;
              P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0100000") then
              -- sra rd,rs1,shamnt
              IMNMC <= IM_SRA;
              RRS1 <= '1';
              RRS2 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_SHR;
              RES_SRC <= RS_PIPEA; --B;
              --P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end if;
          when others =>
            -- invalid instruction
            ILLG <= '1';
            IMNMC <= IM_BAD_INSTR;
        end case;
 
    elsif(OPCODE = OP_ALUI) then
 
        -- ALU-immediate instructions
        case FUNCT3 is
          when "000" =>
            -- addi rd,rs1,imm12
            IMNMC <= IM_ADDI;
            RRS1 <= '1';
            WRD <= '1';
            RES_SRC <= RS_PIPEA;
            ALU_OP <= ALU_ADD;
            --P0_ONLY <= '1';
            ILLG <= '0';
          when "010" =>
            -- slti rd,rs1,imm12
            IMNMC <= IM_SLTI;
            RRS1 <= '1';
            WRD <= '1';
            RES_SRC <= RS_PIPEB; --A;
            ALU_OP <= ALU_SLT;
            P0_ONLY <= '1';
            ILLG <= '0';
          when "011" =>
            -- sltiu rd,rs1,imm12
            IMNMC <= IM_SLTIU;
            RRS1 <= '1';
            WRD <= '1';
            SU <= '0';
            RES_SRC <= RS_PIPEB; --A;
            ALU_OP <= ALU_SLT;
            P0_ONLY <= '1';
            ILLG <= '0';
          when "100" =>
            -- xori rd,rs1,imm12
            IMNMC <= IM_XORI;
            RRS1 <= '1';
            WRD <= '1';
            ALU_OP <= ALU_XOR;
            RES_SRC <= RS_PIPEA; --B;
            --P0_ONLY <= '1';
            ILLG <= '0';
          when "110" =>
            -- ori rd,rs1,imm12
            IMNMC <= IM_ORI;
            RRS1 <= '1';
            WRD <= '1';
            ALU_OP <= ALU_OR;
            RES_SRC <= RS_PIPEA; --B;
            --P0_ONLY <= '1';
            ILLG <= '0';
          when "111" =>
            -- andi rd,rs1,imm12
            IMNMC <= IM_ANDI;
            RRS1 <= '1';
            WRD <= '1';
            ALU_OP <= ALU_AND;
            RES_SRC <= RS_PIPEA; --B;
            --P0_ONLY <= '1';
            ILLG <= '0';
          when "001" =>
            RES_SRC <= RS_PIPEA; --B;
            if(FUNCT7 = "0000000") then
              -- slli rd,rs1,shamnt
              IMNMC <= IM_SLLI;
              RRS1 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_SHL;
              --P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              ILLG <= '1';
              IMNMC <= IM_BAD_INSTR;
            end if;
          when "101" =>
            if(FUNCT7 = "0000000") then
              -- srli rd,rs1,shamnt
              IMNMC <= IM_SRLI;
              RRS1 <= '1';
              WRD <= '1';
              SU <= '0';
              ALU_OP <= ALU_SHR;
              --P0_ONLY <= '1';
              ILLG <= '0';
            elsif(FUNCT7 = "0100000") then
              -- srai rd,rs1,shamnt
              IMNMC <= IM_SRAI;
              RRS1 <= '1';
              WRD <= '1';
              ALU_OP <= ALU_SHR;
              --P0_ONLY <= '1';
              ILLG <= '0';
            else
              -- invalid instruction
              ILLG <= '1';
              IMNMC <= IM_BAD_INSTR;
            end if;
          when others =>
            -- invalid instruction
            IMNMC <= IM_BAD_INSTR;
            ILLG <= '1';
        end case;
 
    elsif(OPCODE = OP_SYSTEM) then
 
        -- system instructions
        P0_ONLY <= '1';
        case FUNCT3 is
          when "000" =>
            case IMM12_I is
              when X"000" =>
                -- syscall
                IMNMC <= IM_SCALL;
                ILLG <= '0';
              when X"001" =>
                -- break
                IMNMC <= IM_SBREAK;
                ILLG <= '0';
              when X"100" =>
                -- eret
                IMNMC <= IM_ERET;
                ILLG <= '0';
              --when X"102" =>
              --  -- wfi
              --  IMNMC <= IM_WFI;
              --  ILLG <= '0';
              --when X"101" =>
              --  if(RD = 0) then
              --    -- sfrence.vm rs1
              --    IMNMC <= IM_SFENCEVM;
              --    ILLG <= '0';
              --  else
              --    -- invalid instruction
              --    IMNMC <= IM_BAD_INSTR;
              --    ILLG <= '1';
              --  end if;
              when others =>
              -- invalid instruction
              IMNMC <= IM_BAD_INSTR;
              ILLG <= '1';
            end case;
          when "001" =>
            -- csrrw rd,csr,rs1
            IMNMC <= IM_CSRRW;
            RRS1 <= '1';
            WRD <= '1';
            WCSR <= '1';
            CS_OP <= CS_RW;
            SEQX <= '1';
            RES_SRC <= RS_SIU;
            ILLG <= '0';
          when "010" =>
            -- csrrs rd,csr,rs1
            IMNMC <= IM_CSRRS;
            RRS1 <= '1';
            WRD <= '1';
            WCSR <= '1';
            CS_OP <= CS_RS;
            SEQX <= '1';
            RES_SRC <= RS_SIU;
            ILLG <= '0';
          when "011" =>
            -- csrrc rd,csr,rs1
            IMNMC <= IM_CSRRC;
            RRS1 <= '1';
            WRD <= '1';
            WCSR <= '1';
            CS_OP <= CS_RC;
            SEQX <= '1';
            RES_SRC <= RS_SIU;
            ILLG <= '0';
          when "101" =>
            -- csrrwi rd,csr,imm
            IMNMC <= IM_CSRRWI;
            RRS1 <= '1';
            WRD <= '1';
            WCSR <= '1';
            CS_OP <= CS_RWI;
            SEQX <= '1';
            RES_SRC <= RS_SIU;
            ILLG <= '0';
          when "110" =>
            -- csrrsi rd,csr,imm
            IMNMC <= IM_CSRRSI;
            RRS1 <= '1';
            WRD <= '1';
            WCSR <= '1';
            CS_OP <= CS_RSI;
            SEQX <= '1';
            RES_SRC <= RS_SIU;
            ILLG <= '0';
          when "111" =>
            -- csrrci rd,csr,imm
            IMNMC <= IM_CSRRCI;
            RRS1 <= '1';
            WRD <= '1';
            WCSR <= '1';
            CS_OP <= CS_RCI;
            SEQX <= '1';
            RES_SRC <= RS_SIU;
            ILLG <= '0';
          when others =>
            -- invalid instruction
            IMNMC <= IM_BAD_INSTR;
            ILLG <= '1';
        end case;
 
    else
 
      case OPCODE is
 
      when OP_LUI =>
        -- lui rD,imm20
        IMNMC <= IM_LUI;
        WRD <= '1';
        ALU_OP <= ALU_MOVB;
        RES_SRC <= RS_PIPEB;
        P0_ONLY <= '1';
        ILLG <= '0';
 
      when OP_AUIPC =>
        -- auipc rD,imm20
        IMNMC <= IM_AUIPC;
        WRD <= '1';
        ALU_OP <= ALU_AUIPC;
        RES_SRC <= RS_PIPEB;
        P0_ONLY <= '1';
        ILLG <= '0';
 
      when OP_JAL =>
        -- jal rD,imm20
        IMNMC <= IM_JAL;
        WRD <= '1';
        BJ_OP <= BJ_JAL;
        ALU_OP <= ALU_JAL;
        RES_SRC <= RS_PIPEB;
        --P0_ONLY <= '1';
        ILLG <= '0';
 
      when OP_JALR =>
        if(FUNCT3 = "000") then
          -- jalr rD,rs1,imm12
          IMNMC <= IM_JALR;
          RRS1 <= '1';
          WRD <= '1';
          BJ_OP <= BJ_JALR;
          ALU_OP <= ALU_JAL;
          RES_SRC <= RS_PIPEB;
          --P0_ONLY <= '1';
          ILLG <= '0';
        else
          -- invalid instruction
          IMNMC <= IM_BAD_INSTR;
          ILLG <= '1';
        end if;
 
      when OP_BRANCH =>
        --P0_ONLY <= '1';
        -- branch instructions
        case FUNCT3 is
          when "000" =>
            -- beq rs1,rs2,imm12
            IMNMC <= IM_BEQ;
            RRS1 <= '1';
            RRS2 <= '1';
            BJ_OP <= BJ_BEQ;
            ILLG <= '0';
          when "001" =>
            -- bne rs1,rs2,imm12
            IMNMC <= IM_BNE;
            RRS1 <= '1';
            RRS2 <= '1';
            BJ_OP <= BJ_BNE;
            ILLG <= '0';
          when "100" =>
            -- blt rs1,rs2,imm12
            IMNMC <= IM_BLT;
            RRS1 <= '1';
            RRS2 <= '1';
            BJ_OP <= BJ_BLT;
            ILLG <= '0';
          when "101" =>
            -- bge rs1,rs2,imm12
            IMNMC <= IM_BGE;
            RRS1 <= '1';
            RRS2 <= '1';
            BJ_OP <= BJ_BGE;
            ILLG <= '0';
          when "110" =>
            -- bltu rs1,rs2,imm12
            IMNMC <= IM_BLTU;
            RRS1 <= '1';
            RRS2 <= '1';
            SU <= '0';
            BJ_OP <= BJ_BLT;
            ILLG <= '0';
          when "111" =>
            -- bgeu rs1,rs2,imm12
            IMNMC <= IM_BGEU;
            RRS1 <= '1';
            RRS2 <= '1';
            SU <= '0';
            BJ_OP <= BJ_BGE;
            ILLG <= '0';
          when others =>
            -- invalid instruction
            ILLG <= '1';
            IMNMC <= IM_BAD_INSTR;
        end case;
 
      when OP_LOAD =>
        -- load instructions
        RES_SRC <= RS_LSU;
        case FUNCT3 is
          when "000" =>
            -- lb rd,rs1,imm12
            IMNMC <= IM_LB;
            RRS1 <= '1';
            WRD <= '1';
            LS_OP <= LS_LB;
            ILLG <= '0';
          when "001" =>
            -- lh rd,rs1,imm12
            IMNMC <= IM_LH;
            RRS1 <= '1';
            WRD <= '1';
            LS_OP <= LS_LH;
            ILLG <= '0';
          when "010" =>
            -- lw rd,rs1,imm12
            IMNMC <= IM_LW;
            RRS1 <= '1';
            WRD <= '1';
            LS_OP <= LS_LW;
            ILLG <= '0';
          when "100" =>
            -- lbu rd,rs1,imm12
            IMNMC <= IM_LBU;
            RRS1 <= '1';
            WRD <= '1';
            SU <= '0';
            LS_OP <= LS_LB;
            ILLG <= '0';
          when "101" =>
            -- lhu rd,rs1,imm12
            IMNMC <= IM_LHU;
            RRS1 <= '1';
            WRD <= '1';
            SU <= '0';
            LS_OP <= LS_LH;
            ILLG <= '0';
          when others =>
            -- invalid instruction
            IMNMC <= IM_BAD_INSTR;
            ILLG <= '1';
        end case;
 
      when OP_STORE =>
        --P0_ONLY <= '1';
        -- store instructions
        case FUNCT3 is
          when "000" =>
            -- sb rs1,rs2,imm12
            IMNMC <= IM_SB;
            RRS1 <= '1';
            RRS2 <= '1';
            LS_OP <= LS_SB;
            ILLG <= '0';
          when "001" =>
            -- sh rs1,rs2,imm12
            IMNMC <= IM_SH;
            RRS1 <= '1';
            RRS2 <= '1';
            LS_OP <= LS_SH;
            ILLG <= '0';
          when "010" =>
            -- sw rs1,rs2,imm12
            IMNMC <= IM_SW;
            RRS1 <= '1';
            RRS2 <= '1';
            LS_OP <= LS_SW;
            ILLG <= '0';
          when others =>
            -- invalid instruction
            IMNMC <= IM_BAD_INSTR;
            ILLG <= '1';
        end case;
 
      when OP_MISCMEM =>
        P0_ONLY <= '1';
        if(RD = 0 and RS1 = 0) then
          if(FUNCT3 = "000" and B7 = "0000") then
            -- fence
            IMNMC <= IM_FENCE;
            ILLG <= '0';
          elsif(FUNCT3 = "001" and IMM12_I = X"000") then
            -- fence.i
            IMNMC <= IM_FENCEI;
            ILLG <= '0';
          else
            -- invalid instruction
            ILLG <= '1';
            IMNMC <= IM_BAD_INSTR;
          end if;
        else
          -- invalid instruction
          ILLG <= '1';
          IMNMC <= IM_BAD_INSTR;
        end if;
 
      when others =>
        -- invalid instruction
        ILLG <= '1';
        IMNMC <= IM_BAD_INSTR;
 
      end case;
 
    end if;
 
  end process;
 
  -- OPB-as-immediate flag (set to '1' for all instructions
  -- except branch, store and ALU R-type ones)
  OPB_IMM_o <= '0' when (
    OPCODE = OP_BRANCH or
    OPCODE = OP_STORE or
    OPCODE = OP_ALU
  ) else '1';
 
  -- OPA-as-pc flag (set to '1' for jump&link and auipc
  -- instructions)
  OPA_PC_o <= '1' when (
    OPCODE = OP_AUIPC or 
    OPCODE = OP_JAL
    --OPCODE = OP_JAL or 
    --OPCODE = OP_JALR
  ) else '0';
 
  -- immediate operand selector
  process(OPCODE,IMM12_I,IMM12_S,IMM12_SB,IMM20_U,IMM20_UJ)
    variable ZERO_12 : std_logic_vector(12-1 downto 0) := (others => '1');
  begin
    case OPCODE is
      when OP_LUI|OP_AUIPC =>
        IMM(12-1 downto 0) <= (others => '0');
        IMM(SDLEN-1 downto 12) <= to_signed(IMM20_U);
      when OP_JAL => IMM <= EXTS32(IMM20_UJ);
      when OP_BRANCH => IMM <= EXTS32(IMM12_SB);
      when OP_STORE => IMM <= EXTS32(IMM12_S);
      when others => IMM <= EXTS32(IMM12_I); -- OP_ALUI
    end case;
  end process;
 
  -- rd-non-zero rd write flag
  WRD_NZ <= WRD when (RD /= 0) else '0';
 
  -- rs1-non-zero CSR write flag (csrrw writes CSR even
  -- when rs1 is r0).
  WCSR_NZ <= WCSR when (RS1 /= 0 or IMNMC = IM_CSRRW) else '0';
 
  -- Exception flag
  EXCP <= 
    IADR_MIS_i or 
    IADR_ERR_i or 
    ILLG;
 
  -- Exception cause
  ECAUSE <=
   IADRMIS when IADR_MIS_i = '1' else 
   IACCFLT when IADR_ERR_i = '1' else
   ILLGINS;
 
  -- Re-Fetch flag (to be set in IX* stages)
  RFTCH <= '0';
 
  -- decoded instruction
  DEC_INSTR_o <= (
    IMNMC,
    WCSR_NZ,
    WRD_NZ,
    RRS1,
    RRS2,
    RD,
    RS1,
    RS2,
    IMM,
    SU,
    ALU_OP,
    BJ_OP,
    LS_OP,
    CS_OP,
    RES_SRC,
    P0_ONLY,
    P1_ONLY,
    EXCP,
    ECAUSE,
    RFTCH,
    SEQX
  );
 
end ARC;
 

Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

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