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

Subversion Repositories neorv32

[/] [neorv32/] [trunk/] [rtl/] [core/] [neorv32_cpu_control.vhd] - Diff between revs 38 and 39

Go to most recent revision | Show entire file | Details | Blame | View Log

Rev 38 Rev 39
Line 48... Line 48...
  generic (
  generic (
    -- General --
    -- General --
    HW_THREAD_ID                 : std_ulogic_vector(31 downto 0):= x"00000000"; -- hardware thread id
    HW_THREAD_ID                 : std_ulogic_vector(31 downto 0):= x"00000000"; -- hardware thread id
    CPU_BOOT_ADDR                : std_ulogic_vector(31 downto 0):= x"00000000"; -- cpu boot address
    CPU_BOOT_ADDR                : std_ulogic_vector(31 downto 0):= x"00000000"; -- cpu boot address
    -- RISC-V CPU Extensions --
    -- RISC-V CPU Extensions --
 
    CPU_EXTENSION_RISCV_A        : boolean := false; -- implement atomic extension?
    CPU_EXTENSION_RISCV_C        : boolean := false; -- implement compressed extension?
    CPU_EXTENSION_RISCV_C        : boolean := false; -- implement compressed extension?
    CPU_EXTENSION_RISCV_E        : boolean := false; -- implement embedded RF extension?
    CPU_EXTENSION_RISCV_E        : boolean := false; -- implement embedded RF extension?
    CPU_EXTENSION_RISCV_M        : boolean := false; -- implement muld/div extension?
    CPU_EXTENSION_RISCV_M        : boolean := false; -- implement muld/div extension?
    CPU_EXTENSION_RISCV_U        : boolean := false; -- implement user mode extension?
    CPU_EXTENSION_RISCV_U        : boolean := false; -- implement user mode extension?
    CPU_EXTENSION_RISCV_Zicsr    : boolean := true;  -- implement CSR system?
    CPU_EXTENSION_RISCV_Zicsr    : boolean := true;  -- implement CSR system?
Line 77... Line 78...
    rs1_i         : in  std_ulogic_vector(data_width_c-1 downto 0); -- rf source 1
    rs1_i         : in  std_ulogic_vector(data_width_c-1 downto 0); -- rf source 1
    -- data output --
    -- data output --
    imm_o         : out std_ulogic_vector(data_width_c-1 downto 0); -- immediate
    imm_o         : out std_ulogic_vector(data_width_c-1 downto 0); -- immediate
    fetch_pc_o    : out std_ulogic_vector(data_width_c-1 downto 0); -- PC for instruction fetch
    fetch_pc_o    : out std_ulogic_vector(data_width_c-1 downto 0); -- PC for instruction fetch
    curr_pc_o     : out std_ulogic_vector(data_width_c-1 downto 0); -- current PC (corresponding to current instruction)
    curr_pc_o     : out std_ulogic_vector(data_width_c-1 downto 0); -- current PC (corresponding to current instruction)
    next_pc_o     : out std_ulogic_vector(data_width_c-1 downto 0); -- next PC (corresponding to current instruction)
 
    csr_rdata_o   : out std_ulogic_vector(data_width_c-1 downto 0); -- CSR read data
    csr_rdata_o   : out std_ulogic_vector(data_width_c-1 downto 0); -- CSR read data
    -- interrupts (risc-v compliant) --
    -- interrupts (risc-v compliant) --
    msw_irq_i     : in  std_ulogic; -- machine software interrupt
    msw_irq_i     : in  std_ulogic; -- machine software interrupt
    mext_irq_i    : in  std_ulogic; -- machine external interrupt
    mext_irq_i    : in  std_ulogic; -- machine external interrupt
    mtime_irq_i   : in  std_ulogic; -- machine timer interrupt
    mtime_irq_i   : in  std_ulogic; -- machine timer interrupt
Line 162... Line 162...
    valid : std_ulogic; -- data word is valid when set
    valid : std_ulogic; -- data word is valid when set
  end record;
  end record;
  signal cmd_issue : cmd_issue_t;
  signal cmd_issue : cmd_issue_t;
 
 
  -- instruction execution engine --
  -- instruction execution engine --
  type execute_engine_state_t is (SYS_WAIT, DISPATCH, TRAP, EXECUTE, ALU_WAIT, BRANCH, LOADSTORE_0, LOADSTORE_1, LOADSTORE_2, CSR_ACCESS);
  type execute_engine_state_t is (SYS_WAIT, DISPATCH, TRAP, EXECUTE, ALU_WAIT, BRANCH, FENCE_OP, LOADSTORE_0, LOADSTORE_1, LOADSTORE_2, SYS_ENV, CSR_ACCESS);
  type execute_engine_t is record
  type execute_engine_t is record
    state        : execute_engine_state_t;
    state        : execute_engine_state_t;
    state_prev   : execute_engine_state_t;
    state_prev   : execute_engine_state_t;
    state_nxt    : execute_engine_state_t;
    state_nxt    : execute_engine_state_t;
 
    --
    i_reg        : std_ulogic_vector(31 downto 0);
    i_reg        : std_ulogic_vector(31 downto 0);
    i_reg_nxt    : std_ulogic_vector(31 downto 0);
    i_reg_nxt    : std_ulogic_vector(31 downto 0);
    i_reg_last   : std_ulogic_vector(31 downto 0); -- last executed instruction
    i_reg_last   : std_ulogic_vector(31 downto 0); -- last executed instruction
 
    --
    is_ci        : std_ulogic; -- current instruction is de-compressed instruction
    is_ci        : std_ulogic; -- current instruction is de-compressed instruction
    is_ci_nxt    : std_ulogic;
    is_ci_nxt    : std_ulogic;
    is_jump      : std_ulogic; -- current instruction is jump instruction
    is_jump      : std_ulogic; -- current instruction is jump instruction
    is_jump_nxt  : std_ulogic;
    is_jump_nxt  : std_ulogic;
    is_cp_op     : std_ulogic; -- current instruction is a co-processor operation
    is_cp_op     : std_ulogic; -- current instruction is a co-processor operation
    is_cp_op_nxt : std_ulogic;
    is_cp_op_nxt : std_ulogic;
 
    --
    branch_taken : std_ulogic; -- branch condition fullfilled
    branch_taken : std_ulogic; -- branch condition fullfilled
    pc           : std_ulogic_vector(data_width_c-1 downto 0); -- actual PC, corresponding to current executed instruction
    pc           : std_ulogic_vector(data_width_c-1 downto 0); -- actual PC, corresponding to current executed instruction
    pc_nxt       : std_ulogic_vector(data_width_c-1 downto 0);
    pc_mux_sel   : std_ulogic_vector(1 downto 0); -- source select for PC update
 
    pc_we        : std_ulogic; -- PC update enabled
    next_pc      : std_ulogic_vector(data_width_c-1 downto 0); -- next PC, corresponding to next instruction to be executed
    next_pc      : std_ulogic_vector(data_width_c-1 downto 0); -- next PC, corresponding to next instruction to be executed
    last_pc      : std_ulogic_vector(data_width_c-1 downto 0); -- PC of last executed instruction
    last_pc      : std_ulogic_vector(data_width_c-1 downto 0); -- PC of last executed instruction
    last_pc_nxt  : std_ulogic_vector(data_width_c-1 downto 0); -- PC of last executed instruction
    --
    sleep        : std_ulogic; -- CPU in sleep mode
    sleep        : std_ulogic; -- CPU in sleep mode
    sleep_nxt    : std_ulogic; -- CPU in sleep mode
    sleep_nxt    : std_ulogic;
    if_rst       : std_ulogic; -- instruction fetch was reset
    if_rst       : std_ulogic; -- instruction fetch was reset
    if_rst_nxt   : std_ulogic; -- instruction fetch was reset
    if_rst_nxt   : std_ulogic;
  end record;
  end record;
  signal execute_engine : execute_engine_t;
  signal execute_engine : execute_engine_t;
 
 
  -- trap controller --
  -- trap controller --
  type trap_ctrl_t is record
  type trap_ctrl_t is record
Line 213... Line 217...
    env_call      : std_ulogic;
    env_call      : std_ulogic;
    break_point   : std_ulogic;
    break_point   : std_ulogic;
  end record;
  end record;
  signal trap_ctrl : trap_ctrl_t;
  signal trap_ctrl : trap_ctrl_t;
 
 
 
  -- atomic operations controller --
 
  type atomic_ctrl_t is record
 
    env_start  : std_ulogic; -- begin atomic operations
 
    env_end    : std_ulogic; -- end atomic operations
 
    env_end_ff : std_ulogic; -- end atomic operations dealyed
 
    env_abort  : std_ulogic; -- atomic operations abort (results in failure)
 
    lock       : std_ulogic; -- lock status
 
  end record;
 
  signal atomic_ctrl : atomic_ctrl_t;
 
 
  -- CPU control signals --
  -- CPU control signals --
  signal ctrl_nxt, ctrl : std_ulogic_vector(ctrl_width_c-1 downto 0);
  signal ctrl_nxt, ctrl : std_ulogic_vector(ctrl_width_c-1 downto 0);
 
 
  -- fast bus access --
  -- fast bus access --
  signal bus_fast_ir : std_ulogic;
  signal bus_fast_ir : std_ulogic;
Line 329... Line 343...
        end if;
        end if;
 
 
      when IFETCH_ISSUE => -- store instruction data to prefetch buffer
      when IFETCH_ISSUE => -- store instruction data to prefetch buffer
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        if (bus_i_wait_i = '0') or (be_instr_i = '1') or (ma_instr_i = '1') then -- wait for bus response
        if (bus_i_wait_i = '0') or (be_instr_i = '1') or (ma_instr_i = '1') then -- wait for bus response
          fetch_engine.bus_err_ack <= '1'; -- acknowledge any instruction bus errors, the execute engine has to take care of them / terminate current transfer
 
          fetch_engine.pc_nxt      <= std_ulogic_vector(unsigned(fetch_engine.pc) + 4);
          fetch_engine.pc_nxt      <= std_ulogic_vector(unsigned(fetch_engine.pc) + 4);
          ipb.we                   <= '1';
          ipb.we                   <= '1';
          fetch_engine.state_nxt   <= IFETCH_REQUEST;
          fetch_engine.state_nxt   <= IFETCH_REQUEST;
        end if;
        end if;
 
 
Line 524... Line 537...
  imm_gen: process(execute_engine.i_reg, clk_i)
  imm_gen: process(execute_engine.i_reg, clk_i)
    variable opcode_v : std_ulogic_vector(6 downto 0);
    variable opcode_v : std_ulogic_vector(6 downto 0);
  begin
  begin
    opcode_v := execute_engine.i_reg(instr_opcode_msb_c downto instr_opcode_lsb_c+2) & "11";
    opcode_v := execute_engine.i_reg(instr_opcode_msb_c downto instr_opcode_lsb_c+2) & "11";
    if rising_edge(clk_i) then
    if rising_edge(clk_i) then
 
      if (execute_engine.state = BRANCH) then -- next_PC as immediate fro jump-and-link operations (=return address)
 
        imm_o <= execute_engine.next_pc;
 
      else -- "nromal" immediate from instruction
      case opcode_v is -- save some bits here, LSBs are always 11 for rv32
      case opcode_v is -- save some bits here, LSBs are always 11 for rv32
        when opcode_store_c => -- S-immediate
        when opcode_store_c => -- S-immediate
          imm_o(31 downto 11) <= (others => execute_engine.i_reg(31)); -- sign extension
          imm_o(31 downto 11) <= (others => execute_engine.i_reg(31)); -- sign extension
          imm_o(10 downto 05) <= execute_engine.i_reg(30 downto 25);
          imm_o(10 downto 05) <= execute_engine.i_reg(30 downto 25);
          imm_o(04 downto 01) <= execute_engine.i_reg(11 downto 08);
          imm_o(04 downto 01) <= execute_engine.i_reg(11 downto 08);
Line 547... Line 563...
          imm_o(19 downto 12) <= execute_engine.i_reg(19 downto 12);
          imm_o(19 downto 12) <= execute_engine.i_reg(19 downto 12);
          imm_o(11)           <= execute_engine.i_reg(20);
          imm_o(11)           <= execute_engine.i_reg(20);
          imm_o(10 downto 05) <= execute_engine.i_reg(30 downto 25);
          imm_o(10 downto 05) <= execute_engine.i_reg(30 downto 25);
          imm_o(04 downto 01) <= execute_engine.i_reg(24 downto 21);
          imm_o(04 downto 01) <= execute_engine.i_reg(24 downto 21);
          imm_o(00)           <= '0';
          imm_o(00)           <= '0';
 
          when opcode_atomic_c => -- atomic memory access
 
            imm_o               <= (others => '0'); -- effective address is reg + 0
        when others => -- I-immediate
        when others => -- I-immediate
          imm_o(31 downto 11) <= (others => execute_engine.i_reg(31)); -- sign extension
          imm_o(31 downto 11) <= (others => execute_engine.i_reg(31)); -- sign extension
          imm_o(10 downto 05) <= execute_engine.i_reg(30 downto 25);
          imm_o(10 downto 05) <= execute_engine.i_reg(30 downto 25);
          imm_o(04 downto 01) <= execute_engine.i_reg(24 downto 21);
          imm_o(04 downto 01) <= execute_engine.i_reg(24 downto 21);
          imm_o(00)           <= execute_engine.i_reg(20);
          imm_o(00)           <= execute_engine.i_reg(20);
      end case;
      end case;
    end if;
    end if;
 
    end if;
  end process imm_gen;
  end process imm_gen;
 
 
 
 
  -- Branch Condition Check -----------------------------------------------------------------
  -- Branch Condition Check -----------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
Line 583... Line 602...
  -- for registers that DO require a specific reset state --
  -- for registers that DO require a specific reset state --
  execute_engine_fsm_sync_rst: process(rstn_i, clk_i)
  execute_engine_fsm_sync_rst: process(rstn_i, clk_i)
  begin
  begin
    if (rstn_i = '0') then
    if (rstn_i = '0') then
      execute_engine.pc      <= CPU_BOOT_ADDR(data_width_c-1 downto 1) & '0';
      execute_engine.pc      <= CPU_BOOT_ADDR(data_width_c-1 downto 1) & '0';
      execute_engine.last_pc <= CPU_BOOT_ADDR(data_width_c-1 downto 1) & '0';
 
      execute_engine.state   <= SYS_WAIT;
      execute_engine.state   <= SYS_WAIT;
      execute_engine.sleep   <= '0';
      execute_engine.sleep   <= '0';
      execute_engine.if_rst  <= '1'; -- instruction fetch is reset after system reset
      execute_engine.if_rst  <= '1'; -- instruction fetch is reset after system reset
    elsif rising_edge(clk_i) then
    elsif rising_edge(clk_i) then
      execute_engine.pc      <= execute_engine.pc_nxt(data_width_c-1 downto 1) & '0';
      -- PC update --
      execute_engine.last_pc <= execute_engine.last_pc_nxt;
      if (execute_engine.pc_we = '1') then
 
        case execute_engine.pc_mux_sel is
 
          when "00"   => execute_engine.pc <= execute_engine.next_pc(data_width_c-1 downto 1) & '0'; -- normal (linear) increment
 
          when "01"   => execute_engine.pc <= alu_add_i(data_width_c-1 downto 1) & '0'; -- jump/branch
 
          when "10"   => execute_engine.pc <= csr.mtvec(data_width_c-1 downto 1) & '0'; -- trap
 
          when others => execute_engine.pc <= csr.mepc(data_width_c-1 downto 1) & '0'; -- trap return
 
        end case;
 
      end if;
 
      --
      execute_engine.state   <= execute_engine.state_nxt;
      execute_engine.state   <= execute_engine.state_nxt;
      execute_engine.sleep   <= execute_engine.sleep_nxt;
      execute_engine.sleep   <= execute_engine.sleep_nxt;
      execute_engine.if_rst  <= execute_engine.if_rst_nxt;
      execute_engine.if_rst  <= execute_engine.if_rst_nxt;
    end if;
    end if;
  end process execute_engine_fsm_sync_rst;
  end process execute_engine_fsm_sync_rst;
Line 606... Line 632...
      execute_engine.state_prev <= execute_engine.state;
      execute_engine.state_prev <= execute_engine.state;
      execute_engine.i_reg      <= execute_engine.i_reg_nxt;
      execute_engine.i_reg      <= execute_engine.i_reg_nxt;
      execute_engine.is_ci      <= execute_engine.is_ci_nxt;
      execute_engine.is_ci      <= execute_engine.is_ci_nxt;
      execute_engine.is_jump    <= execute_engine.is_jump_nxt;
      execute_engine.is_jump    <= execute_engine.is_jump_nxt;
      execute_engine.is_cp_op   <= execute_engine.is_cp_op_nxt;
      execute_engine.is_cp_op   <= execute_engine.is_cp_op_nxt;
      --
      -- next PC (next linear instruction) --
      if (execute_engine.state = EXECUTE) then
 
        execute_engine.i_reg_last <= execute_engine.i_reg;
 
      end if;
 
      -- next PC --
 
      if (execute_engine.is_ci = '1') then -- compressed instruction?
      if (execute_engine.is_ci = '1') then -- compressed instruction?
        execute_engine.next_pc <= std_ulogic_vector(unsigned(execute_engine.pc) + 2);
        execute_engine.next_pc <= std_ulogic_vector(unsigned(execute_engine.pc) + 2);
      else
      else
        execute_engine.next_pc <= std_ulogic_vector(unsigned(execute_engine.pc) + 4);
        execute_engine.next_pc <= std_ulogic_vector(unsigned(execute_engine.pc) + 4);
      end if;
      end if;
      --
      -- PC & IR of last "executed" instruction --
 
      if (execute_engine.state = EXECUTE) then
 
        execute_engine.last_pc   <= execute_engine.pc;
 
        execute_engine.i_reg_last <= execute_engine.i_reg;
 
      end if;
 
      -- main control bus --
      ctrl <= ctrl_nxt;
      ctrl <= ctrl_nxt;
    end if;
    end if;
  end process execute_engine_fsm_sync;
  end process execute_engine_fsm_sync;
 
 
  -- PC output --
  -- PC output --
  curr_pc_o <= execute_engine.pc(data_width_c-1 downto 1) & '0';
  curr_pc_o <= execute_engine.pc(data_width_c-1 downto 1) & '0'; -- PC for ALU ops
  next_pc_o <= execute_engine.next_pc(data_width_c-1 downto 1) & '0';
 
 
 
 
 
  -- CPU Control Bus Output -----------------------------------------------------------------
  -- CPU Control Bus Output -----------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  ctrl_output: process(ctrl, fetch_engine, trap_ctrl, bus_fast_ir, execute_engine, csr.privilege)
  ctrl_output: process(ctrl, fetch_engine, trap_ctrl, atomic_ctrl, bus_fast_ir, execute_engine, csr.privilege)
  begin
  begin
    -- signals from execute engine --
    -- signals from execute engine --
    ctrl_o <= ctrl;
    ctrl_o <= ctrl;
    -- current privilege level --
    -- current privilege level --
    ctrl_o(ctrl_priv_lvl_msb_c downto ctrl_priv_lvl_lsb_c) <= csr.privilege;
    ctrl_o(ctrl_priv_lvl_msb_c downto ctrl_priv_lvl_lsb_c) <= csr.privilege;
Line 646... Line 672...
    ctrl_o(ctrl_bus_ierr_ack_c) <= fetch_engine.bus_err_ack;
    ctrl_o(ctrl_bus_ierr_ack_c) <= fetch_engine.bus_err_ack;
    ctrl_o(ctrl_bus_derr_ack_c) <= trap_ctrl.env_start_ack;
    ctrl_o(ctrl_bus_derr_ack_c) <= trap_ctrl.env_start_ack;
    -- instruction's function blocks (for co-processors) --
    -- instruction's function blocks (for co-processors) --
    ctrl_o(ctrl_ir_funct12_11_c downto ctrl_ir_funct12_0_c) <= execute_engine.i_reg(instr_funct12_msb_c downto instr_funct12_lsb_c);
    ctrl_o(ctrl_ir_funct12_11_c downto ctrl_ir_funct12_0_c) <= execute_engine.i_reg(instr_funct12_msb_c downto instr_funct12_lsb_c);
    ctrl_o(ctrl_ir_funct3_2_c   downto ctrl_ir_funct3_0_c)  <= execute_engine.i_reg(instr_funct3_msb_c  downto instr_funct3_lsb_c);
    ctrl_o(ctrl_ir_funct3_2_c   downto ctrl_ir_funct3_0_c)  <= execute_engine.i_reg(instr_funct3_msb_c  downto instr_funct3_lsb_c);
 
    -- locked bus operation (for atomica memory operations) --
 
    ctrl_o(ctrl_bus_lock_c) <= atomic_ctrl.lock; -- (bus) lock status
  end process ctrl_output;
  end process ctrl_output;
 
 
 
 
  -- Execute Engine FSM Comb ----------------------------------------------------------------
  -- Execute Engine FSM Comb ----------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  -- -------------------------------------------------------------------------------------------
  execute_engine_fsm_comb: process(execute_engine, fetch_engine, cmd_issue, trap_ctrl, csr, ctrl, csr_acc_valid,
  execute_engine_fsm_comb: process(execute_engine, fetch_engine, cmd_issue, trap_ctrl, csr, ctrl, csr_acc_valid,
                                   alu_add_i, alu_wait_i, bus_d_wait_i, ma_load_i, be_load_i, ma_store_i, be_store_i)
                                   alu_wait_i, bus_d_wait_i, ma_load_i, be_load_i, ma_store_i, be_store_i)
    variable alu_immediate_v : std_ulogic;
    variable alu_immediate_v : std_ulogic;
    variable rs1_is_r0_v     : std_ulogic;
    variable rs1_is_r0_v     : std_ulogic;
    variable opcode_v        : std_ulogic_vector(6 downto 0);
    variable opcode_v        : std_ulogic_vector(6 downto 0);
 
    variable is_atomic_lr_v  : std_ulogic;
 
    variable is_atomic_sc_v  : std_ulogic;
  begin
  begin
    -- arbiter defaults --
    -- arbiter defaults --
    execute_engine.state_nxt    <= execute_engine.state;
    execute_engine.state_nxt    <= execute_engine.state;
    execute_engine.i_reg_nxt    <= execute_engine.i_reg;
    execute_engine.i_reg_nxt    <= execute_engine.i_reg;
    execute_engine.is_jump_nxt  <= '0';
    execute_engine.is_jump_nxt  <= '0';
    execute_engine.is_cp_op_nxt <= execute_engine.is_cp_op;
    execute_engine.is_cp_op_nxt <= execute_engine.is_cp_op;
    execute_engine.is_ci_nxt    <= execute_engine.is_ci;
    execute_engine.is_ci_nxt    <= execute_engine.is_ci;
    execute_engine.pc_nxt       <= execute_engine.pc;
 
    execute_engine.last_pc_nxt  <= execute_engine.last_pc;
 
    execute_engine.sleep_nxt    <= execute_engine.sleep;
    execute_engine.sleep_nxt    <= execute_engine.sleep;
    execute_engine.if_rst_nxt   <= execute_engine.if_rst;
    execute_engine.if_rst_nxt   <= execute_engine.if_rst;
 
    --
 
    execute_engine.pc_mux_sel   <= (others => '0');
 
    execute_engine.pc_we        <= '0';
 
 
    -- instruction dispatch --
    -- instruction dispatch --
    fetch_engine.reset          <= '0';
    fetch_engine.reset          <= '0';
 
 
    -- trap environment control --
    -- trap environment control --
Line 686... Line 717...
 
 
    -- CSR access --
    -- CSR access --
    csr.we_nxt                  <= '0';
    csr.we_nxt                  <= '0';
    csr.re_nxt                  <= '0';
    csr.re_nxt                  <= '0';
 
 
    -- control defaults --
    -- atomic operations control --
 
    atomic_ctrl.env_start       <= '0';
 
    atomic_ctrl.env_end         <= '0';
 
    atomic_ctrl.env_abort       <= '0';
 
 
 
    -- CONTROL DEFAULTS --
    ctrl_nxt <= (others => '0'); -- default: all off
    ctrl_nxt <= (others => '0'); -- default: all off
    if (execute_engine.i_reg(instr_opcode_lsb_c+4) = '1') then -- ALU ops
    if (execute_engine.i_reg(instr_opcode_lsb_c+4) = '1') then -- ALU ops
      ctrl_nxt(ctrl_alu_unsigned_c) <= execute_engine.i_reg(instr_funct3_lsb_c+0); -- unsigned ALU operation? (SLTIU, SLTU)
      ctrl_nxt(ctrl_alu_unsigned_c) <= execute_engine.i_reg(instr_funct3_lsb_c+0); -- unsigned ALU operation? (SLTIU, SLTU)
    else -- branches
    else -- branches
      ctrl_nxt(ctrl_alu_unsigned_c) <= execute_engine.i_reg(instr_funct3_lsb_c+1); -- unsigned branches? (BLTU, BGEU)
      ctrl_nxt(ctrl_alu_unsigned_c) <= execute_engine.i_reg(instr_funct3_lsb_c+1); -- unsigned branches? (BLTU, BGEU)
    end if;
    end if;
 
    -- memor access --
    ctrl_nxt(ctrl_bus_unsigned_c)  <= execute_engine.i_reg(instr_funct3_msb_c); -- unsigned LOAD (LBU, LHU)
    ctrl_nxt(ctrl_bus_unsigned_c)  <= execute_engine.i_reg(instr_funct3_msb_c); -- unsigned LOAD (LBU, LHU)
 
    ctrl_nxt(ctrl_bus_size_msb_c downto ctrl_bus_size_lsb_c) <= execute_engine.i_reg(instr_funct3_lsb_c+1 downto instr_funct3_lsb_c); -- mem transfer size
 
    -- alu.shifter --
    ctrl_nxt(ctrl_alu_shift_dir_c) <= execute_engine.i_reg(instr_funct3_msb_c); -- shift direction (left/right)
    ctrl_nxt(ctrl_alu_shift_dir_c) <= execute_engine.i_reg(instr_funct3_msb_c); -- shift direction (left/right)
    ctrl_nxt(ctrl_alu_shift_ar_c)  <= execute_engine.i_reg(30); -- is arithmetic shift
    ctrl_nxt(ctrl_alu_shift_ar_c)  <= execute_engine.i_reg(30); -- is arithmetic shift
    ctrl_nxt(ctrl_alu_cmd2_c     downto ctrl_alu_cmd0_c)     <= alu_cmd_addsub_c; -- default ALU operation: ADD(I)
    -- ALU control --
    ctrl_nxt(ctrl_cp_id_msb_c    downto ctrl_cp_id_lsb_c)    <= cp_sel_muldiv_c; -- only CP0 (=MULDIV) implemented yet
    ctrl_nxt(ctrl_alu_addsub_c)                          <= '0'; -- ADD(I)
    ctrl_nxt(ctrl_bus_size_msb_c downto ctrl_bus_size_lsb_c) <= execute_engine.i_reg(instr_funct3_lsb_c+1 downto instr_funct3_lsb_c); -- mem transfer size
    ctrl_nxt(ctrl_alu_func1_c  downto ctrl_alu_func0_c)  <= alu_func_cmd_arith_c; -- default ALU function select: arithmetic
 
    ctrl_nxt(ctrl_alu_arith_c)                           <= alu_arith_cmd_addsub_c; -- default ALU arithmetic operation: ADDSUB
 
    ctrl_nxt(ctrl_alu_logic1_c downto ctrl_alu_logic0_c) <= alu_logic_cmd_movb_c; -- default ALU logic operation: MOVB
 
    -- co-processor id --
 
    ctrl_nxt(ctrl_cp_id_msb_c downto ctrl_cp_id_lsb_c) <= cp_sel_muldiv_c; -- default CP = MULDIV
 
 
    -- is immediate ALU operation? --
    -- is immediate ALU operation? --
    alu_immediate_v := not execute_engine.i_reg(instr_opcode_msb_c-1);
    alu_immediate_v := not execute_engine.i_reg(instr_opcode_msb_c-1);
 
 
    -- is rs1 == r0? --
    -- is rs1 == r0? --
    rs1_is_r0_v := not or_all_f(execute_engine.i_reg(instr_rs1_msb_c downto instr_rs1_lsb_c));
    rs1_is_r0_v := not or_all_f(execute_engine.i_reg(instr_rs1_msb_c downto instr_rs1_lsb_c));
 
 
 
    -- is atomic load-reservate/store-conditional? --
 
    if (CPU_EXTENSION_RISCV_A = true) and (execute_engine.i_reg(instr_opcode_lsb_c+2) = '1') then -- valid atomic sub-opcode
 
      is_atomic_lr_v := not execute_engine.i_reg(instr_funct5_lsb_c);
 
      is_atomic_sc_v :=     execute_engine.i_reg(instr_funct5_lsb_c);
 
    else
 
      is_atomic_lr_v := '0';
 
      is_atomic_sc_v := '0';
 
    end if;
 
 
 
 
    -- state machine --
    -- state machine --
    case execute_engine.state is
    case execute_engine.state is
 
 
      when SYS_WAIT => -- System delay cycle (used to wait for side effects to kick in) ((and to init r0 with zero if it is a physical register))
      when SYS_WAIT => -- System delay cycle (used to wait for side effects to kick in) ((and to init r0 with zero if it is a physical register))
Line 720... Line 772...
          ctrl_nxt(ctrl_rf_r0_we_c) <= '1'; -- force RF write access and force rd=r0
          ctrl_nxt(ctrl_rf_r0_we_c) <= '1'; -- force RF write access and force rd=r0
        end if;
        end if;
        --
        --
        execute_engine.state_nxt <= DISPATCH;
        execute_engine.state_nxt <= DISPATCH;
 
 
 
 
      when DISPATCH => -- Get new command from instruction issue engine
      when DISPATCH => -- Get new command from instruction issue engine
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
 
        execute_engine.pc_mux_sel <= "00"; -- linear next PC
        if (cmd_issue.valid = '1') then -- instruction available?
        if (cmd_issue.valid = '1') then -- instruction available?
          -- IR update --
          -- IR update --
          execute_engine.is_ci_nxt <= cmd_issue.data(32); -- flag to indicate this is a de-compressed instruction beeing executed
          execute_engine.is_ci_nxt <= cmd_issue.data(32); -- flag to indicate this is a de-compressed instruction beeing executed
          execute_engine.i_reg_nxt <= cmd_issue.data(31 downto 0);
          execute_engine.i_reg_nxt <= cmd_issue.data(31 downto 0);
          trap_ctrl.instr_ma       <= cmd_issue.data(33); -- misaligned instruction fetch address
          trap_ctrl.instr_ma       <= cmd_issue.data(33); -- misaligned instruction fetch address
          trap_ctrl.instr_be       <= cmd_issue.data(34); -- bus access fault during instrucion fetch
          trap_ctrl.instr_be       <= cmd_issue.data(34); -- bus access fault during instrucion fetch
          illegal_compressed       <= cmd_issue.data(35); -- invalid decompressed instruction
          illegal_compressed       <= cmd_issue.data(35); -- invalid decompressed instruction
          -- PC update --
          -- PC update --
          execute_engine.if_rst_nxt <= '0';
          execute_engine.if_rst_nxt <= '0';
          if (execute_engine.if_rst = '0') then -- if there was NO non-linear PC modification
          if (execute_engine.if_rst = '0') then -- if there was NO non-linear PC modification
            execute_engine.pc_nxt <= execute_engine.next_pc(data_width_c-1 downto 1) & '0';
            execute_engine.pc_we <= '1';
          end if;
          end if;
          -- any reason to go to trap state FAST? --
          -- any reason to go to trap state FAST? --
          if (execute_engine.sleep = '1') or (trap_ctrl.env_start = '1') or (trap_ctrl.exc_fire = '1') or ((cmd_issue.data(33) or cmd_issue.data(34)) = '1') then
          if (execute_engine.sleep = '1') or (trap_ctrl.env_start = '1') or (trap_ctrl.exc_fire = '1') or ((cmd_issue.data(33) or cmd_issue.data(34)) = '1') then
            execute_engine.state_nxt <= TRAP;
            execute_engine.state_nxt <= TRAP;
          else
          else
            execute_engine.state_nxt <= EXECUTE;
            execute_engine.state_nxt <= EXECUTE;
          end if;
          end if;
        end if;
        end if;
 
 
 
 
      when TRAP => -- Start trap environment (also used as cpu sleep state)
      when TRAP => -- Start trap environment (also used as cpu sleep state)
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
 
        execute_engine.pc_mux_sel <= "10"; -- csr.mtvec (trap)
        -- stay here for sleep
        -- stay here for sleep
        if (trap_ctrl.env_start = '1') then -- trap triggered?
        if (trap_ctrl.env_start = '1') then -- trap triggered?
          fetch_engine.reset        <= '1';
          fetch_engine.reset        <= '1';
          execute_engine.if_rst_nxt <= '1'; -- this is a non-linear PC modification
          execute_engine.if_rst_nxt <= '1'; -- this is a non-linear PC modification
          trap_ctrl.env_start_ack   <= '1';
          trap_ctrl.env_start_ack   <= '1';
          execute_engine.pc_nxt     <= csr.mtvec;
          execute_engine.pc_we      <= '1';
          execute_engine.sleep_nxt  <= '0'; -- waky waky
          execute_engine.sleep_nxt  <= '0'; -- waky waky
          execute_engine.state_nxt  <= SYS_WAIT;
          execute_engine.state_nxt  <= SYS_WAIT;
        end if;
        end if;
 
 
 
 
      when EXECUTE => -- Decode and execute instruction
      when EXECUTE => -- Decode and execute instruction
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        execute_engine.last_pc_nxt <= execute_engine.pc; -- store address of current instruction for commit
 
        --
 
        opcode_v := execute_engine.i_reg(instr_opcode_msb_c downto instr_opcode_lsb_c+2) & "11"; -- save some bits here, LSBs are always 11 for rv32
        opcode_v := execute_engine.i_reg(instr_opcode_msb_c downto instr_opcode_lsb_c+2) & "11"; -- save some bits here, LSBs are always 11 for rv32
        case opcode_v is
        case opcode_v is
 
 
          when opcode_alu_c | opcode_alui_c => -- (immediate) ALU operation
          when opcode_alu_c | opcode_alui_c => -- (immediate) ALU operation
          -- ------------------------------------------------------------
          -- ------------------------------------------------------------
            ctrl_nxt(ctrl_alu_opa_mux_c) <= '0'; -- use RS1 as ALU.OPA
            ctrl_nxt(ctrl_alu_opa_mux_c) <= '0'; -- use RS1 as ALU.OPA
            ctrl_nxt(ctrl_alu_opb_mux_c) <= alu_immediate_v; -- use IMM as ALU.OPB for immediate operations
            ctrl_nxt(ctrl_alu_opb_mux_c) <= alu_immediate_v; -- use IMM as ALU.OPB for immediate operations
            ctrl_nxt(ctrl_rf_in_mux_msb_c downto ctrl_rf_in_mux_lsb_c) <= "00"; -- RF input = ALU result
            ctrl_nxt(ctrl_rf_in_mux_msb_c) <= '0'; -- RF input = ALU result
 
 
            -- cp access? --
            -- ALU arithmetic operation type and ADD/SUB --
            if (CPU_EXTENSION_RISCV_M = true) and (execute_engine.i_reg(instr_opcode_lsb_c+5) = opcode_alu_c(5)) and
            if (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_slt_c) or
               (execute_engine.i_reg(instr_funct7_lsb_c) = '1') then -- MULDIV?
               (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_sltu_c) then
              ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_cp_c;
              ctrl_nxt(ctrl_alu_arith_c) <= alu_arith_cmd_slt_c;
              execute_engine.is_cp_op_nxt <= '1'; -- use CP
            else
            -- ALU operation --
              ctrl_nxt(ctrl_alu_arith_c) <= alu_arith_cmd_addsub_c;
            else
 
              case execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) is -- actual ALU operation (re-coding)
 
                when funct3_sll_c  => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_shift_c;  -- SLL(I)
 
                when funct3_slt_c  => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_slt_c;    -- SLT(I)
 
                when funct3_sltu_c => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_slt_c;    -- SLTU(I)
 
                when funct3_xor_c  => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_xor_c;    -- XOR(I)
 
                when funct3_sr_c   => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_shift_c;  -- SRL(I) / SRA(I)
 
                when funct3_or_c   => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_or_c;     -- OR(I)
 
                when funct3_and_c  => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_and_c;    -- AND(I)
 
                when others        => ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_addsub_c; -- ADD(I) / SUB
 
              end case;
 
              execute_engine.is_cp_op_nxt <= '0'; -- no CP operation
 
            end if;
            end if;
 
 
            -- ADD/SUB --
            -- ADD/SUB --
            if ((alu_immediate_v = '0') and (execute_engine.i_reg(instr_funct7_msb_c-1) = '1')) or -- not an immediate op and funct7.6 set => SUB
            if ((alu_immediate_v = '0') and (execute_engine.i_reg(instr_funct7_msb_c-1) = '1')) or -- not an immediate op and funct7.6 set => SUB
               (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_slt_c) or -- SLT operation
               (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_slt_c) or -- SLT operation
Line 796... Line 839...
              ctrl_nxt(ctrl_alu_addsub_c) <= '1'; -- SUB/SLT
              ctrl_nxt(ctrl_alu_addsub_c) <= '1'; -- SUB/SLT
            else
            else
              ctrl_nxt(ctrl_alu_addsub_c) <= '0'; -- ADD(I)
              ctrl_nxt(ctrl_alu_addsub_c) <= '0'; -- ADD(I)
            end if;
            end if;
 
 
 
            -- ALU logic operation --
 
            case execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) is -- actual ALU.logic operation (re-coding)
 
              when funct3_xor_c => ctrl_nxt(ctrl_alu_logic1_c downto ctrl_alu_logic0_c) <= alu_logic_cmd_xor_c; -- XOR(I)
 
              when funct3_or_c  => ctrl_nxt(ctrl_alu_logic1_c downto ctrl_alu_logic0_c) <= alu_logic_cmd_or_c;  -- OR(I)
 
              when funct3_and_c => ctrl_nxt(ctrl_alu_logic1_c downto ctrl_alu_logic0_c) <= alu_logic_cmd_and_c; -- AND(I)
 
              when others       => ctrl_nxt(ctrl_alu_logic1_c downto ctrl_alu_logic0_c) <= alu_logic_cmd_movb_c; -- undefined
 
            end case;
 
 
 
            -- cp access? --
 
            if (CPU_EXTENSION_RISCV_M = true) and (execute_engine.i_reg(instr_opcode_lsb_c+5) = opcode_alu_c(5)) and (execute_engine.i_reg(instr_funct7_lsb_c) = '1') then -- MULDIV CP op?
 
              execute_engine.is_cp_op_nxt                        <= '1'; -- this is a CP operation
 
              ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_copro_c;
 
            -- ALU operation - function select --
 
            else
 
              execute_engine.is_cp_op_nxt <= '0'; -- no CP operation
 
              case execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) is -- actual ALU.func operation (re-coding)
 
                when funct3_xor_c | funct3_or_c | funct3_and_c => ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_logic_c;
 
                when funct3_sll_c | funct3_sr_c                => ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_shift_c;
 
                when others                                    => ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_arith_c;
 
              end case;
 
            end if;
 
 
            -- multi cycle alu operation? --
            -- multi cycle alu operation? --
            if (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_sll_c) or -- SLL shift operation?
            if (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_sll_c) or -- SLL shift operation?
               (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_sr_c) or -- SR shift operation?
               (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_sr_c) or -- SR shift operation?
               ((execute_engine.i_reg(instr_opcode_lsb_c+5) = opcode_alu_c(5)) and (execute_engine.i_reg(instr_funct7_lsb_c) = '1') and (CPU_EXTENSION_RISCV_M = true)) then -- MULDIV?
               ((CPU_EXTENSION_RISCV_M = true) and (execute_engine.i_reg(instr_opcode_lsb_c+5) = opcode_alu_c(5)) and (execute_engine.i_reg(instr_funct7_lsb_c) = '1')) then -- MULDIV CP op?
              execute_engine.state_nxt <= ALU_WAIT;
              execute_engine.state_nxt <= ALU_WAIT;
            else -- single cycle ALU operation
            else -- single cycle ALU operation
              ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back
              ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back
              execute_engine.state_nxt <= DISPATCH;
              execute_engine.state_nxt <= DISPATCH;
            end if;
            end if;
 
 
          when opcode_lui_c | opcode_auipc_c => -- load upper immediate / add upper immediate to PC
          when opcode_lui_c | opcode_auipc_c => -- load upper immediate / add upper immediate to PC
          -- ------------------------------------------------------------
          -- ------------------------------------------------------------
            ctrl_nxt(ctrl_alu_opa_mux_c) <= '1'; -- ALU.OPA = PC (for AUIPC only)
            ctrl_nxt(ctrl_alu_opa_mux_c) <= '1'; -- ALU.OPA = PC (for AUIPC only)
            ctrl_nxt(ctrl_alu_opb_mux_c) <= '1'; -- use IMM as ALU.OPB
            ctrl_nxt(ctrl_alu_opb_mux_c) <= '1'; -- use IMM as ALU.OPB
 
            ctrl_nxt(ctrl_alu_arith_c)   <= alu_arith_cmd_addsub_c; -- actual ALU operation = ADD
 
            ctrl_nxt(ctrl_alu_logic1_c downto ctrl_alu_logic0_c) <= alu_logic_cmd_movb_c; -- MOVB
            if (execute_engine.i_reg(instr_opcode_lsb_c+5) = opcode_lui_c(5)) then -- LUI
            if (execute_engine.i_reg(instr_opcode_lsb_c+5) = opcode_lui_c(5)) then -- LUI
              ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_movb_c; -- actual ALU operation = MOVB
              ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_logic_c; -- actual ALU operation = MOVB
            else -- AUIPC
            else -- AUIPC
              ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_addsub_c; -- actual ALU operation = ADD
              ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_arith_c; -- actual ALU operation = ADD
            end if;
            end if;
            ctrl_nxt(ctrl_rf_in_mux_msb_c downto ctrl_rf_in_mux_lsb_c) <= "00"; -- RF input = ALU result
            ctrl_nxt(ctrl_rf_in_mux_msb_c) <= '0'; -- RF input = ALU result
            ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back
            ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back
            execute_engine.state_nxt  <= DISPATCH;
            execute_engine.state_nxt  <= DISPATCH;
 
 
          when opcode_load_c | opcode_store_c => -- load/store
          when opcode_load_c | opcode_store_c | opcode_atomic_c => -- load/store / atomic memory access
          -- ------------------------------------------------------------
          -- ------------------------------------------------------------
            ctrl_nxt(ctrl_alu_opa_mux_c) <= '0'; -- use RS1 as ALU.OPA
            ctrl_nxt(ctrl_alu_opa_mux_c) <= '0'; -- use RS1 as ALU.OPA
            ctrl_nxt(ctrl_alu_opb_mux_c) <= '1'; -- use IMM as ALU.OPB
            ctrl_nxt(ctrl_alu_opb_mux_c) <= '1'; -- use IMM as ALU.OPB
            ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_addsub_c; -- actual ALU operation = ADD
            ctrl_nxt(ctrl_bus_mo_we_c)   <= '1'; -- write to MAR and MDO (MDO only relevant for store)
            ctrl_nxt(ctrl_bus_mar_we_c) <= '1'; -- write to MAR
            --
            ctrl_nxt(ctrl_bus_mdo_we_c) <= '1'; -- write to MDO (only relevant for stores)
            if (CPU_EXTENSION_RISCV_A = false) or (execute_engine.i_reg(instr_opcode_lsb_c+2) = '0') then -- atomic (A) extension disabled or normal load/store
 
              execute_engine.state_nxt <= LOADSTORE_0;
 
            else -- atomic operation
 
              atomic_ctrl.env_start <= not execute_engine.i_reg(instr_funct5_lsb_c); -- LR: start LOCKED memory access environment
 
              if (execute_engine.i_reg(instr_funct5_msb_c downto instr_funct5_lsb_c) = funct5_a_sc_c) or -- store-conditional
 
                 (execute_engine.i_reg(instr_funct5_msb_c downto instr_funct5_lsb_c) = funct5_a_lr_c) then -- load-reservate
            execute_engine.state_nxt    <= LOADSTORE_0;
            execute_engine.state_nxt    <= LOADSTORE_0;
 
              else -- unimplemented (atomic) instruction
 
                execute_engine.state_nxt <= SYS_WAIT;
 
              end if;
 
            end if;
 
 
          when opcode_branch_c | opcode_jal_c | opcode_jalr_c => -- branch / jump and link (with register)
          when opcode_branch_c | opcode_jal_c | opcode_jalr_c => -- branch / jump and link (with register)
          -- ------------------------------------------------------------
          -- ------------------------------------------------------------
            ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_addsub_c; -- actual ALU operation = ADD
 
            -- compute target address --
            -- compute target address --
 
            ctrl_nxt(ctrl_alu_arith_c) <= alu_arith_cmd_addsub_c; -- actual ALU operation = ADD
 
            ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_arith_c; -- actual ALU operation = ADD
            if (execute_engine.i_reg(instr_opcode_lsb_c+3 downto instr_opcode_lsb_c+2) = opcode_jalr_c(3 downto 2)) then -- JALR
            if (execute_engine.i_reg(instr_opcode_lsb_c+3 downto instr_opcode_lsb_c+2) = opcode_jalr_c(3 downto 2)) then -- JALR
              ctrl_nxt(ctrl_alu_opa_mux_c) <= '0'; -- use RS1 as ALU.OPA (branch target address base)
              ctrl_nxt(ctrl_alu_opa_mux_c) <= '0'; -- use RS1 as ALU.OPA (branch target address base)
            else -- JAL / branch
            else -- JAL / branch
              ctrl_nxt(ctrl_alu_opa_mux_c) <= '1'; -- use PC as ALU.OPA (branch target address base)
              ctrl_nxt(ctrl_alu_opa_mux_c) <= '1'; -- use PC as ALU.OPA (branch target address base)
            end if;
            end if;
            ctrl_nxt(ctrl_alu_opb_mux_c) <= '1'; -- use IMM as ALU.OPB (branch target address offset)
            ctrl_nxt(ctrl_alu_opb_mux_c) <= '1'; -- use IMM as ALU.OPB (branch target address offset)
            -- save return address --
            --
            ctrl_nxt(ctrl_rf_in_mux_msb_c downto ctrl_rf_in_mux_lsb_c) <= "10"; -- RF input = next PC (save return address)
 
            ctrl_nxt(ctrl_rf_wb_en_c)  <= execute_engine.i_reg(instr_opcode_lsb_c+2); -- valid RF write-back? (for JAL/JALR)
 
            execute_engine.is_jump_nxt <= execute_engine.i_reg(instr_opcode_lsb_c+2); -- is this is a jump operation? (for JAL/JALR)
            execute_engine.is_jump_nxt <= execute_engine.i_reg(instr_opcode_lsb_c+2); -- is this is a jump operation? (for JAL/JALR)
            execute_engine.state_nxt   <= BRANCH;
            execute_engine.state_nxt   <= BRANCH;
 
 
          when opcode_fence_c => -- fence operations
          when opcode_fence_c => -- fence operations
          -- ------------------------------------------------------------
          -- ------------------------------------------------------------
            execute_engine.state_nxt <= SYS_WAIT;
            execute_engine.state_nxt <= FENCE_OP;
            -- for simplicity: internally, fence and fence.i perform the same operations (clear and reload instruction prefetch buffer)
 
            -- FENCE.I --
 
            if (CPU_EXTENSION_RISCV_Zifencei = true) then
 
              execute_engine.pc_nxt     <= execute_engine.next_pc(data_width_c-1 downto 1) & '0'; -- "refetch" next instruction
 
              execute_engine.if_rst_nxt <= '1'; -- this is a non-linear PC modification
 
              fetch_engine.reset        <= '1';
 
              if (execute_engine.i_reg(instr_funct3_lsb_c) = funct3_fencei_c(0)) then
 
                ctrl_nxt(ctrl_bus_fencei_c) <= '1';
 
              end if;
 
            end if;
 
            -- FENCE --
 
            if (execute_engine.i_reg(instr_funct3_lsb_c) = funct3_fence_c(0)) then
 
              ctrl_nxt(ctrl_bus_fence_c) <= '1';
 
            end if;
 
 
 
          when opcode_syscsr_c => -- system/csr access
          when opcode_syscsr_c => -- system/csr access
          -- ------------------------------------------------------------
          -- ------------------------------------------------------------
            if (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_env_c) then -- system
            csr.re_nxt <= '1'; -- always read CSR (internally), only relevant for CSR-instructions
 
            if (execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) = funct3_env_c) then -- system/environment
 
              execute_engine.state_nxt <= SYS_ENV;
 
            else -- CSR access
 
              execute_engine.state_nxt <= CSR_ACCESS;
 
            end if;
 
 
 
          when others => -- undefined
 
          -- ------------------------------------------------------------
 
            execute_engine.state_nxt <= SYS_WAIT;
 
 
 
        end case;
 
 
 
 
 
      when SYS_ENV => -- system environment operation - execution
 
      -- ------------------------------------------------------------
 
        execute_engine.pc_mux_sel <= "11"; -- csr.mepc (only for MRET)
              case execute_engine.i_reg(instr_funct12_msb_c downto instr_funct12_lsb_c) is
              case execute_engine.i_reg(instr_funct12_msb_c downto instr_funct12_lsb_c) is
                when funct12_ecall_c => -- ECALL
                when funct12_ecall_c => -- ECALL
                  trap_ctrl.env_call <= '1';
                  trap_ctrl.env_call <= '1';
                when funct12_ebreak_c => -- EBREAK
                when funct12_ebreak_c => -- EBREAK
                  trap_ctrl.break_point <= '1';
                  trap_ctrl.break_point <= '1';
                when funct12_mret_c => -- MRET
                when funct12_mret_c => -- MRET
                  trap_ctrl.env_end <= '1';
                  trap_ctrl.env_end <= '1';
                  execute_engine.pc_nxt <= csr.mepc;
            execute_engine.pc_we <= '1'; -- linear next PC
                  fetch_engine.reset <= '1';
                  fetch_engine.reset <= '1';
                  execute_engine.if_rst_nxt <= '1'; -- this is a non-linear PC modification
                  execute_engine.if_rst_nxt <= '1'; -- this is a non-linear PC modification
                when funct12_wfi_c => -- WFI
                when funct12_wfi_c => -- WFI
                  execute_engine.sleep_nxt <= '1'; -- good night
                  execute_engine.sleep_nxt <= '1'; -- good night
                when others => -- undefined
                when others => -- undefined
                  NULL;
                  NULL;
              end case;
              end case;
              execute_engine.state_nxt <= SYS_WAIT;
              execute_engine.state_nxt <= SYS_WAIT;
            else -- CSR access
 
              csr.re_nxt <= '1'; -- always read CSR (internally)
 
              execute_engine.state_nxt <= CSR_ACCESS;
 
            end if;
 
 
 
          when others => -- undefined
 
          -- ------------------------------------------------------------
 
            execute_engine.state_nxt <= DISPATCH;
 
 
 
        end case;
 
 
 
      when CSR_ACCESS => -- write CSR data to RF, write ALU.res to CSR
      when CSR_ACCESS => -- read & write status and control register (CSR)
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        -- CSR write access --
        -- CSR write access --
        case execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) is
        case execute_engine.i_reg(instr_funct3_msb_c downto instr_funct3_lsb_c) is
          when funct3_csrrw_c | funct3_csrrwi_c => -- CSRRW(I)
          when funct3_csrrw_c | funct3_csrrwi_c => -- CSRRW(I)
            csr.we_nxt <= csr_acc_valid; -- always write CSR if valid access
            csr.we_nxt <= csr_acc_valid; -- always write CSR if valid access
