{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeOperators #-}
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
module Clash.Signal.Delayed.Bundle (
Bundle,
Unbundled,
bundle,
unbundle,
) where
import Control.Applicative (liftA2)
import GHC.TypeLits (KnownNat)
import Prelude hiding (head, map, tail)
import Clash.Signal.Internal (Domain)
import Clash.Signal.Delayed (DSignal, toSignal, unsafeFromSignal)
import qualified Clash.Signal.Bundle as B
import Clash.Sized.BitVector (Bit, BitVector)
import Clash.Sized.Fixed (Fixed)
import Clash.Sized.Index (Index)
import Clash.Sized.RTree (RTree, lazyT)
import Clash.Sized.Signed (Signed)
import Clash.Sized.Unsigned (Unsigned)
import Clash.Sized.Vector (Vec, lazyV)
import GHC.TypeLits (Nat)
class Bundle a where
type Unbundled (dom :: Domain) (d :: Nat) a = res | res -> dom d a
type Unbundled dom d a = DSignal dom d a
bundle :: Unbundled dom d a -> DSignal dom d a
{-# INLINE bundle #-}
default bundle :: (DSignal dom d a ~ Unbundled dom d a)
=> Unbundled dom d a -> DSignal dom d a
bundle s :: Unbundled dom d a
s = DSignal dom d a
Unbundled dom d a
s
unbundle :: DSignal dom d a -> Unbundled dom d a
{-# INLINE unbundle #-}
default unbundle :: (Unbundled dom d a ~ DSignal dom d a)
=> DSignal dom d a -> Unbundled dom d a
unbundle s :: DSignal dom d a
s = DSignal dom d a
Unbundled dom d a
s
instance Bundle ()
instance Bundle Bool
instance Bundle Integer
instance Bundle Int
instance Bundle Float
instance Bundle Double
instance Bundle (Maybe a)
instance Bundle (Either a b)
instance Bundle Bit
instance Bundle (BitVector n)
instance Bundle (Index n)
instance Bundle (Fixed rep int frac)
instance Bundle (Signed n)
instance Bundle (Unsigned n)
instance Bundle (a,b) where
type Unbundled t delay (a,b) = (DSignal t delay a, DSignal t delay b)
bundle :: Unbundled dom d (a, b) -> DSignal dom d (a, b)
bundle = (DSignal dom d a -> DSignal dom d b -> DSignal dom d (a, b))
-> (DSignal dom d a, DSignal dom d b) -> DSignal dom d (a, b)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((a -> b -> (a, b))
-> DSignal dom d a -> DSignal dom d b -> DSignal dom d (a, b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,))
unbundle :: DSignal dom d (a, b) -> Unbundled dom d (a, b)
unbundle tup :: DSignal dom d (a, b)
tup = (((a, b) -> a) -> DSignal dom d (a, b) -> DSignal dom d a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, b) -> a
forall a b. (a, b) -> a
fst DSignal dom d (a, b)
tup, ((a, b) -> b) -> DSignal dom d (a, b) -> DSignal dom d b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, b) -> b
forall a b. (a, b) -> b
snd DSignal dom d (a, b)
tup)
instance Bundle (a,b,c) where
type Unbundled t delay (a,b,c) =
( DSignal t delay a, DSignal t delay b, DSignal t delay c)
bundle :: Unbundled dom d (a, b, c) -> DSignal dom d (a, b, c)
bundle (a,b,c) = (,,) (a -> b -> c -> (a, b, c))
-> DSignal dom d a -> DSignal dom d (b -> c -> (a, b, c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DSignal dom d a
a DSignal dom d (b -> c -> (a, b, c))
-> DSignal dom d b -> DSignal dom d (c -> (a, b, c))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d b
b DSignal dom d (c -> (a, b, c))
-> DSignal dom d c -> DSignal dom d (a, b, c)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d c
c
unbundle :: DSignal dom d (a, b, c) -> Unbundled dom d (a, b, c)
unbundle tup :: DSignal dom d (a, b, c)
tup = (((a, b, c) -> a) -> DSignal dom d (a, b, c) -> DSignal dom d a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(x :: a
x,_,_) -> a
x) DSignal dom d (a, b, c)
tup
,((a, b, c) -> b) -> DSignal dom d (a, b, c) -> DSignal dom d b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,x :: b
x,_) -> b
x) DSignal dom d (a, b, c)
tup
,((a, b, c) -> c) -> DSignal dom d (a, b, c) -> DSignal dom d c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,x :: c
x) -> c
x) DSignal dom d (a, b, c)
tup
)
instance Bundle (a,b,c,d) where
type Unbundled t delay (a,b,c,d) =
( DSignal t delay a, DSignal t delay b, DSignal t delay c, DSignal t delay d)
bundle :: Unbundled dom d (a, b, c, d) -> DSignal dom d (a, b, c, d)
bundle (a,b,c,d) = (,,,) (a -> b -> c -> d -> (a, b, c, d))
-> DSignal dom d a -> DSignal dom d (b -> c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DSignal dom d a
a DSignal dom d (b -> c -> d -> (a, b, c, d))
-> DSignal dom d b -> DSignal dom d (c -> d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d b
b DSignal dom d (c -> d -> (a, b, c, d))
-> DSignal dom d c -> DSignal dom d (d -> (a, b, c, d))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d c
c DSignal dom d (d -> (a, b, c, d))
-> DSignal dom d d -> DSignal dom d (a, b, c, d)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d d
d
unbundle :: DSignal dom d (a, b, c, d) -> Unbundled dom d (a, b, c, d)
unbundle tup :: DSignal dom d (a, b, c, d)
tup = (((a, b, c, d) -> a)
-> DSignal dom d (a, b, c, d) -> DSignal dom d a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(x :: a
x,_,_,_) -> a
x) DSignal dom d (a, b, c, d)
tup
,((a, b, c, d) -> b)
-> DSignal dom d (a, b, c, d) -> DSignal dom d b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,x :: b
x,_,_) -> b
x) DSignal dom d (a, b, c, d)
tup
,((a, b, c, d) -> c)
-> DSignal dom d (a, b, c, d) -> DSignal dom d c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,x :: c
x,_) -> c
x) DSignal dom d (a, b, c, d)
tup
,((a, b, c, d) -> d)
-> DSignal dom d (a, b, c, d) -> DSignal dom d d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,x :: d
x) -> d
x) DSignal dom d (a, b, c, d)
tup
)
instance Bundle (a,b,c,d,e) where
type Unbundled t delay (a,b,c,d,e) =
( DSignal t delay a, DSignal t delay b, DSignal t delay c, DSignal t delay d
, DSignal t delay e)
bundle :: Unbundled dom d (a, b, c, d, e) -> DSignal dom d (a, b, c, d, e)
bundle (a,b,c,d,e) = (,,,,) (a -> b -> c -> d -> e -> (a, b, c, d, e))
-> DSignal dom d a
-> DSignal dom d (b -> c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DSignal dom d a
a DSignal dom d (b -> c -> d -> e -> (a, b, c, d, e))
-> DSignal dom d b
-> DSignal dom d (c -> d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d b
b DSignal dom d (c -> d -> e -> (a, b, c, d, e))
-> DSignal dom d c -> DSignal dom d (d -> e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d c
c DSignal dom d (d -> e -> (a, b, c, d, e))
-> DSignal dom d d -> DSignal dom d (e -> (a, b, c, d, e))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d d
d DSignal dom d (e -> (a, b, c, d, e))
-> DSignal dom d e -> DSignal dom d (a, b, c, d, e)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d e
e
unbundle :: DSignal dom d (a, b, c, d, e) -> Unbundled dom d (a, b, c, d, e)
unbundle tup :: DSignal dom d (a, b, c, d, e)
tup = (((a, b, c, d, e) -> a)
-> DSignal dom d (a, b, c, d, e) -> DSignal dom d a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(x :: a
x,_,_,_,_) -> a
x) DSignal dom d (a, b, c, d, e)
tup
,((a, b, c, d, e) -> b)
-> DSignal dom d (a, b, c, d, e) -> DSignal dom d b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,x :: b
x,_,_,_) -> b
x) DSignal dom d (a, b, c, d, e)
tup
,((a, b, c, d, e) -> c)
-> DSignal dom d (a, b, c, d, e) -> DSignal dom d c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,x :: c
x,_,_) -> c
x) DSignal dom d (a, b, c, d, e)
tup
,((a, b, c, d, e) -> d)
-> DSignal dom d (a, b, c, d, e) -> DSignal dom d d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,x :: d
x,_) -> d
x) DSignal dom d (a, b, c, d, e)
tup
,((a, b, c, d, e) -> e)
-> DSignal dom d (a, b, c, d, e) -> DSignal dom d e
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,x :: e
x) -> e
x) DSignal dom d (a, b, c, d, e)
tup
)
instance Bundle (a,b,c,d,e,f) where
type Unbundled t delay (a,b,c,d,e,f) =
( DSignal t delay a, DSignal t delay b, DSignal t delay c, DSignal t delay d
, DSignal t delay e, DSignal t delay f)
bundle :: Unbundled dom d (a, b, c, d, e, f)
-> DSignal dom d (a, b, c, d, e, f)
bundle (a,b,c,d,e,f) = (,,,,,) (a -> b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> DSignal dom d a
-> DSignal dom d (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DSignal dom d a
a DSignal dom d (b -> c -> d -> e -> f -> (a, b, c, d, e, f))
-> DSignal dom d b
-> DSignal dom d (c -> d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d b
b DSignal dom d (c -> d -> e -> f -> (a, b, c, d, e, f))
-> DSignal dom d c
-> DSignal dom d (d -> e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d c
c DSignal dom d (d -> e -> f -> (a, b, c, d, e, f))
-> DSignal dom d d -> DSignal dom d (e -> f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d d
d DSignal dom d (e -> f -> (a, b, c, d, e, f))
-> DSignal dom d e -> DSignal dom d (f -> (a, b, c, d, e, f))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d e
e DSignal dom d (f -> (a, b, c, d, e, f))
-> DSignal dom d f -> DSignal dom d (a, b, c, d, e, f)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d f
f
unbundle :: DSignal dom d (a, b, c, d, e, f)
-> Unbundled dom d (a, b, c, d, e, f)
unbundle tup :: DSignal dom d (a, b, c, d, e, f)
tup = (((a, b, c, d, e, f) -> a)
-> DSignal dom d (a, b, c, d, e, f) -> DSignal dom d a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(x :: a
x,_,_,_,_,_) -> a
x) DSignal dom d (a, b, c, d, e, f)
tup
,((a, b, c, d, e, f) -> b)
-> DSignal dom d (a, b, c, d, e, f) -> DSignal dom d b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,x :: b
x,_,_,_,_) -> b
x) DSignal dom d (a, b, c, d, e, f)
tup
,((a, b, c, d, e, f) -> c)
-> DSignal dom d (a, b, c, d, e, f) -> DSignal dom d c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,x :: c
x,_,_,_) -> c
x) DSignal dom d (a, b, c, d, e, f)
tup
,((a, b, c, d, e, f) -> d)
-> DSignal dom d (a, b, c, d, e, f) -> DSignal dom d d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,x :: d
x,_,_) -> d
x) DSignal dom d (a, b, c, d, e, f)
tup
,((a, b, c, d, e, f) -> e)
-> DSignal dom d (a, b, c, d, e, f) -> DSignal dom d e
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,x :: e
x,_) -> e
x) DSignal dom d (a, b, c, d, e, f)
tup
,((a, b, c, d, e, f) -> f)
-> DSignal dom d (a, b, c, d, e, f) -> DSignal dom d f
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,_,x :: f
x) -> f
x) DSignal dom d (a, b, c, d, e, f)
tup
)
instance Bundle (a,b,c,d,e,f,g) where
type Unbundled t delay (a,b,c,d,e,f,g) =
( DSignal t delay a, DSignal t delay b, DSignal t delay c, DSignal t delay d
, DSignal t delay e, DSignal t delay f, DSignal t delay g)
bundle :: Unbundled dom d (a, b, c, d, e, f, g)
-> DSignal dom d (a, b, c, d, e, f, g)
bundle (a,b,c,d,e,f,g) = (,,,,,,) (a -> b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> DSignal dom d a
-> DSignal
dom d (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DSignal dom d a
a DSignal dom d (b -> c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> DSignal dom d b
-> DSignal dom d (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d b
b DSignal dom d (c -> d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> DSignal dom d c
-> DSignal dom d (d -> e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d c
c DSignal dom d (d -> e -> f -> g -> (a, b, c, d, e, f, g))
-> DSignal dom d d
-> DSignal dom d (e -> f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d d
d DSignal dom d (e -> f -> g -> (a, b, c, d, e, f, g))
-> DSignal dom d e
-> DSignal dom d (f -> g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d e
e DSignal dom d (f -> g -> (a, b, c, d, e, f, g))
-> DSignal dom d f -> DSignal dom d (g -> (a, b, c, d, e, f, g))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d f
f
DSignal dom d (g -> (a, b, c, d, e, f, g))
-> DSignal dom d g -> DSignal dom d (a, b, c, d, e, f, g)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d g
g
unbundle :: DSignal dom d (a, b, c, d, e, f, g)
-> Unbundled dom d (a, b, c, d, e, f, g)
unbundle tup :: DSignal dom d (a, b, c, d, e, f, g)
tup = (((a, b, c, d, e, f, g) -> a)
-> DSignal dom d (a, b, c, d, e, f, g) -> DSignal dom d a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(x :: a
x,_,_,_,_,_,_) -> a
x) DSignal dom d (a, b, c, d, e, f, g)
tup
,((a, b, c, d, e, f, g) -> b)
-> DSignal dom d (a, b, c, d, e, f, g) -> DSignal dom d b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,x :: b
x,_,_,_,_,_) -> b
x) DSignal dom d (a, b, c, d, e, f, g)
tup
,((a, b, c, d, e, f, g) -> c)
-> DSignal dom d (a, b, c, d, e, f, g) -> DSignal dom d c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,x :: c
x,_,_,_,_) -> c
x) DSignal dom d (a, b, c, d, e, f, g)
tup
,((a, b, c, d, e, f, g) -> d)
-> DSignal dom d (a, b, c, d, e, f, g) -> DSignal dom d d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,x :: d
x,_,_,_) -> d
x) DSignal dom d (a, b, c, d, e, f, g)
tup
,((a, b, c, d, e, f, g) -> e)
-> DSignal dom d (a, b, c, d, e, f, g) -> DSignal dom d e
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,x :: e
x,_,_) -> e
x) DSignal dom d (a, b, c, d, e, f, g)
tup
,((a, b, c, d, e, f, g) -> f)
-> DSignal dom d (a, b, c, d, e, f, g) -> DSignal dom d f
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,_,x :: f
x,_) -> f
x) DSignal dom d (a, b, c, d, e, f, g)
tup
,((a, b, c, d, e, f, g) -> g)
-> DSignal dom d (a, b, c, d, e, f, g) -> DSignal dom d g
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,_,_,x :: g
x) -> g
x) DSignal dom d (a, b, c, d, e, f, g)
tup
)
instance Bundle (a,b,c,d,e,f,g,h) where
type Unbundled t delay (a,b,c,d,e,f,g,h) =
( DSignal t delay a, DSignal t delay b, DSignal t delay c, DSignal t delay d
, DSignal t delay e, DSignal t delay f ,DSignal t delay g, DSignal t delay h)
bundle :: Unbundled dom d (a, b, c, d, e, f, g, h)
-> DSignal dom d (a, b, c, d, e, f, g, h)
bundle (a,b,c,d,e,f,g,h) = (,,,,,,,) (a -> b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d a
-> DSignal
dom d (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DSignal dom d a
a DSignal
dom d (b -> c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d b
-> DSignal
dom d (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d b
b DSignal
dom d (c -> d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d c
-> DSignal
dom d (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d c
c DSignal dom d (d -> e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d d
-> DSignal dom d (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d d
d DSignal dom d (e -> f -> g -> h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d e
-> DSignal dom d (f -> g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d e
e DSignal dom d (f -> g -> h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d f
-> DSignal dom d (g -> h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d f
f
DSignal dom d (g -> h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d g -> DSignal dom d (h -> (a, b, c, d, e, f, g, h))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d g
g DSignal dom d (h -> (a, b, c, d, e, f, g, h))
-> DSignal dom d h -> DSignal dom d (a, b, c, d, e, f, g, h)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DSignal dom d h
h
unbundle :: DSignal dom d (a, b, c, d, e, f, g, h)
-> Unbundled dom d (a, b, c, d, e, f, g, h)
unbundle tup :: DSignal dom d (a, b, c, d, e, f, g, h)
tup = (((a, b, c, d, e, f, g, h) -> a)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(x :: a
x,_,_,_,_,_,_,_) -> a
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
,((a, b, c, d, e, f, g, h) -> b)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,x :: b
x,_,_,_,_,_,_) -> b
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
,((a, b, c, d, e, f, g, h) -> c)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,x :: c
x,_,_,_,_,_) -> c
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
,((a, b, c, d, e, f, g, h) -> d)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,x :: d
x,_,_,_,_) -> d
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
,((a, b, c, d, e, f, g, h) -> e)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d e
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,x :: e
x,_,_,_) -> e
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
,((a, b, c, d, e, f, g, h) -> f)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d f
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,_,x :: f
x,_,_) -> f
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
,((a, b, c, d, e, f, g, h) -> g)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d g
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,_,_,x :: g
x,_) -> g
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
,((a, b, c, d, e, f, g, h) -> h)
-> DSignal dom d (a, b, c, d, e, f, g, h) -> DSignal dom d h
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(_,_,_,_,_,_,_,x :: h
x) -> h
x) DSignal dom d (a, b, c, d, e, f, g, h)
tup
)
instance KnownNat n => Bundle (Vec n a) where
type Unbundled t d (Vec n a) = Vec n (DSignal t d a)
bundle :: Unbundled dom d (Vec n a) -> DSignal dom d (Vec n a)
bundle = Signal dom (Vec n a) -> DSignal dom d (Vec n a)
forall (dom :: Domain) a (n :: Nat).
Signal dom a -> DSignal dom n a
unsafeFromSignal (Signal dom (Vec n a) -> DSignal dom d (Vec n a))
-> (Vec n (DSignal dom d a) -> Signal dom (Vec n a))
-> Vec n (DSignal dom d a)
-> DSignal dom d (Vec n a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vec n (Signal dom a) -> Signal dom (Vec n a)
forall a (dom :: Domain).
Bundle a =>
Unbundled dom a -> Signal dom a
B.bundle (Vec n (Signal dom a) -> Signal dom (Vec n a))
-> (Vec n (DSignal dom d a) -> Vec n (Signal dom a))
-> Vec n (DSignal dom d a)
-> Signal dom (Vec n a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DSignal dom d a -> Signal dom a)
-> Vec n (DSignal dom d a) -> Vec n (Signal dom a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DSignal dom d a -> Signal dom a
forall (dom :: Domain) (delay :: Nat) a.
DSignal dom delay a -> Signal dom a
toSignal
unbundle :: DSignal dom d (Vec n a) -> Unbundled dom d (Vec n a)
unbundle = DSignal dom d (Vec n a) -> Vec n (DSignal dom d a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (DSignal dom d (Vec n a) -> Vec n (DSignal dom d a))
-> (DSignal dom d (Vec n a) -> DSignal dom d (Vec n a))
-> DSignal dom d (Vec n a)
-> Vec n (DSignal dom d a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vec n a -> Vec n a)
-> DSignal dom d (Vec n a) -> DSignal dom d (Vec n a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Vec n a -> Vec n a
forall (n :: Nat) a. KnownNat n => Vec n a -> Vec n a
lazyV
instance KnownNat d => Bundle (RTree d a) where
type Unbundled t delay (RTree d a) = RTree d (DSignal t delay a)
bundle :: Unbundled dom d (RTree d a) -> DSignal dom d (RTree d a)
bundle = Unbundled dom d (RTree d a) -> DSignal dom d (RTree d a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA
unbundle :: DSignal dom d (RTree d a) -> Unbundled dom d (RTree d a)
unbundle = DSignal dom d (RTree d a) -> RTree d (DSignal dom d a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (DSignal dom d (RTree d a) -> RTree d (DSignal dom d a))
-> (DSignal dom d (RTree d a) -> DSignal dom d (RTree d a))
-> DSignal dom d (RTree d a)
-> RTree d (DSignal dom d a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RTree d a -> RTree d a)
-> DSignal dom d (RTree d a) -> DSignal dom d (RTree d a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RTree d a -> RTree d a
forall (d :: Nat) a. KnownNat d => RTree d a -> RTree d a
lazyT