Copyright | (C) 2022 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Extensions |
|
Efficient bundling of initial RAM content with the compiled code
Leveraging Template Haskell, the initial content for the block RAM components in
this module is stored alongside the compiled Haskell code. It covers use cases
where passing the initial content as a Vec
turns out to be
problematically slow.
The data is stored efficiently, with very little overhead (worst-case 7%, often no overhead at all).
Unlike Clash.Prelude.BlockRam.File, Clash.Prelude.BlockRam.Blob generates practically the same HDL as Clash.Prelude.BlockRam and is compatible with all tools consuming the generated HDL.
Synopsis
- blockRamBlob :: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr, NFDataX addr) => MemBlob n m -> Signal dom addr -> Signal dom (Maybe (addr, BitVector m)) -> Signal dom (BitVector m)
- blockRamBlobPow2 :: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) => MemBlob (2 ^ n) m -> Signal dom (Unsigned n) -> Signal dom (Maybe (Unsigned n, BitVector m)) -> Signal dom (BitVector m)
- data MemBlob (n :: Nat) (m :: Nat)
- createMemBlob :: forall a f. (Foldable f, BitPack a) => String -> Maybe Bit -> f a -> DecsQ
- memBlobTH :: forall a f. (Foldable f, BitPack a) => Maybe Bit -> f a -> ExpQ
- unpackMemBlob :: forall n m. MemBlob n m -> [BitVector m]
BlockRAMs initialized with a MemBlob
:: forall dom addr m n. (HiddenClock dom, HiddenEnable dom, Enum addr, NFDataX addr) | |
=> MemBlob n m | Initial content of the BRAM, also determines the size, NB: MUST be a constant |
-> Signal dom addr | Read address |
-> Signal dom (Maybe (addr, BitVector m)) | (write address |
-> Signal dom (BitVector m) | Value of the BRAM at address |
Create a block RAM 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
See also:
- 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
(blockRamBlob
content) rd wrM
:: forall dom m n. (HiddenClock dom, HiddenEnable dom, KnownNat n) | |
=> MemBlob (2 ^ n) m | Initial content of the BRAM, also determines the size, 2^ NB: MUST be a constant |
-> Signal dom (Unsigned n) | Read address |
-> Signal dom (Maybe (Unsigned n, BitVector m)) | (write address |
-> Signal dom (BitVector m) | Value of the BRAM at address |
Create a block RAM 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
See also:
- 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
(blockRamBlobPow2
content) rd wrM
Creating and inspecting MemBlob
data MemBlob (n :: Nat) (m :: Nat) Source #
Efficient storage of memory content
It holds n
words of
.BitVector
m
:: forall a f. (Foldable f, BitPack a) | |
=> String | Name of the binding to generate |
-> Maybe Bit | Value to map don't care bits to. |
-> f a | The content for the |
-> DecsQ |
Create a MemBlob
binding from a list of values
Since this uses Template Haskell, nothing in the arguments given to
createMemBlob
can refer to something defined in the same module.
Example
createMemBlob
"content"Nothing
[15 :: Unsigned 8 .. 17] ram clk en =blockRamBlob
clk en content
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.
>>>
import qualified Prelude as P
>>>
let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
>>>
:{
createMemBlob "content0" (Just 0) es createMemBlob "content1" (Just 1) es x = 1 :}
>>>
let pr = mapM_ (putStrLn . show)
>>>
pr $ P.map pack es
0b0_...._.... 0b1_0000_0111 0b1_0000_1000>>>
pr $ unpackMemBlob content0
0b0_0000_0000 0b1_0000_0111 0b1_0000_1000>>>
pr $ unpackMemBlob content1
0b0_1111_1111 0b1_0000_0111 0b1_0000_1000>>>
:{
createMemBlob "contentN" Nothing es x = 1 :} <interactive>:...: error:... packBVs: cannot convert don't care values. Please specify a mapping to a definite value.
Note how we hinted to clashi
that our multi-line command was a list of
declarations by including a dummy declaration x = 1
. Without this trick,
clashi
would expect an expression and the Template Haskell would not work.
:: forall a f. (Foldable f, BitPack a) | |
=> Maybe Bit | Value to map don't care bits to. |
-> f a | The content for the |
-> ExpQ |
Create a MemBlob
from a list of values
Since this uses Template Haskell, nothing in the arguments given to
memBlobTH
can refer to something defined in the same module.
Example
ram clk en = blockRamBlob
clk en $(memBlobTH Nothing [15 :: Unsigned 8 .. 17])
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.
>>>
import qualified Prelude as P
>>>
let es = [ Nothing, Just (7 :: Unsigned 8), Just 8 ]
>>>
content0 = $(memBlobTH (Just 0) es)
>>>
content1 = $(memBlobTH (Just 1) es)
>>>
let pr = mapM_ (putStrLn . show)
>>>
pr $ P.map pack es
0b0_...._.... 0b1_0000_0111 0b1_0000_1000>>>
pr $ unpackMemBlob content0
0b0_0000_0000 0b1_0000_0111 0b1_0000_1000>>>
pr $ unpackMemBlob content1
0b0_1111_1111 0b1_0000_0111 0b1_0000_1000>>>
$(memBlobTH Nothing es)
<interactive>:...: error:... • packBVs: cannot convert don't care values. Please specify a mapping to a definite value. • In the untyped splice: $(memBlobTH Nothing es)