Line 906... Line 974...
            csr.we_nxt <= '0';
            csr.we_nxt <= '0';
        end case;
        end case;
        -- register file write back --
        -- register file write back --
        ctrl_nxt(ctrl_rf_in_mux_msb_c downto ctrl_rf_in_mux_lsb_c) <= "11"; -- RF input = CSR output
        ctrl_nxt(ctrl_rf_in_mux_msb_c downto ctrl_rf_in_mux_lsb_c) <= "11"; -- RF input = CSR output
        ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back
        ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back
        execute_engine.state_nxt  <= SYS_WAIT; -- have another cycle to let side-effects kick in (FIXME?)
        execute_engine.state_nxt  <= DISPATCH;
 
 
 
 
      when ALU_WAIT => -- wait for multi-cycle ALU operation (shifter or CP) to finish
      when ALU_WAIT => -- wait for multi-cycle ALU operation (shifter or CP) to finish
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        ctrl_nxt(ctrl_rf_in_mux_msb_c downto ctrl_rf_in_mux_lsb_c) <= "00"; -- RF input = ALU result
        ctrl_nxt(ctrl_rf_in_mux_msb_c) <= '0'; -- RF input = ALU result
        ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back (permanent write-back)
        ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back (permanent write-back)
        -- cp access or alu shift? --
        -- cp access or alu shift? --
        if (execute_engine.is_cp_op = '1') then
        if (execute_engine.is_cp_op = '1') then
          ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_cp_c;
          ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_copro_c;
        else
        else
          ctrl_nxt(ctrl_alu_cmd2_c downto ctrl_alu_cmd0_c) <= alu_cmd_shift_c;
          ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_shift_c;
        end if;
        end if;
        -- wait for result --
        -- wait for result --
        if (alu_wait_i = '0') then
        if (alu_wait_i = '0') then
          execute_engine.state_nxt <= DISPATCH;
          execute_engine.state_nxt <= DISPATCH;
        end if;
        end if;
 
 
 
 
      when BRANCH => -- update PC for taken branches and jumps
      when BRANCH => -- update PC for taken branches and jumps
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
 
        -- get and store return address (only relevant for jump-and-link operations) --
 
        ctrl_nxt(ctrl_alu_opb_mux_c)                         <= '1'; -- use IMM as ALU.OPB (next_pc from immediate generator = return address)
 
        ctrl_nxt(ctrl_alu_logic1_c downto ctrl_alu_logic0_c) <= alu_logic_cmd_movb_c; -- MOVB
 
        ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c)   <= alu_func_cmd_logic_c; -- actual ALU operation = MOVB
 
        ctrl_nxt(ctrl_rf_in_mux_msb_c)                       <= '0'; -- RF input = ALU result
 
        ctrl_nxt(ctrl_rf_wb_en_c)                            <= execute_engine.is_jump; -- valid RF write-back? (is jump-and-link?)
 
        -- destination address --
 
        execute_engine.pc_mux_sel <= "01"; -- alu.add = branch/jump destination
        if (execute_engine.is_jump = '1') or (execute_engine.branch_taken = '1') then
        if (execute_engine.is_jump = '1') or (execute_engine.branch_taken = '1') then
          execute_engine.pc_nxt     <= alu_add_i; -- branch/jump destination
          execute_engine.pc_we      <= '1'; -- update PC
          fetch_engine.reset        <= '1'; -- trigger new instruction fetch from modified PC
          fetch_engine.reset        <= '1'; -- trigger new instruction fetch from modified PC
          execute_engine.if_rst_nxt <= '1'; -- this is a non-linear PC modification
          execute_engine.if_rst_nxt <= '1'; -- this is a non-linear PC modification
          execute_engine.state_nxt  <= SYS_WAIT;
          execute_engine.state_nxt  <= SYS_WAIT;
        else
        else
          execute_engine.state_nxt <= DISPATCH;
          execute_engine.state_nxt <= DISPATCH;
        end if;
        end if;
 
 
 
 
 
      when FENCE_OP => -- fence operations - execution
 
      -- ------------------------------------------------------------
 
        execute_engine.state_nxt  <= SYS_WAIT;
 
        execute_engine.pc_mux_sel <= "00"; -- linear next PC = "refetch" next instruction
 
        -- FENCE.I --
 
        if (execute_engine.i_reg(instr_funct3_lsb_c) = funct3_fencei_c(0)) and (CPU_EXTENSION_RISCV_Zifencei = true) then
 
          execute_engine.pc_we        <= '1';
 
          execute_engine.if_rst_nxt   <= '1'; -- this is a non-linear PC modification
 
          fetch_engine.reset          <= '1';
 
          ctrl_nxt(ctrl_bus_fencei_c) <= '1';
 
        end if;
 
        -- FENCE --
 
        if (execute_engine.i_reg(instr_funct3_lsb_c) = funct3_fence_c(0)) then
 
          ctrl_nxt(ctrl_bus_fence_c) <= '1';
 
        end if;
 
 
 
 
      when LOADSTORE_0 => -- trigger memory request
      when LOADSTORE_0 => -- trigger memory request
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        if (execute_engine.i_reg(instr_opcode_msb_c-1) = '0') then -- LOAD
        if (execute_engine.i_reg(instr_opcode_msb_c-1) = '0') or (is_atomic_lr_v = '1') then -- normal load or atomic load-reservate
          ctrl_nxt(ctrl_bus_rd_c) <= '1'; -- read request
          ctrl_nxt(ctrl_bus_rd_c) <= '1'; -- read request
        else -- STORE
        else -- store
          ctrl_nxt(ctrl_bus_wr_c) <= '1'; -- write request
          ctrl_nxt(ctrl_bus_wr_c) <= '1'; -- write request
        end if;
        end if;
        execute_engine.state_nxt <= LOADSTORE_1;
        execute_engine.state_nxt <= LOADSTORE_1;
 
 
 
 
      when LOADSTORE_1 => -- memory latency
      when LOADSTORE_1 => -- memory latency
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        ctrl_nxt(ctrl_bus_mdi_we_c) <= '1'; -- write input data to MDI (only relevant for LOAD)
        ctrl_nxt(ctrl_bus_mi_we_c) <= '1'; -- write input data to MDI (only relevant for LOAD)
        execute_engine.state_nxt <= LOADSTORE_2;
        execute_engine.state_nxt <= LOADSTORE_2;
 
 
 
 
      when LOADSTORE_2 => -- wait for bus transaction to finish
      when LOADSTORE_2 => -- wait for bus transaction to finish
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        ctrl_nxt(ctrl_bus_mdi_we_c) <= '1'; -- keep writing input data to MDI (only relevant for LOAD)
        if (CPU_EXTENSION_RISCV_A = true) then -- only relevant for atomic operations
        ctrl_nxt(ctrl_rf_in_mux_msb_c downto ctrl_rf_in_mux_lsb_c) <= "01"; -- RF input = memory input (only relevant for LOAD)
          ctrl_nxt(ctrl_cp_id_msb_c downto ctrl_cp_id_lsb_c) <= cp_sel_atomic_c; -- SC: result comes from "atomic co-processor"
 
          ctrl_nxt(ctrl_alu_func1_c downto ctrl_alu_func0_c) <= alu_func_cmd_copro_c;
 
        end if;
 
        --
 
        ctrl_nxt(ctrl_rf_in_mux_lsb_c) <= '0'; -- RF input = ALU.res or MEM
 
        if (is_atomic_sc_v = '1') then
 
          ctrl_nxt(ctrl_rf_in_mux_msb_c) <= '0'; -- RF input = ALU.res
 
        else
 
          ctrl_nxt(ctrl_rf_in_mux_msb_c) <= '1'; -- RF input = memory input (only relevant for LOAD)
 
        end if;
 
        --
 
        ctrl_nxt(ctrl_bus_mi_we_c) <= '1'; -- keep writing input data to MDI (only relevant for load operations)
 
        -- wait for memory response --
        if ((ma_load_i or be_load_i or ma_store_i or be_store_i) = '1') then -- abort if exception
        if ((ma_load_i or be_load_i or ma_store_i or be_store_i) = '1') then -- abort if exception
 
          atomic_ctrl.env_abort     <= '1'; -- LOCKED (atomic) memory access environment failed (forces SC result to be non-zero => failure)
 
          ctrl_nxt(ctrl_rf_wb_en_c) <= is_atomic_sc_v; -- SC failes: allow write back of non-zero result
          execute_engine.state_nxt <= DISPATCH;
          execute_engine.state_nxt <= DISPATCH;
        elsif (bus_d_wait_i = '0') then -- wait for bus to finish transaction
        elsif (bus_d_wait_i = '0') then -- wait for bus to finish transaction
          if (execute_engine.i_reg(instr_opcode_msb_c-1) = '0') then -- LOAD
          if (execute_engine.i_reg(instr_opcode_msb_c-1) = '0') or (is_atomic_lr_v = '1') or (is_atomic_sc_v = '1') then -- load / load-reservate / store conditional
            ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back (keep writing back all the time)
            ctrl_nxt(ctrl_rf_wb_en_c) <= '1'; -- valid RF write-back
          end if;
          end if;
 
          atomic_ctrl.env_end      <= '1'; -- normal end of LOCKED (atomic) memory access environment
          execute_engine.state_nxt <= DISPATCH;
          execute_engine.state_nxt <= DISPATCH;
        end if;
        end if;
 
 
 
 
      when others => -- undefined
      when others => -- undefined
      -- ------------------------------------------------------------
      -- ------------------------------------------------------------
        execute_engine.state_nxt <= SYS_WAIT;
        execute_engine.state_nxt <= SYS_WAIT;
 
 
    end case;
    end case;
