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,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?"