hopefully progressing to a more scalable bus architecture

This commit is contained in:
Yehowshua Immanuel 2025-02-25 14:24:54 -05:00
parent 003a1c8545
commit 1f9bd2f015
13 changed files with 187 additions and 46 deletions

View file

@ -3,7 +3,12 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Peripherals.Ram(initRamFromFile, Ram) where
module Peripherals.Ram(
initRamFromFile,
Ram,
RamLine,
-- Peripherals.Ram.read,
write) where
import Clash.Prelude
import qualified Prelude as P
@ -11,6 +16,8 @@ import qualified Data.ByteString.Lazy as BL
import Data.Binary.Get
import Data.Int (Int32)
import qualified Clash.Sized.Vector as Vec
import Types(Addr,
Byte, HalfWord, FullWord, DoubleWord, QuadWord)
-- vector depth has to be known statically at compile time
#ifndef _RAM_DEPTH
@ -19,6 +26,51 @@ import qualified Clash.Sized.Vector as Vec
-- TODO : replace Unsigned 32 with BusVal types later...
type Ram = Vec _RAM_DEPTH (Unsigned 32)
type RamAddr = Unsigned (CLog 2 _RAM_DEPTH)
type RamLine = Unsigned 32
bytesInRam = 1024 * 4
readByte0 :: Ram -> RamAddr -> Byte
readByte0 ram addr = unpack $ slice d31 d24 word
where word = ram !! addr
readByte1 :: Ram -> RamAddr -> Byte
readByte1 ram addr = unpack $ slice d23 d16 word
where word = ram !! addr
readByte2 :: Ram -> RamAddr -> Byte
readByte2 ram addr = unpack $ slice d15 d8 word
where word = ram !! addr
readByte3 :: Ram -> RamAddr -> Byte
readByte3 ram addr = unpack $ slice d7 d0 word
where word = ram !! addr
readHalfWord0 :: Ram -> RamAddr -> HalfWord
readHalfWord0 ram addr = unpack $ slice d31 d16 word
where word = ram !! addr
readHalfWord1 :: Ram -> RamAddr -> HalfWord
readHalfWord1 ram addr = unpack $ slice d15 d0 word
where word = ram !! addr
readFullWord :: Ram -> RamAddr -> FullWord
readFullWord ram addr = ram !! addr
readDoubleWord :: Ram -> RamAddr -> DoubleWord
readDoubleWord ram addr = bitCoerce $ bitCoerce word0 ++# bitCoerce word1
where
word0 = readFullWord ram addr
word1 = readFullWord ram (addr + 1)
readQuadWord :: Ram -> RamAddr -> QuadWord
readQuadWord ram addr = bitCoerce $ bitCoerce dword0 ++# bitCoerce dword1
where
dword0 = readDoubleWord ram addr
dword1 = readDoubleWord ram (addr + 2)
write :: Ram -> RamAddr -> RamLine -> Ram
write ram addr value = replace addr value ram
initRamFromFile :: FilePath -> IO (Maybe Ram)
initRamFromFile filePath =
@ -61,33 +113,3 @@ populateVectorFromInt32 ls v = Vec.fromList adjustedLs
-- Function to increment each element of a Clash vector
-- prepareVector :: KnownNat n => [Int32] -> Vec n (Unsigned 32)
-- prepareVector xs = let
-- unsigneds = map (fromIntegral :: Int32 -> Unsigned 32) xs -- Step 1: Convert Int32 to Unsigned 32
-- len = length unsigneds
-- in case compare len (snatToNum (SNat @n)) of -- Step 2: Adjust the length of the list
-- LT -> takeI unsigneds ++ repeat 0 -- Pad with zeros if the list is shorter
-- GT -> takeI unsigneds -- Truncate if the list is longer
-- EQ -> takeI unsigneds -- No padding or truncation needed
-- Function to load firmware
-- loadFirmware :: KnownNat n => [Int32] -> Vec n (Unsigned 32)
-- loadFirmware (x:xs) = vecHead ++ vecTail
-- where
-- vecHead = singleton (fromIntegral x)
-- vecTail = loadFirmware xs
-- loadFirmware [] = takeI $ repeat 0
-- loadFirmware xs = v
-- where
-- mapped :: [Unsigned 32] = Clash.Prelude.fromIntegral <$> xs
-- c = takeI (mapped ++ repeat 0)
-- v = takeI $ (mapped ++ repeat 0)
-- -- Example usage
-- someList :: [Int32]
-- someList = [1, 2, 3, 4, 5]
-- mem :: Vec 16 (Unsigned 32)
-- mem = loadFirmware someList

View file

@ -3,7 +3,7 @@ module Peripherals.Setup (
) where
import Prelude
import Peripherals.UartCFFI(initTerminal)
import Peripherals.UartCFFI(initTerminal, restoreTerminal)
import Peripherals.Ram (initRamFromFile, Ram)
import Control.Exception (try)
import System.IO.Error (ioeGetErrorString)