read is getting there...

This commit is contained in:
Yehowshua Immanuel 2025-03-10 17:22:51 -04:00
parent 171fcece98
commit ad751a5039
2 changed files with 50 additions and 18 deletions

View file

@ -1,7 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NumericUnderscores #-}
module Decode(decode, DecodeResult) where
module Decode(decode, DecodeResult(..)) where
import DecodeTypes(
RTypeFields(..), ITypeFields(..), STypeFields(..),

View file

@ -10,25 +10,57 @@ import DecodeTypes(
)
import Clash.Prelude
import Decode(DecodeResult)
-- import Types(DoubleWord, RegFileIdx, Addr)
import Decode(DecodeResult(..))
import Cpu(RISCVCPU(..))
import RegFiles (RegVal(..), GPR)
read :: DecodeResult -> RISCVCPU -> DecodeResult
read (Opcode opc) riscvCPU =
case opc of
ADD fields -> Opcode (ADD (readRTypeFields fields (gpr riscvCPU)))
SUB fields -> Opcode (SUB (readRTypeFields fields (gpr riscvCPU)))
XOR fields -> Opcode (XOR (readRTypeFields fields (gpr riscvCPU)))
OR fields -> Opcode (OR (readRTypeFields fields (gpr riscvCPU)))
AND fields -> Opcode (AND (readRTypeFields fields (gpr riscvCPU)))
SLL fields -> Opcode (SLL (readRTypeFields fields (gpr riscvCPU)))
SRL fields -> Opcode (SRL (readRTypeFields fields (gpr riscvCPU)))
SRA fields -> Opcode (SRA (readRTypeFields fields (gpr riscvCPU)))
SLT fields -> Opcode (SLT (readRTypeFields fields (gpr riscvCPU)))
SLTU fields -> Opcode (SLTU (readRTypeFields fields (gpr riscvCPU)))
_ -> undefined
read (DecodeException e) _ = DecodeException e
read (InstructionException e) _ = InstructionException e
-- data SRC = GPR RegVal
-- | FPR RegVal
-- | CSR RegVal
-- | PC Addr
-- deriving (Generic, Show, Eq, NFDataX)
readRTypeFields :: RTypeFields -> GPR -> RTypeFields
readRTypeFields (RTypeFields rd funct3 rs1 rs2 funct7) gprRegFile =
let rs1_val = fetchRegVal rs1 gprRegFile
rs2_val = fetchRegVal rs2 gprRegFile
in RTypeFields rd funct3 rs1_val rs2_val funct7
-- data ReadResult = ReadResult
-- { src1 :: SRC,
-- src2 :: SRC,
-- src3 :: SRC
-- }
-- deriving (Generic, Show, Eq, NFDataX)
readITypeFields :: ITypeFields -> GPR -> ITypeFields
readITypeFields (ITypeFields rd funct3 rs1 imm) gpr =
let rs1_val = fetchRegVal rs1 gpr
in ITypeFields rd funct3 rs1_val imm
read = 2
readSTypeFields :: STypeFields -> GPR -> STypeFields
readSTypeFields (STypeFields funct3 rs1 rs2 imm12) gpr =
let rs1_val = fetchRegVal rs1 gpr
rs2_val = fetchRegVal rs2 gpr
in STypeFields funct3 rs1_val rs2_val imm12
-- opcodeToReadResult :: Opcode -> ReadResult
-- opcodeToReadResult (ADD (RTypeFields _ rd funct3 rs1 rs2 funct7)) = undefined
-- opcodeToReadResult _ = undefined
readBTypeFields :: BTypeFields -> GPR -> BTypeFields
readBTypeFields (BTypeFields funct3 rs1 rs2 imm13) gpr =
let rs1_val = fetchRegVal rs1 gpr
rs2_val = fetchRegVal rs2 gpr
in BTypeFields funct3 rs1_val rs2_val imm13
readUTypeFields :: UTypeFields -> GPR -> UTypeFields
readUTypeFields fields@(UTypeFields rd imm20) _ = fields
readJTypeFields :: JTypeFields -> GPR -> JTypeFields
readJTypeFields fields@(JTypeFields rd imm21) _ = fields
-- Helper function to fetch register value
fetchRegVal :: RegVal -> GPR -> RegVal
fetchRegVal (Unpopulated idx) gprVal = Value idx (gprVal !! idx)
fetchRegVal val@(Value _ _) _ = val -- Already populated, no change