Copyright | (C) 2013-2016 University of Twente 2017 Google Inc. 2019 Myrtle Software Ltd 2021 LUMI GUIDE FIETSDETECTIE B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Extensions |
|
Synopsis
- data DSignal (dom :: Domain) (delay :: Nat) a
- delayed :: forall dom a n d. (KnownDomain dom, KnownNat d, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> Vec d a -> DSignal dom n a -> DSignal dom (n + d) a
- delayedI :: (KnownNat d, KnownDomain dom, NFDataX a) => Clock dom -> Reset dom -> Enable dom -> a -> DSignal dom n a -> DSignal dom (n + d) a
- delayN :: forall dom a d n. (KnownDomain dom, NFDataX a) => SNat d -> a -> Enable dom -> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a
- delayI :: forall d n a dom. (NFDataX a, KnownDomain dom, KnownNat d) => a -> Enable dom -> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a
- delayedFold :: forall dom n delay k a. (NFDataX a, KnownDomain dom, KnownNat delay, KnownNat k) => SNat delay -> a -> (a -> a -> a) -> Enable dom -> Clock dom -> Vec (2 ^ k) (DSignal dom n a) -> DSignal dom (n + (delay * k)) a
- feedback :: (DSignal dom n a -> (DSignal dom n a, DSignal dom ((n + m) + 1) a)) -> DSignal dom n a
- fromSignal :: Signal dom a -> DSignal dom 0 a
- toSignal :: DSignal dom delay a -> Signal dom a
- dfromList :: NFDataX a => [a] -> DSignal dom 0 a
- dfromList_lazy :: [a] -> DSignal dom 0 a
- unsafeFromSignal :: Signal dom a -> DSignal dom n a
- antiDelay :: SNat d -> DSignal dom (n + d) a -> DSignal dom n a
- forward :: SNat d -> DSignal dom n a -> DSignal dom (n + d) a
Documentation
data DSignal (dom :: Domain) (delay :: Nat) a Source #
A synchronized signal with samples of type a
, synchronized to clock
clk
, that has accumulated delay
amount of samples delay along its path.
DSignal has the type role
>>>
:i DSignal
type role DSignal nominal nominal representational ...
as it is safe to coerce the values in the signal, but not safe to coerce the synthesis domain or delay in the signal.
Instances
Lift a => Lift (DSignal dom delay a :: Type) Source # | |
Functor (DSignal dom delay) Source # | |
Applicative (DSignal dom delay) Source # | |
Defined in Clash.Signal.Delayed.Internal pure :: a -> DSignal dom delay a Source # (<*>) :: DSignal dom delay (a -> b) -> DSignal dom delay a -> DSignal dom delay b Source # liftA2 :: (a -> b -> c) -> DSignal dom delay a -> DSignal dom delay b -> DSignal dom delay c Source # (*>) :: DSignal dom delay a -> DSignal dom delay b -> DSignal dom delay b Source # (<*) :: DSignal dom delay a -> DSignal dom delay b -> DSignal dom delay a Source # | |
Foldable (DSignal dom delay) Source # | |
Defined in Clash.Signal.Delayed.Internal fold :: Monoid m => DSignal dom delay m -> m Source # foldMap :: Monoid m => (a -> m) -> DSignal dom delay a -> m Source # foldMap' :: Monoid m => (a -> m) -> DSignal dom delay a -> m Source # foldr :: (a -> b -> b) -> b -> DSignal dom delay a -> b Source # foldr' :: (a -> b -> b) -> b -> DSignal dom delay a -> b Source # foldl :: (b -> a -> b) -> b -> DSignal dom delay a -> b Source # foldl' :: (b -> a -> b) -> b -> DSignal dom delay a -> b Source # foldr1 :: (a -> a -> a) -> DSignal dom delay a -> a Source # foldl1 :: (a -> a -> a) -> DSignal dom delay a -> a Source # toList :: DSignal dom delay a -> [a] Source # null :: DSignal dom delay a -> Bool Source # length :: DSignal dom delay a -> Int Source # elem :: Eq a => a -> DSignal dom delay a -> Bool Source # maximum :: Ord a => DSignal dom delay a -> a Source # minimum :: Ord a => DSignal dom delay a -> a Source # | |
Traversable (DSignal dom delay) Source # | |
Defined in Clash.Signal.Delayed.Internal traverse :: Applicative f => (a -> f b) -> DSignal dom delay a -> f (DSignal dom delay b) Source # sequenceA :: Applicative f => DSignal dom delay (f a) -> f (DSignal dom delay a) Source # mapM :: Monad m => (a -> m b) -> DSignal dom delay a -> m (DSignal dom delay b) Source # sequence :: Monad m => DSignal dom delay (m a) -> m (DSignal dom delay a) Source # | |
Fractional a => Fractional (DSignal dom delay a) Source # | |
Num a => Num (DSignal dom delay a) Source # | |
Defined in Clash.Signal.Delayed.Internal (+) :: DSignal dom delay a -> DSignal dom delay a -> DSignal dom delay a Source # (-) :: DSignal dom delay a -> DSignal dom delay a -> DSignal dom delay a Source # (*) :: DSignal dom delay a -> DSignal dom delay a -> DSignal dom delay a Source # negate :: DSignal dom delay a -> DSignal dom delay a Source # abs :: DSignal dom delay a -> DSignal dom delay a Source # signum :: DSignal dom delay a -> DSignal dom delay a Source # fromInteger :: Integer -> DSignal dom delay a Source # | |
Show a => Show (DSignal dom delay a) Source # | |
Arbitrary a => Arbitrary (DSignal dom delay a) Source # | |
CoArbitrary a => CoArbitrary (DSignal dom delay a) Source # | |
Defined in Clash.Signal.Delayed.Internal | |
Default a => Default (DSignal dom delay a) Source # | |
Defined in Clash.Signal.Delayed.Internal | |
type HasDomain dom1 (DSignal dom2 delay a) Source # | |
Defined in Clash.Class.HasDomain.HasSpecificDomain | |
type TryDomain t (DSignal dom delay a) Source # | |
Defined in Clash.Class.HasDomain.HasSingleDomain |
Delay-annotated synchronous signals
:: forall dom a n d. (KnownDomain dom, KnownNat d, NFDataX a) | |
=> Clock dom | |
-> Reset dom | |
-> Enable dom | |
-> Vec d a | Initial values |
-> DSignal dom n a | |
-> DSignal dom (n + d) a |
Delay a DSignal
for d
periods.
delay3 :: KnownDomain dom => Clock dom -> Reset dom -> Enable dom ->DSignal
dom n Int ->DSignal
dom (n + 3) Int delay3 clk rst en =delayed
clk rst en (-1:>
-1:>
-1:>
Nil
)
>>>
sampleN 7 (delay3 systemClockGen resetGen enableGen (dfromList [0..]))
[-1,-1,-1,-1,1,2,3]
:: (KnownNat d, KnownDomain dom, NFDataX a) | |
=> Clock dom | |
-> Reset dom | |
-> Enable dom | |
-> a | Initial value |
-> DSignal dom n a | |
-> DSignal dom (n + d) a |
Delay a DSignal
for d
periods, where d
is derived from the
context.
delay2 :: KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> Int ->DSignal
dom n Int ->DSignal
dom (n + 2) Int delay2 =delayedI
>>>
sampleN 7 (delay2 systemClockGen resetGen enableGen (-1) (dfromList ([0..])))
[-1,-1,-1,1,2,3,4]
d
can also be specified using type application:
>>>
:t delayedI @3
delayedI @3 :: ... => Clock dom -> Reset dom -> Enable dom -> a -> DSignal dom n a -> DSignal dom (n + 3) a
:: forall d n a dom. (NFDataX a, KnownDomain dom, KnownNat d) | |
=> a | Initial value |
-> Enable dom | |
-> Clock dom | |
-> DSignal dom n a | |
-> DSignal dom (n + d) a |
Delay a DSignal
for d
cycles, where d
is derived from the context.
The value at time 0..d-1 is a default value.
delayI2 ::KnownDomain
dom => Int ->Enable
dom ->Clock
dom ->DSignal
dom n Int ->DSignal
dom (n + 2) Int delayI2 =delayI
>>>
sampleN 6 (delayI2 (-1) enableGen systemClockGen (dfromList [1..]))
[-1,-1,1,2,3,4]
You can also use type application to do the same:
>>>
sampleN 6 (delayI @2 (-1) enableGen systemClockGen (dfromList [1..]))
[-1,-1,1,2,3,4]
:: forall dom n delay k a. (NFDataX a, KnownDomain dom, KnownNat delay, KnownNat k) | |
=> SNat delay | Delay applied after each step |
-> a | Initial value |
-> (a -> a -> a) | Fold operation to apply |
-> Enable dom | |
-> Clock dom | |
-> Vec (2 ^ k) (DSignal dom n a) | Vector input of size 2^k |
-> DSignal dom (n + (delay * k)) a | Output Signal delayed by (delay * k) |
Tree fold over a Vec
of DSignal
s with a combinatorial function,
and delaying delay
cycles after each application.
Values at times 0..(delay*k)-1 are set to a default.
countingSignals :: Vec 4 (DSignal dom 0 Int) countingSignals = repeat (dfromList [0..])
>>>
printX $ sampleN 6 (delayedFold d1 (-1) (+) enableGen systemClockGen countingSignals)
[-1,-2,0,4,8,12]
>>>
printX $ sampleN 8 (delayedFold d2 (-1) (*) enableGen systemClockGen countingSignals)
[-1,-1,1,1,0,1,16,81]
feedback :: (DSignal dom n a -> (DSignal dom n a, DSignal dom ((n + m) + 1) a)) -> DSignal dom n a Source #
Feed the delayed result of a function back to its input:
mac :: forall dom . KnownDomain dom => Clock dom -> Reset dom -> Enable dom ->DSignal
dom 0 Int ->DSignal
dom 0 Int ->DSignal
dom 0 Int mac clk rst en x y =feedback
(mac' x y) where mac' ::DSignal
dom 0 Int ->DSignal
dom 0 Int ->DSignal
dom 0 Int -> (DSignal
dom 0 Int,DSignal
dom 1 Int) mac' a b acc = let acc' = a * b + acc in (acc,delayedI
clk rst en 0 acc')
>>>
sampleN 7 (toSignal (mac systemClockGen systemResetGen enableGen (dfromList [0..]) (dfromList [0..])))
[0,0,1,5,14,30,55]
Signal <-> DSignal conversion
List <-> DSignal conversion (not synthesizable)
dfromList :: NFDataX a => [a] -> DSignal dom 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 (toSignal (dfromList [1,2,3,4,5]))
[1,2]
NB: This function is not synthesizable
lazy versions
dfromList_lazy :: [a] -> DSignal dom 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 (toSignal (dfromList [1,2,3,4,5]))
[1,2]
NB: This function is not synthesizable
Experimental
unsafeFromSignal :: Signal dom a -> DSignal dom n a Source #
antiDelay :: SNat d -> DSignal dom (n + d) a -> DSignal dom n a Source #
EXPERIMENTAL
Access a delayed signal from the future in the present. Often required When writing a circuit that requires feedback from itself.
mac :: KnownDomain dom => Clock dom -> Reset dom -> Enable dom ->DSignal
dom 0 Int ->DSignal
dom 0 Int ->DSignal
dom 0 Int mac clk rst en x y = acc' where acc' = (x * y) +antiDelay
d1 acc acc =delayedI
clk rst en 0 acc'
forward :: SNat d -> DSignal dom n a -> DSignal dom (n + d) a Source #
EXPERIMENTAL
Access a delayed signal from the past in the present. In contrast with
delayed
and friends forward does not insert
any logic. This means using this function violates the delay invariant of
DSignal
. This is sometimes useful when combining unrelated delayed signals
where inserting logic is not wanted or when abstracting over internal
delayed signals where the internal delay information should not be leaked.
For example, the circuit below returns a sequence of numbers as a pair but the internal delay information between the elements of the pair should not leak into the type.
numbers :: forall dom . KnownDomain dom => Clock dom -> Reset dom -> Enable dom ->DSignal
dom 5 (Int, Int) numbers clk rst en = DB.bundle (forward d1 s1, s2) where s1 ::DSignal
dom 4 Int s1 =delayed
clk rst en (100 :> 10 :> 5 :> 1 :> Nil) (pure 200) s2 ::DSignal
dom 5 Int s2 = fmap (2*) $delayN
d1 0 en clk s1
>>>
sampleN 8 (toSignal (numbers systemClockGen systemResetGen enableGen))
[(1,0),(1,2),(5,2),(10,10),(100,20),(200,200),(200,400),(200,400)]