clash-prelude-0.10.1: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2015, University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellUnsafe
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • DataKinds
  • FlexibleContexts
  • MagicHash
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll

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 <$> blockRamFile d7 "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 <$> blockRamFile d7 "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)]

Synopsis

BlockRAM synchronised to the system clock

blockRamFile Source

Arguments

:: (KnownNat m, Enum addr) 
=> SNat n

Size of the blockRAM

-> FilePath

File describing the initial content of the blockRAM

-> Signal addr

Write address w

-> Signal addr

Read address r

-> Signal Bool

Write enable

-> Signal (BitVector m)

Value to write (at address w)

-> Signal (BitVector m)

Value of the blockRAM at address r from the previous clock cycle

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:

blockRamFilePow2 Source

Arguments

:: (KnownNat m, KnownNat n, KnownNat (2 ^ n)) 
=> FilePath

File describing the initial content of the blockRAM

-> Signal (Unsigned n)

Write address w

-> Signal (Unsigned n)

Read address r

-> Signal Bool

Write enable

-> Signal (BitVector m)

Value to write (at address w)

-> Signal (BitVector m)

Value of the blockRAM at address r from the previous clock cycle

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:

BlockRAM synchronised to an arbitrary clock

blockRamFile' Source

Arguments

:: (KnownNat m, Enum addr) 
=> SClock clk

Clock to synchronize to

-> SNat n

Size of the blockRAM

-> FilePath

File describing the initial content of the blockRAM

-> Signal' clk addr

Write address w

-> Signal' clk addr

Read address r

-> Signal' clk Bool

Write enable

-> Signal' clk (BitVector m)

Value to write (at address w)

-> Signal' clk (BitVector m)

Value of the blockRAM at address r from the previous clock cycle

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:

blockRamFilePow2' Source

Arguments

:: (KnownNat m, KnownNat n, KnownNat (2 ^ n)) 
=> SClock clk

Clock to synchronize to

-> FilePath

File describing the initial content of the blockRAM

-> Signal' clk (Unsigned n)

Write address w

-> Signal' clk (Unsigned n)

Read address r

-> Signal' clk Bool

Write enable

-> Signal' clk (BitVector m)

Value to write (at address w)

-> Signal' clk (BitVector m)

Value of the blockRAM at address r from the previous clock cycle

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:

Internal

blockRamFile# Source

Arguments

:: KnownNat m 
=> SClock clk

Clock to synchronize to

-> SNat n

Size of the blockRAM

-> FilePath

File describing the initial content of the blockRAM

-> Signal' clk Int

Write address w

-> Signal' clk Int

Read address r

-> Signal' clk Bool

Write enable

-> Signal' clk (BitVector m)

Value to write (at address w)

-> Signal' clk (BitVector m)

Value of the blockRAM at address r from the previous clock cycle

blockRamFile primitive

initMem :: KnownNat n => FilePath -> [BitVector n] Source

NB: Not synthesisable