RiscV-Formal/hs/Simulation.hs
2025-03-04 23:43:35 -05:00

84 lines
2.2 KiB
Haskell

{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ConstraintKinds #-}
module Simulation(
Args(..),
simulation,
RISCVCPU(..),
Machine(..),
Simulation(..)
) where
import qualified Prelude as P
import Peripherals.Setup(setupPeripherals, InitializedPeripherals(..))
import Peripherals.Teardown(teardownPeripherals)
import Clash.Prelude
import Bus(Peripherals(..))
import Cpu(
RISCVCPU(..),
riscvCPUInit)
import Fetch(fetchInstruction, FetchResult (..))
import Isa.Decode(decode)
import Debug.Trace
import Types (Insn)
import Control.Monad.RWS (MonadState(put))
data Args = Args {
firmware :: FilePath
} deriving (Show)
data Simulation
= Success [Machine]
| Failure String
deriving (Show)
data Machine = Machine
{ cpu :: RISCVCPU,
peripherals :: Peripherals
}
deriving (Generic, Show, Eq, NFDataX)
debugInsn :: FetchResult -> String
debugInsn fetchResult =
case fetchResult of
Instruction insn ->
"Decoded instruction: " P.++ show opcode
P.++ " | Binary: " P.++ binaryInsn
P.++ " (" P.++ show insn P.++ ")"
where
binaryInsn = show (bitCoerce insn :: BitVector 32)
opcode = decode insn
InstructionException e -> show e
simulationLoop :: Int -> Machine -> IO [Machine]
simulationLoop 0 machine = return [machine]
simulationLoop n machine = do
let machinePeripherals = peripherals machine
currPc = pc $ cpu machine
fetchResult <- fetchInstruction machinePeripherals currPc
putStrLn $ debugInsn fetchResult
let pc' = currPc + 4
cpu' = (cpu machine) { pc = pc' }
machine' = machine { cpu = cpu' }
rest <- simulationLoop (n - 1) machine'
return (machine : rest)
simulation :: Args -> IO Simulation
simulation args = do
initializedPeripherals <- setupPeripherals (firmware args)
case initializedPeripherals of
InitializationError e -> return $ Failure e
InitializedPeripherals ram -> do
let initState =
Machine {
cpu = riscvCPUInit,
peripherals = Bus.Peripherals ram
}
sim <- simulationLoop 15 initState
teardownPeripherals
return $ Success sim