| Copyright | (C) 2015-2016, University of Twente | 
|---|---|
| License | BSD2 (see the file LICENSE) | 
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> | 
| Safe Haskell | Unsafe | 
| Language | Haskell2010 | 
| Extensions | 
 | 
CLaSH.Prelude.BlockRam.File
Contents
Description
Initialising a BlockRAM with a data file
BlockRAM primitives that can be initialised with a data file. The BNF grammar for this data file is simple:
FILE = LINE+
LINE = BIT+
BIT  = '0'
     | '1'
Consecutive LINEs 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:
topEntity :: Signal (Unsigned 3) -> Signal (Unsigned 9) topEntity rd =unpack<$>blockRamFiled7 "memory.bin" 0 rd (signal False) 0
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 $ topEntity (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:
topEntity2 :: Signal (Unsigned 3) -> Signal (Unsigned 6,Signed 3) topEntity2 rd =unpack<$>blockRamFiled7 "memory.bin" 0 rd (signal False) 0
And then we would see:
>>> import qualified Data.List as L >>> L.tail $ sampleN 4 $ topEntity2 (fromList [3..5]) [(1,2),(1,3)(1,-4)]
- blockRamFile :: (KnownNat m, Enum addr) => SNat n -> FilePath -> Signal addr -> Signal addr -> Signal Bool -> Signal (BitVector m) -> Signal (BitVector m)
- blockRamFilePow2 :: forall n m. (KnownNat m, KnownNat n, KnownNat (2 ^ n)) => FilePath -> Signal (Unsigned n) -> Signal (Unsigned n) -> Signal Bool -> Signal (BitVector m) -> Signal (BitVector m)
- blockRamFile' :: (KnownNat m, Enum addr) => SClock clk -> SNat n -> FilePath -> Signal' clk addr -> Signal' clk addr -> Signal' clk Bool -> Signal' clk (BitVector m) -> Signal' clk (BitVector m)
- blockRamFilePow2' :: forall clk n m. (KnownNat m, KnownNat n, KnownNat (2 ^ n)) => SClock clk -> FilePath -> Signal' clk (Unsigned n) -> Signal' clk (Unsigned n) -> Signal' clk Bool -> Signal' clk (BitVector m) -> Signal' clk (BitVector m)
- blockRamFile# :: KnownNat m => SClock clk -> SNat n -> FilePath -> Signal' clk Int -> Signal' clk Int -> Signal' clk Bool -> Signal' clk (BitVector m) -> Signal' clk (BitVector m)
- initMem :: KnownNat n => FilePath -> IO [BitVector n]
BlockRAM synchronised to the system clock
Arguments
| :: (KnownNat m, Enum addr) | |
| => SNat n | Size of the blockRAM | 
| -> FilePath | File describing the initial content of the blockRAM | 
| -> Signal addr | Write address  | 
| -> Signal addr | Read address  | 
| -> Signal Bool | Write enable | 
| -> Signal (BitVector m) | Value to write (at address  | 
| -> Signal (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
- 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 readNewfor obtaining write-before-read semantics like this:readNew (blockRamFile size file) wr rd en dt.
- 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.
Arguments
| :: (KnownNat m, KnownNat n, KnownNat (2 ^ n)) | |
| => FilePath | File describing the initial content of the blockRAM | 
| -> Signal (Unsigned n) | Write address  | 
| -> Signal (Unsigned n) | Read address  | 
| -> Signal Bool | Write enable | 
| -> Signal (BitVector m) | Value to write (at address  | 
| -> Signal (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
- 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 readNewfor obtaining write-before-read semantics like this:readNew (blockRamFilePow2 file) wr rd en dt.
- 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.
BlockRAM synchronised to an arbitrary clock
Arguments
| :: (KnownNat m, Enum addr) | |
| => SClock clk | 
 | 
| -> SNat n | Size of the blockRAM | 
| -> FilePath | File describing the initial content of the blockRAM | 
| -> Signal' clk addr | Write address  | 
| -> Signal' clk addr | Read address  | 
| -> Signal' clk Bool | Write enable | 
| -> Signal' clk (BitVector m) | Value to write (at address  | 
| -> Signal' clk (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
- 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 (blockRamFile' clk size file) wr rd en dt.
- 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.
Arguments
| :: (KnownNat m, KnownNat n, KnownNat (2 ^ n)) | |
| => SClock clk | 
 | 
| -> FilePath | File describing the initial content of the blockRAM | 
| -> Signal' clk (Unsigned n) | Write address  | 
| -> Signal' clk (Unsigned n) | Read address  | 
| -> Signal' clk Bool | Write enable | 
| -> Signal' clk (BitVector m) | Value to write (at address  | 
| -> Signal' clk (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
- 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 (blockRamFilePow2' clk file) wr rd en dt.
- 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.
Internal
Arguments
| :: KnownNat m | |
| => SClock clk | 
 | 
| -> SNat n | Size of the blockRAM | 
| -> FilePath | File describing the initial content of the blockRAM | 
| -> Signal' clk Int | Write address  | 
| -> Signal' clk Int | Read address  | 
| -> Signal' clk Bool | Write enable | 
| -> Signal' clk (BitVector m) | Value to write (at address  | 
| -> Signal' clk (BitVector m) | Value of the  | 
blockRamFile primitive