Line 1001... Line 1115...
    end if;
    end if;
 
 
    -- check CSR access --
    -- check CSR access --
    case execute_engine.i_reg(instr_csr_id_msb_c downto instr_csr_id_lsb_c) is
    case execute_engine.i_reg(instr_csr_id_msb_c downto instr_csr_id_lsb_c) is
      when csr_mstatus_c   => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mstatus_c   => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_misa_c      => csr_acc_valid <= is_m_mode_v;-- and (not csr_wacc_v); -- M-mode only, MISA is read-only for the NEORV32 but we don't cause an exception here for compatibility
      when csr_misa_c      => csr_acc_valid <= is_m_mode_v;-- and (not csr_wacc_v); -- M-mode only, MISA is read-only in the NEORV32 but we don't cause an exception here for compatibility
      when csr_mie_c       => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mie_c       => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mtvec_c     => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mtvec_c     => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mscratch_c  => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mscratch_c  => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mepc_c      => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mepc_c      => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mcause_c    => csr_acc_valid <= is_m_mode_v; -- M-mode only
      when csr_mcause_c    => csr_acc_valid <= is_m_mode_v; -- M-mode only
Line 1215... Line 1329...
            end if;
            end if;
          else
          else
            illegal_instruction <= '1';
            illegal_instruction <= '1';
          end if;
          end if;
 
 
 
        when opcode_atomic_c => -- atomic instructions --
 
          if (CPU_EXTENSION_RISCV_A = true) and -- atomic memory operations (A extension) enabled
 
             ((execute_engine.i_reg(instr_funct5_msb_c downto instr_funct5_lsb_c) = funct5_a_lr_c) or -- LR
 
              (execute_engine.i_reg(instr_funct5_msb_c downto instr_funct5_lsb_c) = funct5_a_sc_c)) then -- SC
 
            illegal_instruction <= '0';
 
          else
 
            illegal_instruction <= '1';
 
          end if;
 
 
        when others => -- undefined instruction -> illegal!
        when others => -- undefined instruction -> illegal!
          illegal_instruction <= '1';
          illegal_instruction <= '1';
 
 
      end case;
      end case;
    else
    else
