getting closer...

This commit is contained in:
Yehowshua Immanuel 2025-02-19 09:06:40 -05:00
parent 32932f4816
commit f9248057f9
7 changed files with 107 additions and 51 deletions

View file

@ -3,49 +3,66 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ConstraintKinds #-}
module Simulation(Args(..), simulation) where
module Simulation(Args(..), simulation, Simulation(..)) where
import Peripherals.Setup(setupPeripherals)
import qualified Prelude as P
import Peripherals.Setup(setupPeripherals, InitializedPeripherals(..))
import Peripherals.Teardown(teardownPeripherals)
import Text.Printf (printf)
import Clash.Prelude
import Machine(
Machine(..),
RISCVCPU(..),
Peripherals(..),
machineInit, RISCVCPU (RISCVCPU))
import Fetch(fetchInstruction)
import Fetch(fetchInstruction, FetchResult (Instruction, Misaligned))
import Isa.Decode(decode)
import Isa.Forms(Opcode(..))
import Peripherals.UartCFFI(writeCharToTerminal)
import Control.Concurrent (threadDelay)
import Debug.Trace
import Types (Mem, Addr)
data Args = Args {
firmware :: FilePath
} deriving (Show)
machine :: Machine
machine = machineInit
data Simulation
= Success [Machine]
| Failure String
deriving (Show)
-- machine :: Machine
-- machine = machineInit
machine' :: Machine -> Machine
machine' machine =
let
-- instruction =
-- traceShow
-- (printf "0x%X" (toInteger v) :: String)
-- v
-- where v = fetchInstruction mem msr pc
-- instruction = traceShow (bitpatToOpcode v) v
-- where v = fetchInstruction machineMem machinePC
machineMem = mem machine
machinePeripherals = peripherals machine
machineMem = ram $ machinePeripherals
machineCPU = cpu machine
machinePC = pc machineCPU
instruction = fetchInstruction machineMem machinePC
addr = 0 :: Integer
-- execute would go here, but right now, we simply
mem' = replace addr (3) machineMem
peripherals' = machinePeripherals { ram = mem' }
cpu' = machineCPU { pc = machinePC + 4 }
instruction =
case (fetchInstruction machineMem machinePC) of
Instruction i -> i
_ -> undefined
in
machine { cpu = cpu', mem = mem' }
case (fetchInstruction machineMem machinePC) of
Instruction insn ->
let binaryInsn = show (bitCoerce insn :: BitVector 32)
in trace ("Decoded instruction: " P.++ show opcode
P.++ " | Binary: " P.++ binaryInsn
P.++ " (" P.++ show insn P.++ ")") $
machine { cpu = cpu', peripherals = peripherals' }
where
opcode = decode insn
Misaligned addr -> undefined
simulationLoop :: Int -> Machine -> IO [Machine]
simulationLoop 0 state = return [state]
@ -54,15 +71,14 @@ simulationLoop n state = do
rest <- simulationLoop (n - 1) newState
return (state : rest)
simulation :: Args -> IO [Machine]
simulation :: Args -> IO Simulation
simulation args = do
setupPeripherals
initializedPeripherals <- setupPeripherals (firmware args)
case initializedPeripherals of
InitializationError e -> return $ Failure e
InitializedPeripherals ram -> do
-- quick smoketest that UART works - remove later
writeCharToTerminal 'a'
threadDelay 1000000 -- Delay for 1 second (1,000,000 microseconds)
let initState = machine
sim <- simulationLoop 5 initState
teardownPeripherals
return sim
let initState = machineInit $ Machine.Peripherals ram
sim <- simulationLoop 5 initState
teardownPeripherals
return $ Success sim