clash-prelude-0.11: 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
Extensions
  • Cpp
  • ScopedTypeVariables
  • DataKinds
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll

CLaSH.Signal.Delayed

Contents

Description

 

Synopsis

Delay-annotated synchronous signals

type DSignal delay a = DSignal' SystemClock 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.

delay :: forall a n d. KnownNat d => Vec d a -> DSignal n a -> DSignal (n + d) a Source #

Delay a DSignal for d periods.

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

delayI :: (Default a, KnownNat d) => DSignal n a -> DSignal (n + d) a Source #

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

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

feedback :: (DSignal' clk n a -> (DSignal' clk n a, DSignal' clk ((n + m) + 1) a)) -> DSignal' clk n a Source #

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

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

Signal <-> DSignal conversion

fromSignal :: Signal' clk a -> DSignal' clk 0 a Source #

Signals are not delayed

sample s == dsample (fromSignal s)

toSignal :: DSignal' clk delay a -> Signal' clk a Source #

Strip a DSignal from its delay information.

List <-> DSignal conversion (not synthesisable)

dfromList :: NFData a => [a] -> DSignal' clk 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.

>>> sampleN 2 (dfromList [1,2,3,4,5])
[1,2]

NB: This function is not synthesisable

lazy versions

dfromList_lazy :: [a] -> DSignal' clk 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.

>>> sampleN 2 (dfromList [1,2,3,4,5])
[1,2]

NB: This function is not synthesisable

Experimental

unsafeFromSignal :: Signal' clk a -> DSignal' clk n a Source #

EXPERIMENTAL

Unsafely convert a Signal to any DSignal clk'.

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

antiDelay :: SNat d -> DSignal' clk (n + d) a -> DSignal' clk n a Source #

EXPERIMENTAL

Access a delayed signal in the present.

mac :: DSignal clk' 0 Int -> DSignal clk' 0 Int -> DSignal clk' 0 Int
mac x y = acc'
  where
    acc' = (x * y) + antiDelay d1 acc
    acc  = delay (singleton 0) acc'