{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Peripherals.Ram( initRamFromFile, Ram, RamLine, -- Peripherals.Ram.read, write) where import Clash.Prelude import qualified Prelude as P 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 #define _RAM_DEPTH 1024 #endif -- 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 = let initRam = Vec.replicate (SNat :: SNat _RAM_DEPTH) 0 in do bs <- readFileIntoByteString filePath let ints = getInts bs pure $ populateVectorFromInt32 ints initRam readFileIntoByteString :: FilePath -> IO BL.ByteString readFileIntoByteString filePath = BL.readFile filePath -- Define a function to read a ByteString and convert to [Int32] getInts :: BL.ByteString -> [Int32] getInts bs = runGet listOfInts bs where listOfInts = do empty <- isEmpty if empty then pure [] else do i <- getInt32le -- Parse a single Int32 from the stream rest <- listOfInts -- Recursively parse the rest pure (i : rest) -- Adjusts the length of a list of integers by either truncating or padding with zeros populateVectorFromInt32 :: KnownNat n => [Int32] -> Vec n (Unsigned 32) -> Maybe (Vec n (Unsigned 32)) populateVectorFromInt32 ls v = Vec.fromList adjustedLs where vecLen = length v adjustedLs = fromIntegral <$> adjustLength vecLen ls adjustLength :: Int -> [Int32] -> [Int32] adjustLength n xs = P.take n (xs P.++ P.repeat 0)