| Copyright | (C) 2013-2016, University of Twente | 
|---|---|
| License | BSD2 (see the file LICENSE) | 
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
| Extensions | MagicHash | 
CLaSH.Signal
Contents
Description
- type Signal a = Signal' SystemClock a
- signal :: Applicative f => a -> f a
- register :: a -> Signal a -> Signal a
- regEn :: a -> Signal Bool -> Signal a -> Signal a
- mux :: Applicative f => f Bool -> f a -> f a -> f a
- (.&&.) :: Applicative f => f Bool -> f Bool -> f Bool
- (.||.) :: Applicative f => f Bool -> f Bool -> f Bool
- not1 :: Functor f => f Bool -> f Bool
- class Bundle a
- type Unbundled a = Unbundled' SystemClock a
- bundle :: Bundle a => Unbundled a -> Signal a
- unbundle :: Bundle a => Signal a -> Unbundled a
- simulate :: (Signal' clk1 a -> Signal' clk2 b) -> [a] -> [b]
- simulateB :: (Bundle a, Bundle b) => (Unbundled a -> Unbundled b) -> [a] -> [b]
- simulate_strict :: (NFData a, NFData b) => (Signal' clk1 a -> Signal' clk2 b) -> [a] -> [b]
- simulateB_strict :: (Bundle a, Bundle b, NFData a, NFData b) => (Unbundled a -> Unbundled b) -> [a] -> [b]
- sample :: Foldable f => f a -> [a]
- sampleN :: Foldable f => Int -> f a -> [a]
- fromList :: [a] -> Signal' clk a
- sample_strict :: (Foldable f, NFData a) => f a -> [a]
- sampleN_strict :: (Foldable f, NFData a) => Int -> f a -> [a]
- fromList_strict :: NFData a => [a] -> Signal' clk a
- testFor :: Foldable f => Int -> f Bool -> Property
- (.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
- (./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool
- compare1 :: (Ord a, Applicative f) => f a -> f a -> f Ordering
- (.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- (.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool
- fromEnum1 :: (Enum a, Functor f) => f a -> f Int
- toRational1 :: (Real a, Functor f) => f a -> f Rational
- toInteger1 :: (Integral a, Functor f) => f a -> f Integer
- testBit1 :: (Bits a, Applicative f) => f a -> f Int -> f Bool
- popCount1 :: (Bits a, Functor f) => f a -> f Int
- shift1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- rotate1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- setBit1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- clearBit1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- shiftL1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- unsafeShiftL1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- shiftR1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- unsafeShiftR1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- rotateL1 :: (Bits a, Applicative f) => f a -> f Int -> f a
- rotateR1 :: (Bits a, Applicative f) => f a -> f Int -> f a
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
mux :: Applicative f => f Bool -> f a -> f a -> f a Source
Boolean connectives
Product/Signal isomorphism
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'=idunbundle'.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 instanceBundleD where typeUnbundled'clk D =Signal'clk Dbundle'_ s = sunbundle'_ 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
Simulation functions (not synthesisable)
Strict versions
simulate_strict :: (NFData a, NFData b) => (Signal' clk1 a -> Signal' clk2 b) -> [a] -> [b] Source
Deprecated: simulate will be strict in CLaSH 1.0, and simulate_strict will be removed
Version of simulate that strictly evaluates the input elements and the
 output elements
N.B: Exceptions are lazily rethrown
simulateB_strict :: (Bundle a, Bundle b, NFData a, NFData b) => (Unbundled a -> Unbundled b) -> [a] -> [b] Source
Deprecated: 'simulateB will be strict in CLaSH 1.0, and simulateB_strict will be removed
Version of simulateB that strictly evaluates the input elements and the
 output elements
N.B: Exceptions are lazily rethrown
List <-> Signal conversion (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
Strict versions
sample_strict :: (Foldable f, NFData a) => f a -> [a] Source
Deprecated: sample will be strict in CLaSH 1.0, and sample_strict will be removed
Version of sample that strictly evaluates the samples
N.B: Exceptions are lazily rethrown
sampleN_strict :: (Foldable f, NFData a) => Int -> f a -> [a] Source
Deprecated: sampleN will be strict in CLaSH 1.0, and sampleN_strict will be removed
Version of sampleN that strictly evaluates the samples
N.B: Exceptions are lazily rethrown
fromList_strict :: NFData a => [a] -> Signal' clk a Source
Deprecated: fromList will be strict in CLaSH 1.0, and fromList_strict will be removed
Version of fromList that strictly evaluates the elements of the list
N.B: Exceptions are lazily rethrown
QuickCheck combinators
Type classes
Eq-like
(.==.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 Source
(./=.) :: (Eq a, Applicative f) => f a -> f a -> f Bool infix 4 Source
Ord-like
compare1 :: (Ord a, Applicative f) => f a -> f a -> f Ordering Source
(.<.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source
(.<=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source
(.>=.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source
(.>.) :: (Ord a, Applicative f) => f a -> f a -> f Bool infix 4 Source
Enum-like
Rational-like
toRational1 :: (Real a, Functor f) => f a -> f Rational Source
Integral-like
toInteger1 :: (Integral a, Functor f) => f a -> f Integer Source
Bits-like
shift1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
rotate1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
setBit1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
clearBit1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
shiftL1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
unsafeShiftL1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
shiftR1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
unsafeShiftR1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source
rotateL1 :: (Bits a, Applicative f) => f a -> f Int -> f a Source