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

@ -12,22 +12,27 @@ import Data.Maybe (listToMaybe)
import Data.List (isPrefixOf)
import Text.Show.Pretty (ppShow)
import Simulation (simulation, Args(..))
import Simulation (simulation, Args(..), Simulation(..))
main :: IO ()
main = do
rawArgs <- getArgs
args <- parseArgs rawArgs
states <- simulation args
simResult <- simulation args
putStrLn "Simulating Machine"
-- mapM_ (putStrLn . ppShow) states -- Uncomment to print each state, if needed.
putStrLn $ "Last state: " ++ show (last states)
putStrLn $ "Executed for " ++ show (length states) ++ " cycles"
putStrLn "Simulation complete"
case simResult of
Success states -> do
-- mapM_ (putStrLn . ppShow) states -- Uncomment to print each state, if needed.
putStrLn $ "Last state: " ++ show (last states)
putStrLn $ "Executed for " ++ show (length states) ++ " cycles"
putStrLn "Simulation complete"
Failure err -> do
putStrLn $ "Simulation failed: " ++ err
exitFailure
-- Function to parse command line arguments into the Args data type
parseArgs :: [String] -> IO Args
parseArgs argv =
parseArgs argv =
case extractKey "firmware" argv of
Just firmwarePath -> return Args { firmware = firmwarePath }
Nothing -> do

View file

@ -1,7 +1,9 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NumericUnderscores #-}
module Fetch(fetchInstruction) where
module Fetch(
fetchInstruction,
FetchResult(..)) where
import Clash.Prelude
import Types(Mem, Addr, Insn)

View file

@ -4,12 +4,14 @@
module Machine(
Machine(..),
RISCVCPU(..),
Peripherals(..),
Endian(..),
machineInit) where
import Clash.Prelude
import Types(Pc, Mem)
import RegFiles(GPR, FPR, CSR, gprInit, fprInit, csrInit)
import Peripherals.Ram(Ram)
data Endian = Big | Little
deriving (Generic, Show, Eq, NFDataX)
@ -20,6 +22,12 @@ data PrivilegeLevel
| UserMode
deriving (Generic, Show, Eq, NFDataX)
data Peripherals = Peripherals
{
ram :: Ram
}
deriving (Generic, Show, Eq, NFDataX)
data RISCVCPU = RISCVCPU
{ pc :: Pc,
gpr :: GPR,
@ -30,7 +38,7 @@ data RISCVCPU = RISCVCPU
data Machine = Machine
{ cpu :: RISCVCPU,
mem :: Mem 14
peripherals :: Peripherals
}
deriving (Generic, Show, Eq, NFDataX)
@ -42,11 +50,11 @@ riscvCPUInit =
fprInit
MachineMode
machineInit :: Machine
machineInit =
machineInit :: Peripherals -> Machine
machineInit peripherals =
Machine
riscvCPUInit
memInit
peripherals
memInit :: Vec 14 (Unsigned 32)
memInit =

View file

@ -3,7 +3,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Peripherals.Ram() where
module Peripherals.Ram(initRamFromFile, Ram) where
import Clash.Prelude
import qualified Prelude as P
@ -21,7 +21,7 @@ import qualified Clash.Sized.Vector as Vec
type Ram = Vec _RAM_DEPTH (Unsigned 32)
initRamFromFile :: FilePath -> IO (Maybe Ram)
initRamFromFile filePath =
initRamFromFile filePath =
let
initRam = Vec.replicate (SNat :: SNat _RAM_DEPTH) 0
in
@ -47,10 +47,10 @@ getInts bs = runGet listOfInts bs
pure (i : rest)
-- Adjusts the length of a list of integers by either truncating or padding with zeros
populateVectorFromInt32 ::
populateVectorFromInt32 ::
KnownNat n =>
[Int32] ->
Vec n (Unsigned 32) ->
[Int32] ->
Vec n (Unsigned 32) ->
Maybe (Vec n (Unsigned 32))
populateVectorFromInt32 ls v = Vec.fromList adjustedLs
where
@ -79,8 +79,8 @@ populateVectorFromInt32 ls v = Vec.fromList adjustedLs
-- vecTail = loadFirmware xs
-- loadFirmware [] = takeI $ repeat 0
-- loadFirmware xs = v
-- where
-- loadFirmware xs = v
-- where
-- mapped :: [Unsigned 32] = Clash.Prelude.fromIntegral <$> xs
-- c = takeI (mapped ++ repeat 0)
-- v = takeI $ (mapped ++ repeat 0)
@ -90,4 +90,4 @@ populateVectorFromInt32 ls v = Vec.fromList adjustedLs
-- someList = [1, 2, 3, 4, 5]
-- mem :: Vec 16 (Unsigned 32)
-- mem = loadFirmware someList
-- mem = loadFirmware someList

View file

@ -1,8 +1,29 @@
module Peripherals.Setup (setupPeripherals) where
module Peripherals.Setup (
setupPeripherals, InitializedPeripherals(..)
) where
import Prelude
import Peripherals.UartCFFI(initTerminal)
import Peripherals.Ram (initRamFromFile, Ram)
import Control.Exception (try)
import System.IO.Error (ioeGetErrorString)
setupPeripherals :: IO ()
setupPeripherals = do
initTerminal
type FirmwareFilePath = FilePath
data InitializedPeripherals
= InitializedPeripherals Ram
| InitializationError String
deriving (Show)
setupPeripherals :: FirmwareFilePath -> IO InitializedPeripherals
setupPeripherals firmwareFilePath = do
initTerminal
result <- try (initRamFromFile firmwareFilePath)
return $ case result of
Right (Just ram) -> InitializedPeripherals ram
Right Nothing -> InitializationError $ firmwareFilePath ++ failure ++ suggestion
Left e -> InitializationError $ firmwareFilePath ++ failure ++ suggestion ++ " Error: " ++ ioeGetErrorString e
where
failure = ": Failed to initialize RAM from file!"
suggestion = " Is the file 4-byte aligned?"

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

View file

@ -23,9 +23,13 @@ $(ELF): $(SRC) $(LDSCRIPT)
$(AS) $(ARCH_FLAGS) -o $(OBJ) $(SRC)
$(LD) -T $(LDSCRIPT) -o $(ELF) $(OBJ)
# Convert ELF to raw binary
# Convert ELF to raw binary and pad to the next multiple of 4 bytes
$(BIN): $(ELF)
$(OBJCOPY) -O binary $(ELF) $(BIN)
# Pad the binary to a multiple of 4 bytes
size=$$(stat -f%z $(BIN)); \
padding=$$(( (4 - (size % 4)) % 4 )); \
[ $$padding -ne 0 ] && dd if=/dev/zero bs=1 count=$$padding >> $(BIN) || true
# Run in QEMU
run: $(BIN)