Copyright | (C) 2015-2016 University of Twente 2019 Myrtle Software Ltd 2017 Google Inc. 2021 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Extensions |
|
Initializing a BlockRAM with a data file
BlockRAM primitives that can be 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
Such a file can be produced with memFile
:
writeFile "memory.bin" (memFile Nothing [7 :: Unsigned 9 .. 13])
We can instantiate a BlockRAM using the content of the above file like so:
f :: (HiddenClock dom, HiddenEnable dom) => Signal dom (Unsigned 3) -> Signal dom (Unsigned 9) f rd =unpack
<$>
blockRamFile
d7 "memory.bin" rd (pure Nothing)
In the example above, we basically treat the BlockRAM as an synchronous ROM. We can see that it works as expected:
>>> import qualified Data.List as L >>> L.tail $ sampleN 4 $ f (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 :: (HiddenClock dom, HiddenEnable dom) => Signal dom (Unsigned 3) -> Signal dom (Unsigned 6,Signed 3) g clk rd =unpack
<$>
blockRamFile
d7 "memory.bin" rd (pure Nothing)
And then we would see:
>>> import qualified Data.List as L >>> L.tail $ sampleN 4 $ g (fromList [3..5]) [(1,2),(1,3)(1,-4)]
Synopsis
- blockRamFile :: (KnownNat m, Enum addr, HiddenClock dom, HiddenEnable dom, HasCallStack) => SNat n -> FilePath -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m)
- blockRamFilePow2 :: forall dom n m. (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom, HasCallStack) => FilePath -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m)
- memFile :: forall a f. (BitPack a, Foldable f, HasCallStack) => Maybe Bit -> f a -> String
BlockRAM synchronized to an arbitrary clock
:: (KnownNat m, Enum addr, HiddenClock dom, HiddenEnable dom, HasCallStack) | |
=> SNat n | Size of the blockRAM |
-> FilePath | File describing the initial content of the blockRAM |
-> Signal dom addr | Read address |
-> Signal dom (Maybe (addr, BitVector m)) | (write address |
-> Signal dom (BitVector m) | Value of the |
Create a blockRAM with space for n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is undefined, reading it will throw an
XException
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.Prelude.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew
for obtaining write-before-read semantics like this:
.readNew
(blockRamFile
size file) rd wrM - See Clash.Prelude.BlockRam.File for more information on how to instantiate a Block RAM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
:: forall dom n m. (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom, HasCallStack) | |
=> FilePath | File describing the initial content of the blockRAM |
-> Signal dom (Unsigned n) | Read address |
-> Signal dom (Maybe (Unsigned n, BitVector m)) | (write address |
-> Signal dom (BitVector m) | Value of the |
Create a blockRAM with space for 2^n
elements
- NB: Read value is delayed by 1 cycle
- NB: Initial output value is undefined, reading it will throw an
XException
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.Prelude.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew
for obtaining write-before-read semantics like this:
.readNew
(blockRamFilePow2
file) rd wrM - See Clash.Prelude.BlockRam.File for more information on how to instantiate a Block RAM with the contents of a data file.
- See Clash.Sized.Fixed for ideas on how to create your own data files.
Producing files
:: forall a f. (BitPack a, Foldable f, HasCallStack) | |
=> Maybe Bit | Value to map don't care bits to. Nothing means throwing an error on don't care bits. |
-> f a | Values to convert. |
-> String | Contents of the memory file. |
Convert data to the String contents of a memory file.
- NB: Not synthesizable
The following document the several ways to instantiate components with files:
- See Clash.Sized.Fixed for more ideas on how to create your own data files.
Example
The Maybe
datatype has don't care bits, where the actual value does not
matter. But the bits need a defined value in the memory. Either 0 or 1 can be
used, and both are valid representations of the data.
>>>
let es = [ Nothing, Just (7 :: Unsigned 8), Just 8]
>>>
mapM_ (putStrLn . show . pack) es
0b0_...._.... 0b1_0000_0111 0b1_0000_1000>>>
putStr (memFile (Just 0) es)
000000000 100000111 100001000>>>
putStr (memFile (Just 1) es)
011111111 100000111 100001000