{-| Copyright : (C) 2015-2016, University of Twente, 2017 , Google Inc. 2019 , Myrtle Software Ltd. License : BSD2 (see the file LICENSE) Maintainer : Christiaan Baaij <christiaan.baaij@gmail.com> = Initializing a ROM with a data file #usingromfiles# ROMs initialized with a data file. The BNF grammar for this data file is simple: @ FILE = LINE+ LINE = BIT+ BIT = '0' | '1' @ Consecutive @LINE@s correspond to consecutive memory addresses starting at @0@. For example, a data file @memory.bin@ containing the 9-bit unsigned number @7@ to @13@ looks like: @ 000000111 000001000 000001001 000001010 000001011 000001100 000001101 @ We can instantiate a synchronous ROM using the content of the above file like so: @ f :: Clock dom -> Signal dom (Unsigned 3) -> Signal dom (Unsigned 9) f clk rd = 'Clash.Class.BitPack.unpack' '<$>' 'romFile' clk d7 \"memory.bin\" rd @ And see that it works as expected: @ __>>> import qualified Data.List as L__ __>>> L.tail $ sampleN 4 $ f systemClockGen (fromList [3..5])__ [10,11,12] @ However, we can also interpret the same data as a tuple of a 6-bit unsigned number, and a 3-bit signed number: @ g :: Clock dom Regular -> Signal dom (Unsigned 3) -> Signal dom (Unsigned 6,Signed 3) g clk rd = 'Clash.Class.BitPack.unpack' '<$>' 'romFile' clk d7 \"memory.bin\" rd @ And then we would see: @ __>>> import qualified Data.List as L__ __>>> L.tail $ sampleN 4 $ g systemClockGen (fromList [3..5])__ [(1,2),(1,3)(1,-4)] @ -} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE Unsafe #-} {-# OPTIONS_HADDOCK show-extensions #-} module Clash.Explicit.ROM.File ( -- * Synchronous ROM synchronized to an arbitrary clock romFile , romFilePow2 -- * Internal , romFile# ) where import Data.Array (listArray,(!)) import GHC.TypeLits (KnownNat) import System.IO.Unsafe (unsafePerformIO) -- import Clash.Explicit.BlockRam.File (initMem) import Clash.Promoted.Nat (SNat (..), pow2SNat, snatToNum) import Clash.Sized.BitVector (BitVector) import Clash.Explicit.Signal (Clock, Enable, Signal, KnownDomain, delay) import Clash.Sized.Unsigned (Unsigned) import Clash.XException (NFDataX(deepErrorX)) -- | A ROM with a synchronous read port, with space for 2^@n@ elements -- -- * __NB__: Read value is delayed by 1 cycle -- * __NB__: Initial output value is 'undefined' -- * __NB__: This function might not work for specific combinations of -- code-generation backends and hardware targets. Please check the support table -- below: -- -- @ -- | VHDL | Verilog | SystemVerilog | -- ===============+==========+==========+===============+ -- Altera/Quartus | Broken | Works | Works | -- Xilinx/ISE | Works | Works | Works | -- ASIC | Untested | Untested | Untested | -- ===============+==========+==========+===============+ -- @ -- -- Additional helpful information: -- -- * See "Clash.Explicit.ROM.File#usingromfiles" for more information on how -- to instantiate a ROM with the contents of a data file. -- * See "Clash.Sized.Fixed#creatingdatafiles" for ideas on how to create your -- own data files. romFilePow2 :: forall dom n m . (KnownNat m, KnownNat n, KnownDomain dom) => Clock dom -- ^ 'Clock' to synchronize to -> Enable dom -- ^ Global enable -> FilePath -- ^ File describing the content of -- the ROM -> Signal dom (Unsigned n) -- ^ Read address @rd@ -> Signal dom (BitVector m) -- ^ The value of the ROM at address @rd@ from the previous clock cycle romFilePow2 :: Clock dom -> Enable dom -> FilePath -> Signal dom (Unsigned n) -> Signal dom (BitVector m) romFilePow2 = \Clock dom clk Enable dom en -> Clock dom -> Enable dom -> SNat (2 ^ n) -> FilePath -> Signal dom (Unsigned n) -> Signal dom (BitVector m) forall (m :: Nat) addr (dom :: Domain) (n :: Nat). (KnownNat m, Enum addr, KnownDomain dom) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom addr -> Signal dom (BitVector m) romFile Clock dom clk Enable dom en (SNat n -> SNat (2 ^ n) forall (a :: Nat). SNat a -> SNat (2 ^ a) pow2SNat (KnownNat n => SNat n forall (n :: Nat). KnownNat n => SNat n SNat @ n)) {-# INLINE romFilePow2 #-} -- | A ROM with a synchronous read port, with space for @n@ elements -- -- * __NB__: Read value is delayed by 1 cycle -- * __NB__: Initial output value is 'undefined' -- * __NB__: This function might not work for specific combinations of -- code-generation backends and hardware targets. Please check the support table -- below: -- -- @ -- | VHDL | Verilog | SystemVerilog | -- ===============+==========+==========+===============+ -- Altera/Quartus | Broken | Works | Works | -- Xilinx/ISE | Works | Works | Works | -- ASIC | Untested | Untested | Untested | -- ===============+==========+==========+===============+ -- @ -- -- Additional helpful information: -- -- * See "Clash.Explicit.ROM.File#usingromfiles" for more information on how -- to instantiate a ROM with the contents of a data file. -- * See "Clash.Sized.Fixed#creatingdatafiles" for ideas on how to create your -- own data files. romFile :: (KnownNat m, Enum addr, KnownDomain dom) => Clock dom -- ^ 'Clock' to synchronize to -> Enable dom -- ^ Global enable -> SNat n -- ^ Size of the ROM -> FilePath -- ^ File describing the content of the ROM -> Signal dom addr -- ^ Read address @rd@ -> Signal dom (BitVector m) -- ^ The value of the ROM at address @rd@ from the previous clock cycle romFile :: Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom addr -> Signal dom (BitVector m) romFile = \Clock dom clk Enable dom en SNat n sz FilePath file Signal dom addr rd -> Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom Int -> Signal dom (BitVector m) forall (m :: Nat) (dom :: Domain) (n :: Nat). (KnownNat m, KnownDomain dom) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom Int -> Signal dom (BitVector m) romFile# Clock dom clk Enable dom en SNat n sz FilePath file (addr -> Int forall a. Enum a => a -> Int fromEnum (addr -> Int) -> Signal dom addr -> Signal dom Int forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b <$> Signal dom addr rd) {-# INLINE romFile #-} -- | romFile primitive romFile# :: (KnownNat m, KnownDomain dom) => Clock dom -- ^ 'Clock' to synchronize to -> Enable dom -- ^ Global enable -> SNat n -- ^ Size of the ROM -> FilePath -- ^ File describing the content of the ROM -> Signal dom Int -- ^ Read address @rd@ -> Signal dom (BitVector m) -- ^ The value of the ROM at address @rd@ from the previous clock cycle romFile# :: Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom Int -> Signal dom (BitVector m) romFile# Clock dom clk Enable dom en SNat n sz FilePath file Signal dom Int rd = Clock dom -> Enable dom -> BitVector m -> Signal dom (BitVector m) -> Signal dom (BitVector m) forall (dom :: Domain) a. (KnownDomain dom, NFDataX a) => Clock dom -> Enable dom -> a -> Signal dom a -> Signal dom a delay Clock dom clk Enable dom en (FilePath -> BitVector m forall a. (NFDataX a, HasCallStack) => FilePath -> a deepErrorX FilePath "First value of romFile is undefined") ((Array Int (BitVector m) content Array Int (BitVector m) -> Int -> BitVector m forall i e. Ix i => Array i e -> i -> e !) (Int -> BitVector m) -> Signal dom Int -> Signal dom (BitVector m) forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b <$> Signal dom Int rd) where mem :: [BitVector m] mem = IO [BitVector m] -> [BitVector m] forall a. IO a -> a unsafePerformIO (FilePath -> IO [BitVector m] forall (n :: Nat). KnownNat n => FilePath -> IO [BitVector n] initMem FilePath file) content :: Array Int (BitVector m) content = (Int, Int) -> [BitVector m] -> Array Int (BitVector m) forall i e. Ix i => (i, i) -> [e] -> Array i e listArray (Int 0,Int szIInt -> Int -> Int forall a. Num a => a -> a -> a -Int 1) [BitVector m] mem szI :: Int szI = SNat n -> Int forall a (n :: Nat). Num a => SNat n -> a snatToNum SNat n sz {-# NOINLINE romFile# #-}