Line 1269... Line 1392...
        -- interrupt buffer: custom fast interrupts
        -- interrupt buffer: custom fast interrupts
        trap_ctrl.irq_buf(interrupt_firq_0_c)    <= csr.mie_firqe(0) and (trap_ctrl.irq_buf(interrupt_firq_0_c) or firq_i(0)) and (not trap_ctrl.irq_ack(interrupt_firq_0_c));
        trap_ctrl.irq_buf(interrupt_firq_0_c)    <= csr.mie_firqe(0) and (trap_ctrl.irq_buf(interrupt_firq_0_c) or firq_i(0)) and (not trap_ctrl.irq_ack(interrupt_firq_0_c));
        trap_ctrl.irq_buf(interrupt_firq_1_c)    <= csr.mie_firqe(1) and (trap_ctrl.irq_buf(interrupt_firq_1_c) or firq_i(1)) and (not trap_ctrl.irq_ack(interrupt_firq_1_c));
        trap_ctrl.irq_buf(interrupt_firq_1_c)    <= csr.mie_firqe(1) and (trap_ctrl.irq_buf(interrupt_firq_1_c) or firq_i(1)) and (not trap_ctrl.irq_ack(interrupt_firq_1_c));
        trap_ctrl.irq_buf(interrupt_firq_2_c)    <= csr.mie_firqe(2) and (trap_ctrl.irq_buf(interrupt_firq_2_c) or firq_i(2)) and (not trap_ctrl.irq_ack(interrupt_firq_2_c));
        trap_ctrl.irq_buf(interrupt_firq_2_c)    <= csr.mie_firqe(2) and (trap_ctrl.irq_buf(interrupt_firq_2_c) or firq_i(2)) and (not trap_ctrl.irq_ack(interrupt_firq_2_c));
        trap_ctrl.irq_buf(interrupt_firq_3_c)    <= csr.mie_firqe(3) and (trap_ctrl.irq_buf(interrupt_firq_3_c) or firq_i(3)) and (not trap_ctrl.irq_ack(interrupt_firq_3_c));
        trap_ctrl.irq_buf(interrupt_firq_3_c)    <= csr.mie_firqe(3) and (trap_ctrl.irq_buf(interrupt_firq_3_c) or firq_i(3)) and (not trap_ctrl.irq_ack(interrupt_firq_3_c));
 
 
        -- trap control --
        -- trap control --
        if (trap_ctrl.env_start = '0') then -- no started trap handler
        if (trap_ctrl.env_start = '0') then -- no started trap handler
          if (trap_ctrl.exc_fire = '1') or ((trap_ctrl.irq_fire = '1') and -- exception/IRQ detected!
          if (trap_ctrl.exc_fire = '1') or ((trap_ctrl.irq_fire = '1') and -- exception/IRQ detected!
             ((execute_engine.state = EXECUTE) or (execute_engine.state = TRAP))) then -- sample IRQs in EXECUTE or TRAP state only -> continue execution even if permanent IRQ
             ((execute_engine.state = EXECUTE) or (execute_engine.state = TRAP))) then -- sample IRQs in EXECUTE or TRAP state only to continue execution even if permanent IRQ
            trap_ctrl.cause     <= trap_ctrl.cause_nxt;   -- capture source ID for program (for mcause csr)
            trap_ctrl.cause     <= trap_ctrl.cause_nxt;   -- capture source ID for program (for mcause csr)
            trap_ctrl.exc_ack   <= '1';                   -- clear execption
            trap_ctrl.exc_ack   <= '1';                   -- clear execption
            trap_ctrl.irq_ack   <= trap_ctrl.irq_ack_nxt; -- capture and clear with interrupt ACK mask
            trap_ctrl.irq_ack   <= trap_ctrl.irq_ack_nxt; -- capture and clear with interrupt ACK mask
            trap_ctrl.env_start <= '1';                   -- now execute engine can start trap handler
            trap_ctrl.env_start <= '1';                   -- now execute engine can start trap handler
          end if;
          end if;
