clash-prelude-1.4.1: Clash: a functional hardware description language - Prelude library
Copyright(C) 2015-2016 University of Twente
2017 Google Inc.
2019 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellUnsafe
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • BangPatterns
  • ViewPatterns
  • DataKinds
  • InstanceSigs
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • DeriveGeneric
  • DefaultSignatures
  • DeriveLift
  • DerivingStrategies
  • FlexibleContexts
  • MagicHash
  • KindSignatures
  • TupleSections
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • BinaryLiterals
  • TypeApplications

Clash.Prelude.ROM.File

Description

Initializing a ROM with a data file

ROMs initialized 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 synchronous ROM 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 <$> romFile d7 "memory.bin" rd

And 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 rd = unpack <$> romFile d7 "memory.bin" rd

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

Asynchronous ROM

asyncRomFile Source #

Arguments

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

Size of the ROM

-> FilePath

File describing the content of the ROM

-> addr

Read address rd

-> BitVector m

The value of the ROM at address rd

An asynchronous/combinational ROM with space for n elements

  • 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.ROM.File for more information on how to instantiate a ROM with the contents of a data file.
  • See Clash.Sized.Fixed for ideas on how to create your own data files.
  • When you notice that asyncRomFile is significantly slowing down your simulation, give it a monomorphic type signature. So instead of leaving the type to be inferred:

    myRomData = asyncRomFile d512 "memory.bin"
    

    or giving it a polymorphic type signature:

    myRomData :: Enum addr => addr -> BitVector 16
    myRomData = asyncRomFile d512 "memory.bin"
    

    you should give it a monomorphic type signature:

    myRomData :: Unsigned 9 -> BitVector 16
    myRomData = asyncRomFile d512 "memory.bin"
    

asyncRomFilePow2 Source #

Arguments

:: forall n m. (KnownNat m, KnownNat n) 
=> FilePath

File describing the content of the ROM

-> Unsigned n

Read address rd

-> BitVector m

The value of the ROM at address rd

An asynchronous/combinational ROM with space for 2^n elements

  • 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.ROM.File for more information on how to instantiate a ROM with the contents of a data file.
  • See Clash.Sized.Fixed for ideas on how to create your own data files.
  • When you notice that asyncRomFilePow2 is significantly slowing down your simulation, give it a monomorphic type signature. So instead of leaving the type to be inferred:

    myRomData = asyncRomFilePow2 "memory.bin"
    

    you should give it a monomorphic type signature:

    myRomData :: Unsigned 9 -> BitVector 16
    myRomData = asyncRomFilePow2 "memory.bin"
    

Synchronous ROM synchronized to an arbitrary clock

romFile Source #

Arguments

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

Size of the ROM

-> FilePath

File describing the content of the ROM

-> Signal dom addr

Read address rd

-> Signal dom (BitVector m)

The value of the ROM at address rd from the previous clock cycle

A ROM with a synchronous read port, 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:

romFilePow2 Source #

Arguments

:: forall n m dom. (KnownNat m, KnownNat n, HiddenClock dom, HiddenEnable dom) 
=> FilePath

File describing the content of the ROM

-> Signal dom (Unsigned n)

Read address rd

-> Signal dom (BitVector m)

The value of the ROM at address rd from the previous clock cycle

A ROM with a synchronous read port, 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

asyncRomFile# Source #

Arguments

:: KnownNat m 
=> SNat n

Size of the ROM

-> FilePath

File describing the content of the ROM

-> Int

Read address rd

-> BitVector m

The value of the ROM at address rd

asyncROMFile primitive