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

Safe HaskellNone
LanguageHaskell2010

CLaSH.Signal

Contents

Synopsis

Implicitly clocked synchronous signal

type Signal a = CSignal SystemClock a Source

Signal synchronised to the "system" clock, which has a period of 1000.

Basic circuit functions

signal :: a -> Signal a Source

Create a constant Signal from a combinational value

>>> sample (signal 4)
[4, 4, 4, 4, ...

register :: a -> Signal a -> Signal a Source

register i s delays the values in Signal s for one cycle, and sets the value at time 0 to i

>>> sampleN 3 (register 8 (fromList [1,2,3,4]))
[8,1,2]

regEn :: a -> Signal Bool -> Signal a -> Signal a Source

Version of register that only updates its content when its second argument is asserted. So given:

oscillate = register False (not1 oscillate)
count     = regEn 0 oscillate (count + 1)

We get:

>>> sampleN 8 oscillate
[False,True,False,True,False,True,False,True]
>>> sampleN 8 count
[0,0,1,1,2,2,3,3]

mux :: CSignal clk Bool -> CSignal clk a -> CSignal clk a -> CSignal clk a Source

A multiplexer. Given "mux b t f", output t when b is True, and f when b is False.

Boolean connectives

(.&&.) :: CSignal clk Bool -> CSignal clk Bool -> CSignal clk Bool infixr 3 Source

Version of (&&) that returns a CSignal of Bool

(.||.) :: CSignal clk Bool -> CSignal clk Bool -> CSignal clk Bool infixr 2 Source

Version of (||) that returns a CSignal of Bool

not1 :: CSignal clk Bool -> CSignal clk Bool Source

Version of not that operates on CSignals of Bool

Product/Signal isomorphism

class Bundle a Source

Isomorphism between a CSignal of a product type (e.g. a tuple) and a product type of CSignals.

Instances of Bundle must satisfy the following laws:

bundle . unbundle = id
unbundle . bundle = id

Instances

Bundle Bool 
Bundle Double 
Bundle Float 
Bundle Int 
Bundle Integer 
Bundle () 
Bundle (Maybe a) 
Bundle (Index n) 
Bundle (BitVector n) 
Bundle (Signed n) 
Bundle (Unsigned n) 
Bundle (Either a b) 
Bundle (a, b) 
KnownNat n => Bundle (Vec n a) 
Bundle (a, b, c) 
Bundle (Fixed rep int frac) 
Bundle (a, b, c, d) 
Bundle (a, b, c, d, e) 
Bundle (a, b, c, d, e, f) 
Bundle (a, b, c, d, e, f, g) 
Bundle (a, b, c, d, e, f, g, h) 

type Unbundled' a = Unbundled SystemClock a Source

Isomorphism between a Signal of a product type (e.g. a tuple) and a product type of Signals.

bundle' :: Bundle a => Unbundled' a -> Signal a Source

Example:

bundle' :: (Signal a, Signal b) -> Signal (a,b)

However:

bundle' :: Signal Bit -> Signal Bit

unbundle' :: Bundle a => Signal a -> Unbundled' a Source

Example:

unbundle' :: Signal (a,b) -> (Signal a, Signal b)

However:

unbundle' :: Signal Bit -> Signal Bit

Simulation functions (not synthesisable)

simulate :: (Signal a -> Signal b) -> [a] -> [b] Source

Simulate a (Signal a -> Signal b) function given a list of samples of type a

>>> simulate (register 8) [1, 2, 3, ...
[8, 1, 2, 3, ...

NB: This function is not synthesisable

simulateB :: (Bundle a, Bundle b) => (Unbundled' a -> Unbundled' b) -> [a] -> [b] Source

Simulate a (Bundled a -> Bundled b) function given a list of samples of type a

>>> simulateB (wrap . register (8,8) . unwrap) [(1,1), (2,2), (3,3), ...
[(8,8), (1,1), (2,2), (3,3), ...

NB: This function is not synthesisable

List <-> Signal conversion (not synthesisable)

sample :: Signal a -> [a] Source

Get an infinite list of samples from a Signal

The elements in the list correspond to the values of the Signal at consecutive clock cycles

sample s == [s0, s1, s2, s3, ...

NB: This function is not synthesisable

sampleN :: Int -> Signal a -> [a] Source

Get a list of n samples from a Signal

The elements in the list correspond to the values of the Signal at consecutive clock cycles

sampleN 3 s == [s0, s1, s2]

NB: This function is not synthesisable

fromList :: [a] -> Signal a Source

Create a Signal from a list

Every element in the list will correspond to a value of the signal for one clock cycle.

>>> sampleN 2 (fromList [1,2,3,4,5])
[1,2]

NB: This function is not synthesisable

Type classes

Eq-like

(.==.) :: Eq a => CSignal clk a -> CSignal clk a -> CSignal clk Bool infix 4 Source

Version of (==) that returns a CSignal of Bool

(./=.) :: Eq a => CSignal clk a -> CSignal clk a -> CSignal clk Bool infix 4 Source

Version of (/=) that returns a CSignal of Bool

Ord-like

compare1 :: Ord a => CSignal clk a -> CSignal clk a -> CSignal clk Ordering Source

Version of compare that returns a CSignal of Ordering

(.<.) :: Ord a => CSignal clk a -> CSignal clk a -> CSignal clk Bool infix 4 Source

Version of (<) that returns a CSignal of Bool

(.<=.) :: Ord a => CSignal clk a -> CSignal clk a -> CSignal clk Bool infix 4 Source

Version of (<=) that returns a CSignal of Bool

(.>=.) :: Ord a => CSignal clk a -> CSignal clk a -> CSignal clk Bool infix 4 Source

Version of (>=) that returns a CSignal of Bool

(.>.) :: Ord a => CSignal clk a -> CSignal clk a -> CSignal clk Bool infix 4 Source

Version of (>) that returns a CSignal of Bool

Enum-like

fromEnum1 :: Enum a => CSignal clk a -> CSignal clk Int Source

Version of fromEnum that returns a CSignal of Int

Rational-like

toRational1 :: Real a => CSignal clk a -> CSignal clk Rational Source

Version of toRational that returns a CSignal of Rational

Integral-like

toInteger1 :: Integral a => CSignal clk a -> CSignal clk Integer Source

Version of toRational that returns a CSignal of Integer

Bits-like

testBit1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk Bool Source

Version of testBit that has a CSignal of Int as indexing argument, and a result of CSignal of Bool

popCount1 :: Bits a => CSignal clk a -> CSignal clk Int Source

Version of popCount that returns a CSignal of Int

shift1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of shift that has a CSignal of Int as indexing argument

rotate1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of rotate that has a CSignal of Int as indexing argument

setBit1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of setBit that has a CSignal of Int as indexing argument

clearBit1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of clearBit that has a CSignal of Int as indexing argument

shiftL1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of shiftL that has a CSignal of Int as indexing argument

unsafeShiftL1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of unsafeShiftL that has a CSignal of Int as indexing argument

shiftR1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of shiftR that has a CSignal of Int as indexing argument

unsafeShiftR1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of unsafeShiftR that has a CSignal of Int as indexing argument

rotateL1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of rotateL that has a CSignal of Int as indexing argument

rotateR1 :: Bits a => CSignal clk a -> CSignal clk Int -> CSignal clk a Source

Version of rotateR that has a CSignal of Int as indexing argument