{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
{-# LANGUAGE Safe #-}
{-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise #-}
module Clash.Signal.Delayed
(
DSignal
, delayed
, delayedI
, delayN
, delayI
, delayedFold
, feedback
, fromSignal
, toSignal
, dfromList
, dfromList_lazy
, unsafeFromSignal
, antiDelay
)
where
import GHC.TypeLits
(KnownNat, type (^), type (+), type (*))
import Clash.Signal.Delayed.Internal
(DSignal(..), dfromList, dfromList_lazy, fromSignal, toSignal,
unsafeFromSignal, antiDelay, feedback)
import qualified Clash.Explicit.Signal.Delayed as E
import Clash.Sized.Vector
import Clash.Signal
(HiddenClock, HiddenClockResetEnable, HiddenEnable, hideClock,
hideClockResetEnable, hideEnable)
import Clash.Promoted.Nat (SNat (..))
import Clash.XException (NFDataX)
delayed
:: ( KnownNat d
, HiddenClockResetEnable dom
, NFDataX a
)
=> Vec d a
-> DSignal dom n a
-> DSignal dom (n + d) a
delayed :: Vec d a -> DSignal dom n a -> DSignal dom (n + d) a
delayed = (KnownDomain dom =>
Clock dom
-> Reset dom
-> Enable dom
-> Vec d a
-> DSignal dom n a
-> DSignal dom (n + d) a)
-> Vec d a -> DSignal dom n a -> DSignal dom (n + d) a
forall (dom :: Symbol) r.
HiddenClockResetEnable dom =>
(KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r) -> r
hideClockResetEnable KnownDomain dom =>
Clock dom
-> Reset dom
-> Enable dom
-> Vec d a
-> DSignal dom n a
-> DSignal dom (n + d) a
forall (dom :: Symbol) a (n :: Nat) (d :: Nat).
(KnownDomain dom, KnownNat d, NFDataX a) =>
Clock dom
-> Reset dom
-> Enable dom
-> Vec d a
-> DSignal dom n a
-> DSignal dom (n + d) a
E.delayed
delayedI
:: ( KnownNat d
, NFDataX a
, HiddenClockResetEnable dom )
=> a
-> DSignal dom n a
-> DSignal dom (n + d) a
delayedI :: a -> DSignal dom n a -> DSignal dom (n + d) a
delayedI = (KnownDomain dom =>
Clock dom
-> Reset dom
-> Enable dom
-> a
-> DSignal dom n a
-> DSignal dom (n + d) a)
-> a -> DSignal dom n a -> DSignal dom (n + d) a
forall (dom :: Symbol) r.
HiddenClockResetEnable dom =>
(KnownDomain dom => Clock dom -> Reset dom -> Enable dom -> r) -> r
hideClockResetEnable KnownDomain dom =>
Clock dom
-> Reset dom
-> Enable dom
-> a
-> DSignal dom n a
-> DSignal dom (n + d) a
forall (d :: Nat) (dom :: Symbol) a (n :: Nat).
(KnownNat d, KnownDomain dom, NFDataX a) =>
Clock dom
-> Reset dom
-> Enable dom
-> a
-> DSignal dom n a
-> DSignal dom (n + d) a
E.delayedI
delayN
:: forall dom a d n
. ( HiddenClock dom
, HiddenEnable dom
, NFDataX a )
=> SNat d
-> a
-> DSignal dom n a
-> DSignal dom (n+d) a
delayN :: SNat d -> a -> DSignal dom n a -> DSignal dom (n + d) a
delayN SNat d
d a
dflt = (Clock dom -> DSignal dom n a -> DSignal dom (n + d) a)
-> DSignal dom n a -> DSignal dom (n + d) a
forall (dom :: Symbol) r. HiddenClock dom => (Clock dom -> r) -> r
hideClock ((Enable dom
-> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a)
-> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a
forall (dom :: Symbol) r.
HiddenEnable dom =>
(Enable dom -> r) -> r
hideEnable (SNat d
-> a
-> Enable dom
-> Clock dom
-> DSignal dom n a
-> DSignal dom (n + d) a
forall (dom :: Symbol) a (d :: Nat) (n :: Nat).
(KnownDomain dom, NFDataX a) =>
SNat d
-> a
-> Enable dom
-> Clock dom
-> DSignal dom n a
-> DSignal dom (n + d) a
E.delayN SNat d
d a
dflt))
delayI
:: forall d n a dom
. ( HiddenClock dom
, HiddenEnable dom
, NFDataX a
, KnownNat d )
=> a
-> DSignal dom n a
-> DSignal dom (n+d) a
delayI :: a -> DSignal dom n a -> DSignal dom (n + d) a
delayI a
dflt = (Clock dom -> DSignal dom n a -> DSignal dom (n + d) a)
-> DSignal dom n a -> DSignal dom (n + d) a
forall (dom :: Symbol) r. HiddenClock dom => (Clock dom -> r) -> r
hideClock ((Enable dom
-> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a)
-> Clock dom -> DSignal dom n a -> DSignal dom (n + d) a
forall (dom :: Symbol) r.
HiddenEnable dom =>
(Enable dom -> r) -> r
hideEnable (a
-> Enable dom
-> Clock dom
-> DSignal dom n a
-> DSignal dom (n + d) a
forall (d :: Nat) (n :: Nat) a (dom :: Symbol).
(NFDataX a, KnownDomain dom, KnownNat d) =>
a
-> Enable dom
-> Clock dom
-> DSignal dom n a
-> DSignal dom (n + d) a
E.delayI a
dflt))
delayedFold
:: forall dom n delay k a
. ( HiddenClock dom
, HiddenEnable dom
, NFDataX a
, KnownNat delay
, KnownNat k )
=> SNat delay
-> a
-> (a -> a -> a)
-> Vec (2^k) (DSignal dom n a)
-> DSignal dom (n + (delay * k)) a
delayedFold :: SNat delay
-> a
-> (a -> a -> a)
-> Vec (2 ^ k) (DSignal dom n a)
-> DSignal dom (n + (delay * k)) a
delayedFold SNat delay
d a
dflt a -> a -> a
f = (Clock dom
-> Vec (2 ^ k) (DSignal dom n a)
-> DSignal dom (n + (delay * k)) a)
-> Vec (2 ^ k) (DSignal dom n a) -> DSignal dom (n + (delay * k)) a
forall (dom :: Symbol) r. HiddenClock dom => (Clock dom -> r) -> r
hideClock ((Enable dom
-> Clock dom
-> Vec (2 ^ k) (DSignal dom n a)
-> DSignal dom (n + (delay * k)) a)
-> Clock dom
-> Vec (2 ^ k) (DSignal dom n a)
-> DSignal dom (n + (delay * k)) a
forall (dom :: Symbol) r.
HiddenEnable dom =>
(Enable dom -> r) -> r
hideEnable (SNat delay
-> a
-> (a -> a -> a)
-> Enable dom
-> Clock dom
-> Vec (2 ^ k) (DSignal dom n a)
-> DSignal dom (n + (delay * k)) a
forall (dom :: Symbol) (n :: Nat) (delay :: Nat) (k :: Nat) 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
E.delayedFold SNat delay
d a
dflt a -> a -> a
f))