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 |
|
Initialising a ROM with a data file
ROMs initialised 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 synchronous ROM using the content of the above file like so:
topEntity :: Signal (Unsigned 3) -> Signal (Unsigned 9) topEntity rd =unpack
<$>
romFile
d7 "memory.bin" rd
And 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
<$>
romFile
d7 "memory.bin" rd
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)]
- asyncRomFile :: (KnownNat m, Enum addr) => SNat n -> FilePath -> addr -> BitVector m
- asyncRomFilePow2 :: forall n m. (KnownNat m, KnownNat n, KnownNat (2 ^ n)) => FilePath -> Unsigned n -> BitVector m
- romFile :: (KnownNat m, KnownNat k) => SNat n -> FilePath -> Signal (Unsigned k) -> Signal (BitVector m)
- romFilePow2 :: forall n m. (KnownNat m, KnownNat n, KnownNat (2 ^ n)) => FilePath -> Signal (Unsigned n) -> Signal (BitVector m)
- romFile' :: (KnownNat m, Enum addr) => SClock clk -> SNat n -> FilePath -> Signal' clk addr -> Signal' clk (BitVector m)
- romFilePow2' :: forall clk n m. (KnownNat m, KnownNat n, KnownNat (2 ^ n)) => SClock clk -> FilePath -> Signal' clk (Unsigned n) -> Signal' clk (BitVector m)
- asyncRomFile# :: KnownNat m => SNat n -> FilePath -> Int -> BitVector m
- romFile# :: KnownNat m => SClock clk -> SNat n -> FilePath -> Signal' clk Int -> Signal' clk (BitVector m)
Asynchronous ROM
:: (KnownNat m, Enum addr) | |
=> SNat n | Size of the ROM |
-> FilePath | File describing the content of the ROM |
-> addr | Read address |
-> BitVector m | The value of the ROM at address |
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"
:: (KnownNat m, KnownNat n, KnownNat (2 ^ n)) | |
=> FilePath | File describing the content of the ROM |
-> Unsigned n | Read address |
-> BitVector m | The value of the ROM at address |
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 synchronised to the system clock
:: (KnownNat m, KnownNat k) | |
=> SNat n | Size of the ROM |
-> FilePath | File describing the content of the ROM |
-> Signal (Unsigned k) | Read address |
-> Signal (BitVector m) | The value of the ROM at address |
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:
- 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.
:: (KnownNat m, KnownNat n, KnownNat (2 ^ n)) | |
=> FilePath | File describing the content of the ROM |
-> Signal (Unsigned n) | Read address |
-> Signal (BitVector m) | The value of the ROM at address |
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:
- 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.
Synchronous ROM synchronised to an arbitrary clock
:: (KnownNat m, Enum addr) | |
=> SClock clk |
|
-> SNat n | Size of the ROM |
-> FilePath | File describing the content of the ROM |
-> Signal' clk addr | Read address |
-> Signal' clk (BitVector m) | The value of the ROM at address |
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:
- 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.
:: (KnownNat m, KnownNat n, KnownNat (2 ^ n)) | |
=> SClock clk |
|
-> FilePath | File describing the content of the ROM |
-> Signal' clk (Unsigned n) | Read address |
-> Signal' clk (BitVector m) | The value of the ROM at address |
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:
- 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.