Line 1393... Line 1515...
      trap_ctrl.irq_ack_nxt <= (others => '0');
      trap_ctrl.irq_ack_nxt <= (others => '0');
    end if;
    end if;
  end process trap_priority;
  end process trap_priority;
 
 
 
 
 
  -- Atomic Operation Controller ------------------------------------------------------------
 
  -- -------------------------------------------------------------------------------------------
 
  atomics_controller: process(rstn_i, clk_i)
 
  begin
 
    if (rstn_i = '0') then
 
      atomic_ctrl.lock       <= '0';
 
      atomic_ctrl.env_end_ff <= '0';
 
    elsif rising_edge(clk_i) then
 
      if (CPU_EXTENSION_RISCV_A = true) then
 
        if (atomic_ctrl.env_end_ff = '1') or -- normal termination
 
           (atomic_ctrl.env_abort = '1') or  -- fast temrination (error)
 
           (trap_ctrl.env_start = '1') then -- triggered trap -> failure
 
          atomic_ctrl.lock <= '0';
 
        elsif (atomic_ctrl.env_start = '1') then
 
          atomic_ctrl.lock <= '1';
 
        end if;
 
        atomic_ctrl.env_end_ff <= atomic_ctrl.env_end;
 
      else
 
        atomic_ctrl.lock       <= '0';
 
        atomic_ctrl.env_end_ff <= '0';
 
      end if;
 
    end if;
 
  end process atomics_controller;
 
 
 
 
