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

Copyright(C) 2013-2015, University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010
ExtensionsMagicHash

CLaSH.Signal

Contents

Description

 

Synopsis

Implicitly clocked synchronous signal

type Signal a = Signal' SystemClock a Source

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

Basic circuit functions

signal :: Applicative f => a -> f a Source

The above type is a generalisation for:

signal :: a -> Signal a

Create a constant Signal from a combinational value

>>> import qualified Data.List as List
>>> List.take 5 (sample (signal 4 :: Signal Int))
[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 :: Signal' clk Bool -> Signal' clk a -> Signal' clk a -> Signal' clk a Source

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

Boolean connectives

(.&&.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 3 Source

The above type is a generalisation for:

(.&&.) :: Signal Bool -> Signal Bool -> Signal Bool

It is a version of (&&) that returns a Signal of Bool

(.||.) :: Applicative f => f Bool -> f Bool -> f Bool infixr 2 Source

The above type is a generalisation for:

(.||.) :: Signal Bool -> Signal Bool -> Signal Bool

It is a version of (||) that returns a Signal of Bool

not1 :: Functor f => f Bool -> f Bool Source

The above type is a generalisation for:

not1 :: Signal Bool -> Signal Bool

It is a version of not that operates on Signals of Bool

Product/Signal isomorphism

class Bundle a Source

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

Instances of Bundle must satisfy the following laws:

bundle' . unbundle' = id
unbundle' . bundle' = id

By default, bundle' and unbundle', are defined as the identity, that is, writing:

data D = A | B

instance Bundle D

is the same as:

data D = A | B

instance Bundle D where
  type Unbundled' clk D = Signal' clk D
  bundle'   _ s = s
  unbundle' _ s = s

Instances

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

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' clk1 a -> Signal' clk2 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 (Unbundled a -> Unbundled b) function given a list of samples of type a

>>> simulateB (unbundle . register (8,8) . bundle) [(1,1), (2,2), (3,3)] :: [(Int,Int)]
[(8,8),(1,1),(2,2),(3,3)...

NB: This function is not synthesisable

List <-> Signal conversion (not synthesisable)

sample :: Foldable f => f a -> [a] Source

The above type is a generalisation for:

sample :: Signal a -> [a]

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 :: Foldable f => Int -> f a -> [a] Source

The above type is a generalisation for:

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

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' clk 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, Applicative f) => f a -> f a -> f Bool infix 4 Source

The above type is a generalisation for:

(.==.) :: Eq a => Signal a -> Signal a -> Signal Bool

It is a version of (==) that returns a Signal of Bool

(./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 Source

The above type is a generalisation for:

(./=.) :: Eq a => Signal a -> Signal a -> Signal Bool

It is a version of (/=) that returns a Signal of Bool

Ord-like

compare1 :: (Ord a, Applicative f) => f a -> f a -> f Ordering Source

The above type is a generalisation for:

compare :: Ord a => Signal a -> Signal a -> Signal Ordering

It is a version of compare that returns a Signal of Ordering

(.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source

The above type is a generalisation for:

(.<.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (<) that returns a Signal of Bool

(.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source

The above type is a generalisation for:

(.<=.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (<=) that returns a Signal of Bool

(.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source

The above type is a generalisation for:

(.>=.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (>=) that returns a Signal of Bool

(.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source

The above type is a generalisation for:

(.>.) :: Ord a => Signal a -> Signal a -> Signal Bool

It is a version of (>) that returns a Signal of Bool

Enum-like

fromEnum1 :: (Enum a, Functor f) => f a -> f Int Source

The above type is a generalisation for:

fromEnum1 :: Enum a => Signal a -> Signal Int

It is a version of fromEnum that returns a CLaSH.Signal.Signal' of Int

Rational-like

toRational1 :: (Real a, Functor f) => f a -> f Rational Source

The above type is a generalisation for:

fromEnum1 :: Real a => Signal a -> Signal Rational

| It is a version of toRational that returns a Signal of Rational

Integral-like

toInteger1 :: (Integral a, Functor f) => f a -> f Integer Source

The above type is a generalisation for:

toInteger1 :: Integral a => Signal a -> Signal Integer

It is a version of toRational that returns a Signal of Integer

Bits-like

testBit1 :: (Bits a, Applicative f) => f a -> f Int -> f Bool Source

The above type is a generalisation for:

testBit1 :: Bits a => Signal a -> Signal Int -> Signal Bool

It is a version of testBit that has a Signal of Int as indexing argument, and a result of Signal of Bool

popCount1 :: (Bits a, Functor f) => f a -> f Int Source

The above type is a generalisation for:

popCount1 :: Bits a => Signal a -> Signal Int

It is a version of popCount that returns a Signal of Int

shift1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

shift1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of shift that has a Signal of Int as indexing argument

rotate1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

rotate1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of rotate that has a Signal of Int as indexing argument

setBit1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

setBit1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of setBit that has a Signal of Int as indexing argument

clearBit1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

clearBit1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of clearBit that has a Signal of Int as indexing argument

shiftL1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

shiftL1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of shiftL that has a Signal of Int as indexing argument

unsafeShiftL1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

unsafeShiftL1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of unsafeShiftL that has a Signal of Int as indexing argument

shiftR1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

shiftR1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of shiftR that has a Signal of Int as indexing argument

unsafeShiftR1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

unsafeShiftR1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of unsafeShiftR that has a Signal of Int as indexing argument

rotateL1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

rotateL1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of rotateL that has a Signal of Int as indexing argument

rotateR1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source

The above type is a generalisation for:

rotateR1 :: Bits a => Signal a -> Signal Int -> Signal a

It is a version of rotateR that has a Signal of Int as indexing argument