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

Copyright(C) 2013-2016 University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
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

>>> sampleN 5 (signal 4 :: Signal Int)
[4,4,4,4,4]

register :: a -> Signal a -> Signal a infixr 3 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]

registerMaybe :: a -> Signal (Maybe a) -> Signal a infixr 3 Source #

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 :: Applicative f => f Bool -> f a -> f a -> f a Source #

The above type is a generalisation for:

mux :: Signal Bool -> Signal a -> Signal a -> Signal a

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 #

Deprecated: not1 will be removed in clash-prelude-1.0, use "fmap not" instead.

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 where 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

Associated Types

type Unbundled' (clk :: Clock) a = res | res -> clk Source #

Methods

bundle :: Unbundled' clk a -> Signal' clk a Source #

Example:

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

However:

bundle :: Signal' clk Bit -> Signal' clk Bit

bundle :: Signal' clk a -> Signal' clk a Source #

Example:

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

However:

bundle :: Signal' clk Bit -> Signal' clk Bit

unbundle :: Signal' clk a -> Unbundled' clk a Source #

Example:

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

However:

unbundle :: Signal' clk Bit -> Signal' clk Bit

unbundle :: Signal' clk a -> Signal' clk a Source #

Example:

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

However:

unbundle :: Signal' clk Bit -> Signal' clk Bit

Instances

Bundle Bool Source # 

Associated Types

type Unbundled' (clk :: Clock) Bool = (res :: *) Source #

Bundle Double Source # 

Associated Types

type Unbundled' (clk :: Clock) Double = (res :: *) Source #

Bundle Float Source # 

Associated Types

type Unbundled' (clk :: Clock) Float = (res :: *) Source #

Bundle Int Source # 

Associated Types

type Unbundled' (clk :: Clock) Int = (res :: *) Source #

Bundle Integer Source # 

Associated Types

type Unbundled' (clk :: Clock) Integer = (res :: *) Source #

Bundle () Source #

Note that:

bundle   :: () -> Signal' clk ()
unbundle :: Signal' clk () -> ()

Associated Types

type Unbundled' (clk :: Clock) () = (res :: *) Source #

Methods

bundle :: Unbundled' clk () -> Signal' clk () Source #

unbundle :: Signal' clk () -> Unbundled' clk () Source #

Bundle (Maybe a) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Maybe a) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (Maybe a) -> Signal' clk (Maybe a) Source #

unbundle :: Signal' clk (Maybe a) -> Unbundled' clk (Maybe a) Source #

Bundle (Index n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Index n) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (Index n) -> Signal' clk (Index n) Source #

unbundle :: Signal' clk (Index n) -> Unbundled' clk (Index n) Source #

Bundle (BitVector n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (BitVector n) = (res :: *) Source #

Bundle (Signed n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Signed n) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (Signed n) -> Signal' clk (Signed n) Source #

unbundle :: Signal' clk (Signed n) -> Unbundled' clk (Signed n) Source #

Bundle (Unsigned n) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Unsigned n) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (Unsigned n) -> Signal' clk (Unsigned n) Source #

unbundle :: Signal' clk (Unsigned n) -> Unbundled' clk (Unsigned n) Source #

Bundle (Either a b) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Either a b) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (Either a b) -> Signal' clk (Either a b) Source #

unbundle :: Signal' clk (Either a b) -> Unbundled' clk (Either a b) Source #

Bundle (a, b) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (a, b) -> Signal' clk (a, b) Source #

unbundle :: Signal' clk (a, b) -> Unbundled' clk (a, b) Source #

KnownNat n => Bundle (Vec n a) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Vec n a) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (Vec n a) -> Signal' clk (Vec n a) Source #

unbundle :: Signal' clk (Vec n a) -> Unbundled' clk (Vec n a) Source #

KnownNat d => Bundle (RTree d a) Source # 

Associated Types

type Unbundled' (clk :: Clock) (RTree d a) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (RTree d a) -> Signal' clk (RTree d a) Source #

unbundle :: Signal' clk (RTree d a) -> Unbundled' clk (RTree d a) Source #

Bundle (a, b, c) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b, c) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (a, b, c) -> Signal' clk (a, b, c) Source #

unbundle :: Signal' clk (a, b, c) -> Unbundled' clk (a, b, c) Source #

Bundle (Fixed rep int frac) Source # 

Associated Types

type Unbundled' (clk :: Clock) (Fixed rep int frac) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (Fixed rep int frac) -> Signal' clk (Fixed rep int frac) Source #