-- ****************************************************************************************************************************
-- ****************************************************************************************************************************
-- Control and Status Registers (CSRs)
-- Control and Status Registers (CSRs)
-- ****************************************************************************************************************************
-- ****************************************************************************************************************************
 
 
  -- Control and Status Registers Write Data ------------------------------------------------
  -- Control and Status Registers Write Data ------------------------------------------------
Line 1675... Line 1822...
            csr.rdata(03) <= csr.mstatus_mie;  -- MIE
            csr.rdata(03) <= csr.mstatus_mie;  -- MIE
            csr.rdata(07) <= csr.mstatus_mpie; -- MPIE
            csr.rdata(07) <= csr.mstatus_mpie; -- MPIE
            csr.rdata(11) <= csr.mstatus_mpp(0); -- MPP: machine previous privilege mode low
            csr.rdata(11) <= csr.mstatus_mpp(0); -- MPP: machine previous privilege mode low
            csr.rdata(12) <= csr.mstatus_mpp(1); -- MPP: machine previous privilege mode high
            csr.rdata(12) <= csr.mstatus_mpp(1); -- MPP: machine previous privilege mode high
          when csr_misa_c => -- R/-: misa - ISA and extensions
          when csr_misa_c => -- R/-: misa - ISA and extensions
            csr.rdata(00) <= '0';                                         -- A CPU extension
            csr.rdata(00) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_A);     -- A CPU extension
            csr.rdata(01) <= '0';                                         -- B CPU extension
 
            csr.rdata(02) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_C);     -- C CPU extension
            csr.rdata(02) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_C);     -- C CPU extension
            csr.rdata(03) <= '0';                                         -- D CPU extension
 
            csr.rdata(04) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_E);     -- E CPU extension
            csr.rdata(04) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_E);     -- E CPU extension
            csr.rdata(05) <= '0';                                         -- F CPU extension
 
            csr.rdata(08) <= not bool_to_ulogic_f(CPU_EXTENSION_RISCV_E); -- I CPU extension (if not E)
            csr.rdata(08) <= not bool_to_ulogic_f(CPU_EXTENSION_RISCV_E); -- I CPU extension (if not E)
            csr.rdata(12) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_M);     -- M CPU extension
            csr.rdata(12) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_M);     -- M CPU extension
            csr.rdata(20) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_U);     -- U CPU extension
            csr.rdata(20) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_U);     -- U CPU extension
            csr.rdata(23) <= '1';                                         -- X CPU extension (non-std extensions)
            csr.rdata(23) <= '1';                                         -- X CPU extension (non-std extensions)
            csr.rdata(30) <= '1'; -- 32-bit architecture (MXL lo)
            csr.rdata(30) <= '1'; -- 32-bit architecture (MXL lo)
