Copyright | (C) 2013-2016 University of Twente 2017 Myrtle Software Ltd Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Unsafe |
Language | Haskell2010 |
Extensions |
|
CλaSH (pronounced ‘clash’) is a functional hardware description language that borrows both its syntax and semantics from the functional programming language Haskell. The merits of using a functional language to describe hardware comes from the fact that combinational circuits can be directly modeled as mathematical functions and that functional languages lend themselves very well at describing and (de-)composing mathematical functions.
This package provides:
- Prelude library containing datatypes and functions for circuit design
To use the library:
- Import Clash.Prelude; by default clock and reset lines are implicitly routed for all the components found in Clash.Prelude. You can read more about implicit clock and reset lines in Clash.Signal
- Alternatively, if you want to explicitly route clock and reset ports, for more straightforward multi-clock designs, you can import the Clash.Explicit.Prelude module. Note that you should not import Clash.Prelude and Clash.Explicit.Prelude at the same time as they have overlapping definitions.
For now, Clash.Prelude is also the best starting point for exploring the library. A preliminary version of a tutorial can be found in Clash.Tutorial. Some circuit examples can be found in Clash.Examples.
Synopsis
- mealy :: HiddenClockReset domain gated synchronous => (s -> i -> (s, o)) -> s -> Signal domain i -> Signal domain o
- mealyB :: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) => (s -> i -> (s, o)) -> s -> Unbundled domain i -> Unbundled domain o
- (<^>) :: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) => (s -> i -> (s, o)) -> s -> Unbundled domain i -> Unbundled domain o
- moore :: HiddenClockReset domain gated synchronous => (s -> i -> s) -> (s -> o) -> s -> Signal domain i -> Signal domain o
- mooreB :: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) => (s -> i -> s) -> (s -> o) -> s -> Unbundled domain i -> Unbundled domain o
- registerB :: (HiddenClockReset domain gated synchronous, Bundle a) => a -> Unbundled domain a -> Unbundled domain a
- asyncRom :: (KnownNat n, Enum addr) => Vec n a -> addr -> a
- asyncRomPow2 :: KnownNat n => Vec (2 ^ n) a -> Unsigned n -> a
- rom :: (KnownNat n, KnownNat m, HiddenClock domain gated) => Vec n a -> Signal domain (Unsigned m) -> Signal domain a
- romPow2 :: (KnownNat n, HiddenClock domain gated) => Vec (2 ^ n) a -> Signal domain (Unsigned n) -> Signal domain a
- asyncRomFile :: (KnownNat m, Enum addr) => SNat n -> FilePath -> addr -> BitVector m
- asyncRomFilePow2 :: forall n m. (KnownNat m, KnownNat n) => FilePath -> Unsigned n -> BitVector m
- romFile :: (KnownNat m, KnownNat n, HiddenClock domain gated) => SNat n -> FilePath -> Signal domain (Unsigned n) -> Signal domain (BitVector m)
- romFilePow2 :: forall n m domain gated. (KnownNat m, KnownNat n, HiddenClock domain gated) => FilePath -> Signal domain (Unsigned n) -> Signal domain (BitVector m)
- asyncRam :: (Enum addr, HiddenClock domain gated, HasCallStack) => SNat n -> Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
- asyncRamPow2 :: (KnownNat n, HiddenClock domain gated, HasCallStack) => Signal domain (Unsigned n) -> Signal domain (Maybe (Unsigned n, a)) -> Signal domain a
- blockRam :: (Enum addr, HiddenClock domain gated, HasCallStack) => Vec n a -> Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
- blockRamPow2 :: (KnownNat n, HiddenClock domain gated, HasCallStack) => Vec (2 ^ n) a -> Signal domain (Unsigned n) -> Signal domain (Maybe (Unsigned n, a)) -> Signal domain a
- blockRamFile :: (KnownNat m, Enum addr, HiddenClock domain gated, HasCallStack) => SNat n -> FilePath -> Signal domain addr -> Signal domain (Maybe (addr, BitVector m)) -> Signal domain (BitVector m)
- blockRamFilePow2 :: forall domain gated n m. (KnownNat m, KnownNat n, HiddenClock domain gated, HasCallStack) => FilePath -> Signal domain (Unsigned n) -> Signal domain (Maybe (Unsigned n, BitVector m)) -> Signal domain (BitVector m)
- readNew :: (Eq addr, HiddenClockReset domain gated synchronous) => (Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a) -> Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
- window :: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) => Signal domain a -> Vec (n + 1) (Signal domain a)
- windowD :: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) => Signal domain a -> Vec (n + 1) (Signal domain a)
- isRising :: (HiddenClockReset domain gated synchronous, Bounded a, Eq a) => a -> Signal domain a -> Signal domain Bool
- isFalling :: (HiddenClockReset domain gated synchronous, Bounded a, Eq a) => a -> Signal domain a -> Signal domain Bool
- riseEvery :: HiddenClockReset domain gated synchronous => SNat n -> Signal domain Bool
- oscillate :: HiddenClockReset domain gated synchronous => Bool -> SNat n -> Signal domain Bool
- module Clash.Signal
- module Clash.Signal.Delayed
- module Clash.Prelude.DataFlow
- module Clash.Sized.BitVector
- module Clash.Prelude.BitIndex
- module Clash.Prelude.BitReduction
- module Clash.Sized.Signed
- module Clash.Sized.Unsigned
- module Clash.Sized.Index
- module Clash.Sized.Fixed
- module Clash.Sized.Vector
- module Clash.Sized.RTree
- module Clash.Annotations.TopEntity
- module GHC.TypeLits
- module Clash.Promoted.Nat
- module Clash.Promoted.Nat.Literals
- module Clash.Promoted.Nat.TH
- module Clash.Promoted.Symbol
- class Lift t where
- module Clash.Class.BitPack
- module Clash.Class.Num
- module Clash.Class.Resize
- module Control.Applicative
- module Data.Bits
- module Clash.XException
- undefined :: HasCallStack => a
- module Clash.NamedTypes
- module Clash.Hidden
- seq :: a -> b -> b
- filter :: (a -> Bool) -> [a] -> [a]
- print :: Show a => a -> IO ()
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- otherwise :: Bool
- ($) :: (a -> b) -> a -> b
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Bounded a where
- class Enum a where
- class Eq a where
- class Fractional a => Floating a where
- class Num a => Fractional a where
- class (Real a, Enum a) => Integral a where
- class Applicative m => Monad (m :: * -> *) where
- class Functor (f :: * -> *) where
- class Num a where
- class Eq a => Ord a where
- class Read a where
- class (Num a, Ord a) => Real a where
- class (RealFrac a, Floating a) => RealFloat a where
- class (Real a, Fractional a) => RealFrac a where
- class Show a where
- class Functor f => Applicative (f :: * -> *) where
- class Foldable (t :: * -> *) where
- class (Functor t, Foldable t) => Traversable (t :: * -> *) where
- class Semigroup a where
- class Semigroup a => Monoid a where
- data Bool
- data Char
- data Double
- data Float
- data Int
- data Integer
- data Maybe a
- data Ordering
- type Rational = Ratio Integer
- data IO a
- data Word
- data Either a b
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- appendFile :: FilePath -> String -> IO ()
- writeFile :: FilePath -> String -> IO ()
- readFile :: FilePath -> IO String
- interact :: (String -> String) -> IO ()
- getContents :: IO String
- getLine :: IO String
- getChar :: IO Char
- putStrLn :: String -> IO ()
- putStr :: String -> IO ()
- putChar :: Char -> IO ()
- ioError :: IOError -> IO a
- type FilePath = String
- userError :: String -> IOError
- type IOError = IOException
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- or :: Foldable t => t Bool -> Bool
- and :: Foldable t => t Bool -> Bool
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- unwords :: [String] -> String
- words :: String -> [String]
- unlines :: [String] -> String
- lines :: String -> [String]
- read :: Read a => String -> a
- reads :: Read a => ReadS a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- lex :: ReadS String
- readParen :: Bool -> ReadS a -> ReadS a
- type ReadS a = String -> [(a, String)]
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- lcm :: Integral a => a -> a -> a
- gcd :: Integral a => a -> a -> a
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- (^) :: (Num a, Integral b) => a -> b -> a
- odd :: Integral a => a -> Bool
- even :: Integral a => a -> Bool
- showParen :: Bool -> ShowS -> ShowS
- showString :: String -> ShowS
- showChar :: Char -> ShowS
- shows :: Show a => a -> ShowS
- type ShowS = String -> String
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- break :: (a -> Bool) -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- cycle :: [a] -> [a]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- maybe :: b -> (a -> b) -> Maybe a -> b
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- subtract :: Num a => a -> a -> a
- asTypeOf :: a -> a -> a
- until :: (a -> Bool) -> (a -> a) -> a -> a
- ($!) :: (a -> b) -> a -> b
- flip :: (a -> b -> c) -> b -> a -> c
- (.) :: (b -> c) -> (a -> b) -> a -> c
- const :: a -> b -> a
- id :: a -> a
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- type String = [Char]
- errorWithoutStackTrace :: [Char] -> a
- error :: HasCallStack => [Char] -> a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
Creating synchronous sequential circuits
:: HiddenClockReset domain gated synchronous | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Signal domain i -> Signal domain o | Synchronous sequential function with input and output matching that of the mealy machine |
Create a synchronous function from a combinational function describing a mealy machine
macT :: Int -- Current state -> (Int,Int) -- Input -> (Int,Int) -- (Updated state, output) macT s (x,y) = (s',s) where s' = x * y + s mac :: HiddenClockReset domain gated synchronous =>Signal
domain (Int, Int) ->Signal
domain Int mac =mealy
macT 0
>>>
simulate mac [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14... ...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac :: HiddenClockReset domain gated synchronous => (Signal
domain Int,Signal
domain Int) -> (Signal
domain Int,Signal
domain Int) ->Signal
domain Int dualMac (a,b) (x,y) = s1 + s2 where s1 =mealy
mac 0 (bundle
(a,x)) s2 =mealy
mac 0 (bundle
(b,y))
:: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Unbundled domain i -> Unbundled domain o | Synchronous sequential function with input and output matching that of the mealy machine |
A version of mealy
that does automatic Bundle
ing
Given a function f
of type:
f :: Int -> (Bool, Int) -> (Int, (Int, Bool))
When we want to make compositions of f
in g
using mealy
, we have to
write:
g a b c = (b1,b2,i2) where (i1,b1) =unbundle
(mealy
f 0 (bundle
(a,b))) (i2,b2) =unbundle
(mealy
f 3 (bundle
(i1,c)))
Using mealyB
however we can write:
g a b c = (b1,b2,i2) where (i1,b1) =mealyB
f 0 (a,b) (i2,b2) =mealyB
f 3 (i1,c)
:: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) | |
=> (s -> i -> (s, o)) | Transfer function in mealy machine form:
|
-> s | Initial state |
-> Unbundled domain i -> Unbundled domain o | Synchronous sequential function with input and output matching that of the mealy machine |
Infix version of mealyB
:: HiddenClockReset domain gated synchronous | |
=> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Signal domain i -> Signal domain o | Synchronous sequential function with input and output matching that of the moore machine |
Create a synchronous function from a combinational function describing a moore machine
macT :: Int -- Current state -> (Int,Int) -- Input -> Int -- Updated state macT s (x,y) = x * y + s mac :: HiddenClockReset domain gated synchronous =>Signal
domain (Int, Int) ->Signal
domain Int mac =moore
mac id 0
>>>
simulate mac [(1,1),(2,2),(3,3),(4,4)]
[0,1,5,14... ...
Synchronous sequential functions can be composed just like their combinational counterpart:
dualMac :: HiddenClockReset domain gated synchronous => (Signal
domain Int,Signal
domain Int) -> (Signal
domain Int,Signal
domain Int) ->Signal
domain Int dualMac (a,b) (x,y) = s1 + s2 where s1 =moore
mac id 0 (bundle
(a,x)) s2 =moore
mac id 0 (bundle
(b,y))
:: (Bundle i, Bundle o, HiddenClockReset domain gated synchronous) | |
=> (s -> i -> s) | Transfer function in moore machine form:
|
-> (s -> o) | Output function in moore machine form:
|
-> s | Initial state |
-> Unbundled domain i -> Unbundled domain o | Synchronous sequential function with input and output matching that of the moore machine |
A version of moore
that does automatic Bundle
ing
Given a functions t
and o
of types:
t :: Int -> (Bool, Int) -> Int o :: Int -> (Int, Bool)
When we want to make compositions of t
and o
in g
using moore
, we have to
write:
g a b c = (b1,b2,i2) where (i1,b1) =unbundle
(moore
t o 0 (bundle
(a,b))) (i2,b2) =unbundle
(moore
t o 3 (bundle
(i1,c)))
Using mooreB
however we can write:
g a b c = (b1,b2,i2) where (i1,b1) =mooreB
t o 0 (a,b) (i2,b2) =mooreB
t o 3 (i1,c)
registerB :: (HiddenClockReset domain gated synchronous, Bundle a) => a -> Unbundled domain a -> Unbundled domain a infixr 3 Source #
Create a register
function for product-type like signals (e.g. '(Signal a, Signal b)')
rP :: HiddenClockReset domain gated synchronous => (Signal domain Int, Signal domain Int) -> (Signal domain Int, Signal domain Int) rP = registerB (8,8)
>>>
simulateB rP [(1,1),(2,2),(3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)... ...
ROMs
:: (KnownNat n, Enum addr) | |
=> Vec n a | ROM content NB: must be a constant |
-> addr | Read address |
-> a | The value of the ROM at address |
An asynchronous/combinational ROM with space for n
elements
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
:: KnownNat n | |
=> Vec (2 ^ n) a | ROM content NB: must be a constant |
-> Unsigned n | Read address |
-> a | The value of the ROM at address |
An asynchronous/combinational ROM with space for 2^n
elements
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
:: (KnownNat n, KnownNat m, HiddenClock domain gated) | |
=> Vec n a | ROM content NB: must be a constant |
-> Signal domain (Unsigned m) | Read address |
-> Signal domain a | 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
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
:: (KnownNat n, HiddenClock domain gated) | |
=> Vec (2 ^ n) a | ROM content NB: must be a constant |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain a | 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
Additional helpful information:
- See Clash.Sized.Fixed and Clash.Prelude.BlockRam for ideas on how to use ROMs and RAMs
ROMs initialised with a data file
:: (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) | |
=> 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"
:: (KnownNat m, KnownNat n, HiddenClock domain gated) | |
=> SNat n | Size of the ROM |
-> FilePath | File describing the content of the ROM |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (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, HiddenClock domain gated) | |
=> FilePath | File describing the content of the ROM |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (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.
RAM primitives with a combinational read port
:: (Enum addr, HiddenClock domain gated, HasCallStack) | |
=> SNat n | Size |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, a)) | (write address |
-> Signal domain a | Value of the |
Create a RAM with space for n
elements.
- NB: Initial content of the RAM is
undefined
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a RAM.
:: (KnownNat n, HiddenClock domain gated, HasCallStack) | |
=> Signal domain (Unsigned n) | Read address |
-> Signal domain (Maybe (Unsigned n, a)) | (write address |
-> Signal domain a | Value of the |
Create a RAM with space for 2^n
elements
- NB: Initial content of the RAM is
undefined
Additional helpful information:
- See Clash.Prelude.BlockRam for more information on how to use a RAM.
BlockRAM primitives
:: (Enum addr, HiddenClock domain gated, HasCallStack) | |
=> Vec n a | Initial content of the BRAM, also
determines the size, NB: MUST be a constant. |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, a)) | (write address |
-> Signal domain a | 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
bram40 ::HiddenClock
domain =>Signal
domain (Unsigned
6) ->Signal
domain (Maybe (Unsigned
6,Bit
)) ->Signal
domainBit
bram40 =blockRam
(replicate
d40 1)
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 (blockRam inits) rd wrM
.
:: (KnownNat n, HiddenClock domain gated, HasCallStack) | |
=> Vec (2 ^ n) a | Initial content of the BRAM, also
determines the size, NB: MUST be a constant. |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (Maybe (Unsigned n, a)) | (write address |
-> Signal domain a | 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
bram32 ::HiddenClock
domain =>Signal
domain (Unsigned
5) ->Signal
domain (Maybe (Unsigned
5,Bit
)) ->Signal
domainBit
bram32 =blockRamPow2
(replicate
d32 1)
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 (blockRamPow2 inits) rd wrM
.
BlockRAM primitives initialised with a data file
:: (KnownNat m, Enum addr, HiddenClock domain gated, HasCallStack) | |
=> SNat n | Size of the blockRAM |
-> FilePath | File describing the initial content of the blockRAM |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, BitVector m)) | (write address |
-> Signal domain (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) rd wrM
. - 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.
:: (KnownNat m, KnownNat n, HiddenClock domain gated, HasCallStack) | |
=> FilePath | File describing the initial content of the blockRAM |
-> Signal domain (Unsigned n) | Read address |
-> Signal domain (Maybe (Unsigned n, BitVector m)) | (write address |
-> Signal domain (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) rd wrM
. - 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 read/write conflict resolution
:: (Eq addr, HiddenClockReset domain gated synchronous) | |
=> (Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a) | The |
-> Signal domain addr | Read address |
-> Signal domain (Maybe (addr, a)) | (Write address |
-> Signal domain a | Value of the |
Create read-after-write blockRAM from a read-before-write one (synchronised to system clock)
>>>
import Clash.Prelude
>>>
:t readNew (blockRam (0 :> 1 :> Nil))
readNew (blockRam (0 :> 1 :> Nil)) :: ... ... => Signal domain addr -> Signal domain (Maybe (addr, a)) -> Signal domain a
Utility functions
:: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) | |
=> Signal domain a | Signal to create a window over |
-> Vec (n + 1) (Signal domain a) | Window of at least size 1 |
Give a window over a Signal
window4 :: HiddenClockReset domain gated synchronous => Signal domain Int -> Vec 4 (Signal domain Int) window4 = window
>>>
simulateB window4 [1::Int,2,3,4,5] :: [Vec 4 Int]
[<1,0,0,0>,<2,1,0,0>,<3,2,1,0>,<4,3,2,1>,<5,4,3,2>... ...
:: (KnownNat n, Default a, HiddenClockReset domain gated synchronous) | |
=> Signal domain a | Signal to create a window over |
-> Vec (n + 1) (Signal domain a) | Window of at least size 1 |
Give a delayed window over a Signal
windowD3 :: HiddenClockReset domain gated synchronous => Signal domain Int -> Vec 3 (Signal domain Int) windowD3 = windowD
>>>
simulateB windowD3 [1::Int,2,3,4] :: [Vec 3 Int]
[<0,0,0>,<1,0,0>,<2,1,0>,<3,2,1>,<4,3,2>... ...
riseEvery :: HiddenClockReset domain gated synchronous => SNat n -> Signal domain Bool Source #
Give a pulse every n
clock cycles. This is a useful helper function when
combined with functions like
or regEn
,
in order to delay a register by a known amount.mux
To be precise: the given signal will be
for the next False
n-1
cycles,
followed by a single
value:True
>>>
Prelude.last (sampleN 1024 (riseEvery d1024)) == True
True>>>
Prelude.or (sampleN 1023 (riseEvery d1024)) == False
True
For example, to update a counter once every 10 million cycles:
counter =regEn
0 (riseEvery
(SNat
::SNat
10000000)) (counter + 1)
oscillate :: HiddenClockReset domain gated synchronous => Bool -> SNat n -> Signal domain Bool Source #
Oscillate a
for a given number of cycles. This is a convenient
function when combined with something like Bool
, as it allows you to
easily hold a register value for a given number of cycles. The input regEn
determines what the initial value is.Bool
To oscillate on an interval of 5 cycles:
>>>
sampleN 10 (oscillate False d5)
[False,False,False,False,False,True,True,True,True,True]
To oscillate between
and True
:False
>>>
sampleN 10 (oscillate False d1)
[False,True,False,True,False,True,False,True,False,True]
An alternative definition for the above could be:
>>>
let osc' = register False (not <$> osc')
>>>
let sample' = sampleN 200
>>>
sample' (oscillate False d1) == sample' osc'
True
Exported modules
Synchronous signals
module Clash.Signal
module Clash.Signal.Delayed
DataFlow interface
module Clash.Prelude.DataFlow
Datatypes
Bit vectors
module Clash.Sized.BitVector
module Clash.Prelude.BitIndex
module Clash.Prelude.BitReduction
Arbitrary-width numbers
module Clash.Sized.Signed
module Clash.Sized.Unsigned
module Clash.Sized.Index
Fixed point numbers
module Clash.Sized.Fixed
Fixed size vectors
module Clash.Sized.Vector
Perfect depth trees
module Clash.Sized.RTree
Annotations
module Clash.Annotations.TopEntity
Type-level natural numbers
module GHC.TypeLits
module Clash.Promoted.Nat
module Clash.Promoted.Nat.Literals
module Clash.Promoted.Nat.TH
Type-level strings
module Clash.Promoted.Symbol
Template Haskell
A Lift
instance can have any of its values turned into a Template
Haskell expression. This is needed when a value used within a Template
Haskell quotation is bound outside the Oxford brackets ([| ... |]
) but not
at the top level. As an example:
add1 :: Int -> Q Exp add1 x = [| x + 1 |]
Template Haskell has no way of knowing what value x
will take on at
splice-time, so it requires the type of x
to be an instance of Lift
.
A Lift
instance must satisfy $(lift x) ≡ x
for all x
, where $(...)
is a Template Haskell splice.
Lift
instances can be derived automatically by use of the -XDeriveLift
GHC language extension:
{-# LANGUAGE DeriveLift #-} module Foo where import Language.Haskell.TH.Syntax data Bar a = Bar1 a (Bar a) | Bar2 String deriving Lift
Instances
Type classes
Clash
module Clash.Class.BitPack
module Clash.Class.Num
module Clash.Class.Resize
Other
module Control.Applicative
module Data.Bits
Exceptions
module Clash.XException
undefined :: HasCallStack => a Source #
Named types
module Clash.NamedTypes
Hidden arguments
module Clash.Hidden
Haskell Prelude
Clash.Prelude re-exports most of the Haskell Prelude with the exception of the following: (++), (!!), concat, drop, foldl, foldl1, foldr, foldr1, head, init, iterate, last, length, map, repeat, replicate, reverse, scanl, scanr, splitAt, tail, take, unzip, unzip3, zip, zip3, zipWith, zipWith3.
It instead exports the identically named functions defined in terms of
Vec
at Clash.Sized.Vector.
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
filter :: (a -> Bool) -> [a] -> [a] #
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
print :: Show a => a -> IO () #
The print
function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show
; print
converts values to strings for output using the show
operation and
adds a newline.
For example, a program to print the first 20 integers and their powers of 2 could be written as:
main = print ([(n, 2^n) | n <- [0..19]])
($) :: (a -> b) -> a -> b infixr 0 #
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
fromIntegral :: (Integral a, Num b) => a -> b #
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> b #
general coercion to fractional types
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
.
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
.
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
.
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
.
Instances
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
Instances
class Fractional a => Floating a where #
Trigonometric and hyperbolic functions and related functions.