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

Safe HaskellNone
LanguageHaskell2010

CLaSH.Signal.Delayed

Contents

Synopsis

Delay-annotated synchronous signals

data DSignal delay a Source

A synchronized signal with samples of type a, synchronized to "system" clock (period 1000), that has accumulated delay amount of samples delay along its path.

Instances

Functor (DSignal delay) 
Applicative (DSignal delay) 
Num a => Num (DSignal delay a) 
Show a => Show (DSignal delay a) 
Default a => Default (DSignal delay a) 
Lift a => Lift (DSignal delay a) 

dsignal :: a -> DSignal n a Source

Create a constant DSignal from a combinational value

>>> dsample (dsignal 4)
[4, 4, 4, 4, ...

delay :: forall a n m. KnownNat m => Vec m a -> DSignal (n - m) a -> DSignal n a Source

Delay a DSignal for m periods.

delay3 :: DSignal (n - 3) Int -> DSignal n Int
delay3 = delay (0 :> 0 :> 0 :> Nil)
>>> dsampleN 6 (delay3 (dfromList [1..]))
[0,0,0,1,2,3]

delayI :: (Default a, KnownNat m) => DSignal (n - m) a -> DSignal n a Source

Delay a DSignal for m periods, where m is derived from the context.

delay2 :: DSignal (n - 2) Int -> DSignal n Int
delay2 = delayI
>>> dsampleN 6 (delay2 (dfromList [1..])
[0,0,1,2,3,4]

feedback :: (DSignal ((n - m) - 1) a -> (DSignal ((n - m) - 1) a, DSignal n a)) -> DSignal ((n - m) - 1) a Source

Feed the delayed result of a function back to its input:

mac :: DSignal 0 Int -> DSignal 0 Int -> DSignal 0 Int
mac x y = feedback (mac' x y)
  where
    mac' :: DSignal 0 Int -> DSignal 0 Int -> DSignal 0 Int
         -> (DSignal 0 Int, DSignal 1 Int)
    mac' a b acc = let acc' = a * b + acc
                   in  (acc, delay (singleton 0) acc')
>>> dsampleN 6 (mac (dfromList [1..]) (dfromList [1..]))
[0,1,5,14,30,55]

Signal <-> DSignal conversion

fromSignal :: Signal a -> DSignal 0 a Source

Signals are not delayed

sample s == dsample (fromSignal s)

toSignal :: DSignal delay a -> Signal a Source

Strip a DSignal from its delay information.

unsafeFromSignal :: Signal a -> DSignal n a Source

Unsafely convert a Signal to any DSignal.

NB: Should only be used to interface with functions specified in terms of Signal.

List <-> DSignal conversion (not synthesisable)

dsample :: DSignal t a -> [a] Source

Get an infinite list of samples from a DSignal

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

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

NB: This function is not synthesisable

dsampleN :: Int -> DSignal t a -> [a] Source

Get a list of n samples from a DSignal

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

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

NB: This function is not synthesisable

dfromList :: [a] -> DSignal 0 a Source

Create a DSignal from a list

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

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

NB: This function is not synthesisable