Line 1849... Line 1993...
            csr.rdata <= hw_version_c; -- NEORV32 hardware version
            csr.rdata <= hw_version_c; -- NEORV32 hardware version
          when csr_mhartid_c => -- R/-: mhartid - hardware thread ID
          when csr_mhartid_c => -- R/-: mhartid - hardware thread ID
            csr.rdata <= HW_THREAD_ID;
            csr.rdata <= HW_THREAD_ID;
 
 
          -- custom machine read-only CSRs --
          -- custom machine read-only CSRs --
          when csr_mzext_c => -- R/-: mzext
          when csr_mzext_c => -- R/-: mzext - available Z* extensions
            csr.rdata(0) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_Zicsr);    -- RISC-V.Zicsr CPU extension
            csr.rdata(0) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_Zicsr);    -- RISC-V.Zicsr CPU extension
            csr.rdata(1) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_Zifencei); -- RISC-V.Zifencei CPU extension
            csr.rdata(1) <= bool_to_ulogic_f(CPU_EXTENSION_RISCV_Zifencei); -- RISC-V.Zifencei CPU extension
            csr.rdata(2) <= bool_to_ulogic_f(PMP_USE);                      -- RISC-V physical memory protection
            csr.rdata(2) <= bool_to_ulogic_f(PMP_USE);                      -- RISC-V physical memory protection
 
 
          -- undefined/unavailable --
          -- undefined/unavailable --

powered by: WebSVN 2.1.0

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