unbundle :: Signal' clk (Fixed rep int frac) -> Unbundled' clk (Fixed rep int frac) Source #

Bundle (a, b, c, d) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b, c, d) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (a, b, c, d) -> Signal' clk (a, b, c, d) Source #

unbundle :: Signal' clk (a, b, c, d) -> Unbundled' clk (a, b, c, d) Source #

Bundle (a, b, c, d, e) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b, c, d, e) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (a, b, c, d, e) -> Signal' clk (a, b, c, d, e) Source #

unbundle :: Signal' clk (a, b, c, d, e) -> Unbundled' clk (a, b, c, d, e) Source #

Bundle (a, b, c, d, e, f) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b, c, d, e, f) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (a, b, c, d, e, f) -> Signal' clk (a, b, c, d, e, f) Source #

unbundle :: Signal' clk (a, b, c, d, e, f) -> Unbundled' clk (a, b, c, d, e, f) Source #

Bundle (a, b, c, d, e, f, g) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b, c, d, e, f, g) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (a, b, c, d, e, f, g) -> Signal' clk (a, b, c, d, e, f, g) Source #

unbundle :: Signal' clk (a, b, c, d, e, f, g) -> Unbundled' clk (a, b, c, d, e, f, g) Source #

Bundle (a, b, c, d, e, f, g, h) Source # 

Associated Types

type Unbundled' (clk :: Clock) (a, b, c, d, e, f, g, h) = (res :: *) Source #

Methods

bundle :: Unbundled' clk (a, b, c, d, e, f, g, h) -> Signal' clk (a, b, c, d, e, f, g, h) Source #

unbundle :: Signal' clk (a, b, c, d, e, f, g, h) -> Unbundled' clk (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.

Simulation functions (not synthesisable)

simulate :: (NFData a, NFData b) => (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, NFData a, NFData b) => (Unbundled' clk1 a -> Unbundled' clk2 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

lazy versions

simulate_lazy :: (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_lazy :: (Bundle a, Bundle b) => (Unbundled' clk1 a -> Unbundled' clk2 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, NFData a) => 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, NFData a) => 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 :: NFData a => [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

lazy versions

sample_lazy :: 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_lazy :: 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_lazy :: [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

QuickCheck combinators

testFor :: Foldable f => Int -> f Bool -> Property Source #

The above type is a generalisation for:

testFor :: Int -> Signal Bool -> Property

testFor n s tests the signal s for n cycles.

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 #

Deprecated: compare1 will be removed in clash-prelude-1.0, use "liftA2 compare" instead.

The above type is a generalisation for:

compare1 :: 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 #

Deprecated: fromEnum1 will be removed in clash-prelude-1.0, use "fmap fromEnum" instead.

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 #

Deprecated: toRational1 will be removed in clash-prelude-1.0, use "fmap toRational" instead.

The above type is a generalisation for:

toRational1 :: 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 #

Deprecated: toInteger1 will be removed in clash-prelude-1.0, use "fmap toInteger" instead.

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 #

Deprecated: testBit1 will be removed in clash-prelude-1.0, use "liftA2 testBit" instead.

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 #

Deprecated: popCount1 will be removed in clash-prelude-1.0, use "fmap popCount" instead.

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 #

Deprecated: shift1 will be removed in clash-prelude-1.0, use "liftA2 shift" instead.

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 #

Deprecated: rotate1 will be removed in clash-prelude-1.0, use "liftA2 rotate" instead.

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 #

Deprecated: setBit1 will be removed in clash-prelude-1.0, use "liftA2 setBit" instead.

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 #

Deprecated: clearBit1 will be removed in clash-prelude-1.0, use "liftA2 clearBit" instead.

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 #

Deprecated: shiftL1 will be removed in clash-prelude-1.0, use "liftA2 shiftL" instead.

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 #

Deprecated: unsafeShiftL1 will be removed in clash-prelude-1.0, use "liftA2 unsafeShiftL" instead.

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 #

Deprecated: shiftR1 will be removed in clash-prelude-1.0, use "liftA2 shiftR" instead.

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 #

Deprecated: unsafeShiftR1 will be removed in clash-prelude-1.0, use "liftA2 unsafeShiftR" instead.

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 #

Deprecated: rotateL1 will be removed in clash-prelude-1.0, use "liftA2 rotateL" instead.

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 #

Deprecated: rotateR1 will be removed in clash-prelude-1.0, use "liftA2 rotateR" instead.

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