Copyright | (C) 2015-2016 University of Twente 2017 Google Inc. 2019 Myrtle Software Ltd 2022 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
We can instantiate a BlockRAM using the content of the above file like so:
f :: Clock dom -> Enable dom -> Signal dom (Unsigned 3) -> Signal dom (Unsigned 9) f clk ena rd =unpack
<$>
blockRamFile
clk ena d7 "memory.bin" rd (signal 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 systemClockGen enableGen (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 -> Enable dom -> Signal dom (Unsigned 3) -> Signal dom (Unsigned 6,Signed 3) g clk ena rd =unpack
<$>
blockRamFile
clk ena d7 "memory.bin" rd (signal Nothing)
And then we would see:
>>> import qualified Data.List as L >>> L.tail $ sampleN 4 $ g systemClockGen enableGen (fromList [3..5]) [(1,2),(1,3)(1,-4)]
Synopsis
- blockRamFile :: (KnownDomain dom, KnownNat m, Enum addr, HasCallStack) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m)
- blockRamFilePow2 :: forall dom n m. (KnownDomain dom, KnownNat m, KnownNat n, HasCallStack) => Clock dom -> Enable dom -> FilePath -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m)
- blockRamFile# :: forall m dom n. (KnownDomain dom, KnownNat m, HasCallStack) => Clock dom -> Enable dom -> SNat n -> FilePath -> Signal dom Int -> Signal dom Bool -> Signal dom Int -> Signal dom (BitVector m) -> Signal dom (BitVector m)
- initMem :: KnownNat n => FilePath -> IO [BitVector n]
BlockRAM synchronized to an arbitrary clock
:: (KnownDomain dom, KnownNat m, Enum addr, HasCallStack) | |
=> Clock dom |
|
-> Enable dom | Global enable |
-> 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.Explicit.BlockRam for more information on how to use a Block RAM.
- Use the adapter
readNew
for obtaining write-before-read semantics like this:
.readNew
clk rst en (blockRamFile
clk en size file) rd wrM - See Clash.Explicit.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. (KnownDomain dom, KnownNat m, KnownNat n, HasCallStack) | |
=> Clock dom |
|
-> Enable dom | Global enable |
-> 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
clk rst en (blockRamFilePow2' clk en file) rd wrM - See Clash.Explicit.BlockRam.File for more information on how to instantiate a Block RAM with the contents of a data file.
- See Clash.Explicit.Fixed for ideas on how to create your own data files.
Internal
:: forall m dom n. (KnownDomain dom, KnownNat m, HasCallStack) | |
=> Clock dom |
|
-> Enable dom | Global enable |
-> SNat n | Size of the blockRAM |
-> FilePath | File describing the initial content of the blockRAM |
-> Signal dom Int | Read address |
-> Signal dom Bool | Write enable |
-> Signal dom Int | Write address |
-> Signal dom (BitVector m) | Value to write (at address |
-> Signal dom (BitVector m) | Value of the |
blockRamFile primitive