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 HaskellUnsafe
LanguageHaskell2010
Extensions
  • Cpp
  • MonoLocalBinds
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • TypeFamilies
  • GADTs
  • GADTSyntax
  • DataKinds
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • MagicHash
  • KindSignatures
  • ExplicitNamespaces
  • ExplicitForAll

CLaSH.Signal.Internal

Contents

Description

 

Synopsis

Datatypes

data Clock Source #

A clock with a name (Symbol) and period (Nat)

Constructors

Clk Symbol Nat 

data SClock clk where Source #

Singleton value for a type-level Clock with the given name and period

Constructors

SClock :: SSymbol name -> SNat period -> SClock (Clk name period) 

Instances

Show (SClock clk) Source # 

Methods

showsPrec :: Int -> SClock clk -> ShowS #

show :: SClock clk -> String #

showList :: [SClock clk] -> ShowS #

data Signal' clk a Source #

A synchronized signal with samples of type a, explicitly synchronized to a clock clk

NB: The constructor, (:-), is not synthesisable.

Constructors

a :- (Signal' clk a) infixr 5 

Instances

Functor (Signal' clk) Source # 

Methods

fmap :: (a -> b) -> Signal' clk a -> Signal' clk b #

(<$) :: a -> Signal' clk b -> Signal' clk a #

Applicative (Signal' clk) Source # 

Methods

pure :: a -> Signal' clk a #

(<*>) :: Signal' clk (a -> b) -> Signal' clk a -> Signal' clk b #

(*>) :: Signal' clk a -> Signal' clk b -> Signal' clk b #

(<*) :: Signal' clk a -> Signal' clk b -> Signal' clk a #

Foldable (Signal' clk) Source #

NB: Not synthesisable

NB: In "foldr f z s":

  • The function f should be lazy in its second argument.
  • The z element will never be used.

Methods

fold :: Monoid m => Signal' clk m -> m #

foldMap :: Monoid m => (a -> m) -> Signal' clk a -> m #

foldr :: (a -> b -> b) -> b -> Signal' clk a -> b #

foldr' :: (a -> b -> b) -> b -> Signal' clk a -> b #

foldl :: (b -> a -> b) -> b -> Signal' clk a -> b #

foldl' :: (b -> a -> b) -> b -> Signal' clk a -> b #

foldr1 :: (a -> a -> a) -> Signal' clk a -> a #

foldl1 :: (a -> a -> a) -> Signal' clk a -> a #

toList :: Signal' clk a -> [a] #

null :: Signal' clk a -> Bool #

length :: Signal' clk a -> Int #

elem :: Eq a => a -> Signal' clk a -> Bool #

maximum :: Ord a => Signal' clk a -> a #

minimum :: Ord a => Signal' clk a -> a #

sum :: Num a => Signal' clk a -> a #

product :: Num a => Signal' clk a -> a #

Traversable (Signal' clk) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Signal' clk a -> f (Signal' clk b) #

sequenceA :: Applicative f => Signal' clk (f a) -> f (Signal' clk a) #

mapM :: Monad m => (a -> m b) -> Signal' clk a -> m (Signal' clk b) #

sequence :: Monad m => Signal' clk (m a) -> m (Signal' clk a) #

Fractional a => Fractional (Signal' clk a) Source # 

Methods

(/) :: Signal' clk a -> Signal' clk a -> Signal' clk a #

recip :: Signal' clk a -> Signal' clk a #

fromRational :: Rational -> Signal' clk a #

Num a => Num (Signal' clk a) Source # 

Methods

(+) :: Signal' clk a -> Signal' clk a -> Signal' clk a #

(-) :: Signal' clk a -> Signal' clk a -> Signal' clk a #

(*) :: Signal' clk a -> Signal' clk a -> Signal' clk a #

negate :: Signal' clk a -> Signal' clk a #

abs :: Signal' clk a -> Signal' clk a #

signum :: Signal' clk a -> Signal' clk a #

fromInteger :: Integer -> Signal' clk a #

Show a => Show (Signal' clk a) Source # 

Methods

showsPrec :: Int -> Signal' clk a -> ShowS #

show :: Signal' clk a -> String #

showList :: [Signal' clk a] -> ShowS #

Lift a => Lift (Signal' clk a) Source # 

Methods

lift :: Signal' clk a -> Q Exp #

Arbitrary a => Arbitrary (Signal' clk a) Source # 

Methods

arbitrary :: Gen (Signal' clk a) #

shrink :: Signal' clk a -> [Signal' clk a] #

CoArbitrary a => CoArbitrary (Signal' clk a) Source # 

Methods

coarbitrary :: Signal' clk a -> Gen b -> Gen b #

Default a => Default (Signal' clk a) Source # 

Methods

def :: Signal' clk a #

Basic circuits

register# :: SClock clk -> a -> Signal' clk a -> Signal' clk a Source #

regEn# :: SClock clk -> a -> Signal' clk Bool -> Signal' clk a -> Signal' clk a Source #

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.

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]

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

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

lazy version

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

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

Functor

mapSignal# :: (a -> b) -> Signal' clk a -> Signal' clk b Source #

Applicative

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

appSignal# :: Signal' clk (a -> b) -> Signal' clk a -> Signal' clk b Source #

Foldable

foldr# :: (a -> b -> b) -> b -> Signal' clk a -> b Source #

NB: Not synthesisable

NB: In "foldr# f z s":

  • The function f should be lazy in its second argument.
  • The z element will never be used.

Traversable

traverse# :: Applicative f => (a -> f b) -> Signal' clk a -> f (Signal' clk b) Source #

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

EXTREMELY EXPERIMENTAL

joinSignal# :: Signal' clk (Signal' clk a) -> Signal' clk a Source #

WARNING: EXTREMELY EXPERIMENTAL

The circuit semantics of this operation are unclear and/or non-existent. There is a good reason there is no Monad instance for Signal'.

Is currently treated as id by the CLaSH compiler.