{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
#if __GLASGOW_HASKELL__ >= 806
{-# LANGUAGE NoStarIsType #-}
#endif
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
{-# LANGUAGE Trustworthy #-}
{-# 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 Data.Coerce (coerce)
import Data.Kind (Type)
import Data.Proxy (Proxy(..))
import GHC.TypeLits
(KnownNat, type (^), type (+), type (*), Nat)
import Data.Singletons.Prelude (Apply, TyFun, type (@@))
import Clash.Signal.Internal (Domain)
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 (Vec, dtfold)
import Clash.Signal
(HiddenClockResetEnable , hideClockResetEnable, Signal, delay)
import Clash.Promoted.Nat (SNat (..), snatToInteger)
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 :: Domain) 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 :: Domain) 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 :: Domain) 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 :: Domain) 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
. ( HiddenClockResetEnable 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 d :: SNat d
d dflt :: a
dflt = Signal dom a -> DSignal dom (n + d) a
forall a b. Coercible a b => a -> b
coerce (Signal dom a -> DSignal dom (n + d) a)
-> (DSignal dom n a -> Signal dom a)
-> DSignal dom n a
-> DSignal dom (n + d) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Signal dom a -> Signal dom a
go (SNat d -> Integer
forall (n :: Nat). SNat n -> Integer
snatToInteger SNat d
d) (Signal dom a -> Signal dom a)
-> (DSignal dom n a -> Signal dom a)
-> DSignal dom n a
-> Signal dom a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coercible (DSignal dom n a) (Signal dom a) =>
DSignal dom n a -> Signal dom a
forall a b. Coercible a b => a -> b
coerce @_ @(Signal dom a)
where
go :: Integer -> Signal dom a -> Signal dom a
go 0 = Signal dom a -> Signal dom a
forall a. a -> a
id
go i :: Integer
i = a -> Signal dom a -> Signal dom a
forall (dom :: Domain) a.
(NFDataX a, HiddenClock dom, HiddenEnable dom) =>
a -> Signal dom a -> Signal dom a
delay a
dflt (Signal dom a -> Signal dom a)
-> (Signal dom a -> Signal dom a) -> Signal dom a -> Signal dom a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Signal dom a -> Signal dom a
go (Integer
iInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-1)
delayI
:: forall d n a dom
. ( HiddenClockResetEnable 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 dflt :: a
dflt = SNat d -> a -> DSignal dom n a -> DSignal dom (n + d) a
forall (dom :: Domain) a (d :: Nat) (n :: Nat).
(HiddenClockResetEnable dom, NFDataX a) =>
SNat d -> a -> DSignal dom n a -> DSignal dom (n + d) a
delayN (SNat d
forall (n :: Nat). KnownNat n => SNat n
SNat :: SNat d) a
dflt
data DelayedFold (dom :: Domain) (n :: Nat) (delay :: Nat) (a :: Type) (f :: TyFun Nat Type) :: Type
type instance Apply (DelayedFold dom n delay a) k = DSignal dom (n + (delay*k)) a
delayedFold
:: forall dom n delay k a
. ( HiddenClockResetEnable 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 _ dflt :: a
dflt op :: a -> a -> a
op = Proxy (DelayedFold dom n delay a)
-> (DSignal dom n a -> DelayedFold dom n delay a @@ 0)
-> (forall (l :: Nat).
SNat l
-> (DelayedFold dom n delay a @@ l)
-> (DelayedFold dom n delay a @@ l)
-> DelayedFold dom n delay a @@ (l + 1))
-> Vec (2 ^ k) (DSignal dom n a)
-> DelayedFold dom n delay a @@ k
forall (p :: TyFun Nat Type -> Type) (k :: Nat) a.
KnownNat k =>
Proxy p
-> (a -> p @@ 0)
-> (forall (l :: Nat).
SNat l -> (p @@ l) -> (p @@ l) -> p @@ (l + 1))
-> Vec (2 ^ k) a
-> p @@ k
dtfold (Proxy (DelayedFold dom n delay a)
forall k (t :: k). Proxy t
Proxy :: Proxy (DelayedFold dom n delay a)) DSignal dom n a -> DelayedFold dom n delay a @@ 0
forall a. a -> a
id forall (l :: Nat).
SNat l
-> (DelayedFold dom n delay a @@ l)
-> (DelayedFold dom n delay a @@ l)
-> DelayedFold dom n delay a @@ (l + 1)
go
where
go :: SNat l
-> DelayedFold dom n delay a @@ l
-> DelayedFold dom n delay a @@ l
-> DelayedFold dom n delay a @@ (l+1)
go :: SNat l
-> (DelayedFold dom n delay a @@ l)
-> (DelayedFold dom n delay a @@ l)
-> DelayedFold dom n delay a @@ (l + 1)
go SNat x :: DelayedFold dom n delay a @@ l
x y :: DelayedFold dom n delay a @@ l
y = a
-> DSignal dom (n + (delay * l)) a
-> DSignal dom ((n + (delay * l)) + delay) a
forall (d :: Nat) (n :: Nat) a (dom :: Domain).
(HiddenClockResetEnable dom, NFDataX a, KnownNat d) =>
a -> DSignal dom n a -> DSignal dom (n + d) a
delayI a
dflt (a -> a -> a
op (a -> a -> a)
-> DSignal dom (n + (delay * l)) a
-> DSignal dom (n + (delay * l)) (a -> a)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DelayedFold dom n delay a @@ l
DSignal dom (n + (delay * l)) a
x DSignal dom (n + (delay * l)) (a -> a)
-> DSignal dom (n + (delay * l)) a
-> DSignal dom (n + (delay * l)) a
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> DelayedFold dom n delay a @@ l
DSignal dom (n + (delay * l)) a
y)