{-# LANGUAGE PostfixOperators #-}
{-# OPTIONS_HADDOCK hide #-}
module ForSyDe.Atom.MoC.SY.Interface where
import qualified ForSyDe.Atom.MoC.DE.Core as DE
import qualified ForSyDe.Atom.MoC.SDF.Core as SDF
import qualified ForSyDe.Atom.MoC.SY.Core as SY
import ForSyDe.Atom.MoC ((-.-),(-*))
import ForSyDe.Atom.MoC.Stream (Stream(..))
import ForSyDe.Atom.MoC.TimeStamp
import qualified ForSyDe.Atom.Skel.Vector as V (
Vector, vector, zipx, unzipx, fanout, unit, length, reverse, fromVector)
import ForSyDe.Atom.Utility.Tuple
toDE2 :: (Num t, Ord t, Eq t) => SY.Signal t
-> SY.Signal a
-> SY.Signal b
-> (DE.SignalBase t a, DE.SignalBase t b)
eventToDE :: SY t -> SY a -> DE t a
eventToDE (SY.SY t :: t
t) (SY.SY a :: a
a) = t -> a -> DE t a
forall t a. (Num t, Ord t, Eq t) => t -> a -> DE t a
DE.DE t
t a
a
toDE :: f (SY t) -> f (SY a) -> f (DE t a)
toDE ts :: f (SY t)
ts s1 :: f (SY a)
s1 = SY t -> SY a -> DE t a
forall t a. (Num t, Ord t) => SY t -> SY a -> DE t a
eventToDE (SY t -> SY a -> DE t a) -> f (SY t) -> f (SY a -> DE t a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f (SY t)
ts f (SY a -> DE t a) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f (SY a)
s1
toDE2 :: Signal t
-> Signal a -> Signal b -> (SignalBase t a, SignalBase t b)
toDE2 ts :: Signal t
ts s1 :: Signal a
s1 s2 :: Signal b
s2 = (Signal t -> Signal a -> SignalBase t a
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE Signal t
ts Signal a
s1, Signal t -> Signal b -> SignalBase t b
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE Signal t
ts Signal b
s2)
toDE3 :: f (SY t)
-> f (SY a)
-> f (SY a)
-> f (SY a)
-> (f (DE t a), f (DE t a), f (DE t a))
toDE3 ts :: f (SY t)
ts s1 :: f (SY a)
s1 s2 :: f (SY a)
s2 s3 :: f (SY a)
s3 = (f (SY t) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE f (SY t)
ts f (SY a)
s1, f (SY t) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE f (SY t)
ts f (SY a)
s2, f (SY t) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE f (SY t)
ts f (SY a)
s3)
toDE4 :: f (SY t)
-> f (SY a)
-> f (SY a)
-> f (SY a)
-> f (SY a)
-> (f (DE t a), f (DE t a), f (DE t a), f (DE t a))
toDE4 ts :: f (SY t)
ts s1 :: f (SY a)
s1 s2 :: f (SY a)
s2 s3 :: f (SY a)
s3 s4 :: f (SY a)
s4 = (f (SY t) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE f (SY t)
ts f (SY a)
s1, f (SY t) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE f (SY t)
ts f (SY a)
s2, f (SY t) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE f (SY t)
ts f (SY a)
s3, f (SY t) -> f (SY a) -> f (DE t a)
forall (f :: * -> *) t a.
(Applicative f, Num t, Ord t) =>
f (SY t) -> f (SY a) -> f (DE t a)
toDE f (SY t)
ts f (SY a)
s4)
toSDF1 :: SY.Signal a
-> SDF.Signal a
toSDF2 :: SY.Signal a
-> SY.Signal b
-> (SDF.Signal a, SDF.Signal b)
toSDF3 :: SY.Signal a -> SY.Signal b -> SY.Signal c
-> (SDF.Signal a, SDF.Signal b, SDF.Signal c)
toSDF4 :: SY.Signal a -> SY.Signal b -> SY.Signal c -> SY.Signal d
-> (SDF.Signal a, SDF.Signal b, SDF.Signal c, SDF.Signal d)
eventToSDF :: SY a -> SDF a
eventToSDF (SY.SY a :: a
a) = a -> SDF a
forall a. a -> SDF a
SDF.SDF a
a
toSDF1 :: Signal a -> Signal a
toSDF1 = (SY a -> SDF a) -> Signal a -> Signal a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SY a -> SDF a
forall a. SY a -> SDF a
eventToSDF
toSDF2 :: Signal a -> Signal b -> (Signal a, Signal b)
toSDF2 s1 :: Signal a
s1 s2 :: Signal b
s2 = (Signal a -> Signal a
forall a. Signal a -> Signal a
toSDF1 Signal a
s1, Signal b -> Signal b
forall a. Signal a -> Signal a
toSDF1 Signal b
s2)
toSDF3 :: Signal a -> Signal b -> Signal c -> (Signal a, Signal b, Signal c)
toSDF3 s1 :: Signal a
s1 s2 :: Signal b
s2 s3 :: Signal c
s3 = (Signal a -> Signal a
forall a. Signal a -> Signal a
toSDF1 Signal a
s1, Signal b -> Signal b
forall a. Signal a -> Signal a
toSDF1 Signal b
s2, Signal c -> Signal c
forall a. Signal a -> Signal a
toSDF1 Signal c
s3)
toSDF4 :: Signal a
-> Signal b
-> Signal c
-> Signal d
-> (Signal a, Signal b, Signal c, Signal d)
toSDF4 s1 :: Signal a
s1 s2 :: Signal b
s2 s3 :: Signal c
s3 s4 :: Signal d
s4 = (Signal a -> Signal a
forall a. Signal a -> Signal a
toSDF1 Signal a
s1, Signal b -> Signal b
forall a. Signal a -> Signal a
toSDF1 Signal b
s2, Signal c -> Signal c
forall a. Signal a -> Signal a
toSDF1 Signal c
s3, Signal d -> Signal d
forall a. Signal a -> Signal a
toSDF1 Signal d
s4)
toSDF1' :: SDF.Prod
-> SY.Signal (V.Vector a)
-> SDF.Signal a
toSDF2' :: (SDF.Prod, SDF.Prod)
-> SY.Signal (V.Vector a)
-> SY.Signal (V.Vector b)
-> (SDF.Signal a, SDF.Signal b)
toSDF3' :: (SDF.Prod, SDF.Prod, SDF.Prod)
-> SY.Signal (V.Vector a) -> SY.Signal (V.Vector b) -> SY.Signal (V.Vector c)
-> (SDF.Signal a, SDF.Signal b, SDF.Signal c)
toSDF4' :: (SDF.Prod, SDF.Prod, SDF.Prod, SDF.Prod)
-> SY.Signal (V.Vector a) -> SY.Signal (V.Vector b)
-> SY.Signal (V.Vector c) -> SY.Signal (V.Vector d)
-> (SDF.Signal a, SDF.Signal b, SDF.Signal c, SDF.Signal d)
toSDF1' :: Prod -> Signal (Vector a) -> Signal a
toSDF1' p1 :: Prod
p1 s1 :: Signal (Vector a)
s1 = (SY (Prod, [a]) -> SDF (Prod, [a])
forall a. SY a -> SDF a
eventToSDF (SY (Prod, [a]) -> SDF (Prod, [a]))
-> Stream (SY (Prod, [a])) -> Stream (SDF (Prod, [a]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (((,) Prod
p1 ([a] -> (Prod, [a]))
-> (Vector a -> [a]) -> Vector a -> (Prod, [a])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> [a]
forall a. Vector a -> [a]
V.fromVector) Fun SY (Vector a) (Prod, [a])
-> Signal (Vector a) -> Stream (SY (Prod, [a]))
forall (e :: * -> *) a b.
MoC e =>
Fun e a b -> Stream (e a) -> Stream (e b)
-.- Signal (Vector a)
s1) Stream (SDF (Ret SDF a)) -> Signal a
forall (e :: * -> *) b.
MoC e =>
Stream (e (Ret e b)) -> Stream (e b)
-*)
toSDF2' :: (Prod, Prod)
-> Signal (Vector a) -> Signal (Vector b) -> (Signal a, Signal b)
toSDF2' (p1 :: Prod
p1,p2 :: Prod
p2) s1 :: Signal (Vector a)
s1 s2 :: Signal (Vector b)
s2 = (Prod -> Signal (Vector a) -> Signal a
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p1 Signal (Vector a)
s1, Prod -> Signal (Vector b) -> Signal b
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p2 Signal (Vector b)
s2)
toSDF3' :: (Prod, Prod, Prod)
-> Signal (Vector a)
-> Signal (Vector b)
-> Signal (Vector c)
-> (Signal a, Signal b, Signal c)
toSDF3' (p1 :: Prod
p1,p2 :: Prod
p2,p3 :: Prod
p3) s1 :: Signal (Vector a)
s1 s2 :: Signal (Vector b)
s2 s3 :: Signal (Vector c)
s3 = (Prod -> Signal (Vector a) -> Signal a
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p1 Signal (Vector a)
s1, Prod -> Signal (Vector b) -> Signal b
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p2 Signal (Vector b)
s2, Prod -> Signal (Vector c) -> Signal c
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p3 Signal (Vector c)
s3)
toSDF4' :: (Prod, Prod, Prod, Prod)
-> Signal (Vector a)
-> Signal (Vector b)
-> Signal (Vector c)
-> Signal (Vector d)
-> (Signal a, Signal b, Signal c, Signal d)
toSDF4' (p1 :: Prod
p1,p2 :: Prod
p2,p3 :: Prod
p3,p4 :: Prod
p4) s1 :: Signal (Vector a)
s1 s2 :: Signal (Vector b)
s2 s3 :: Signal (Vector c)
s3 s4 :: Signal (Vector d)
s4 = (Prod -> Signal (Vector a) -> Signal a
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p1 Signal (Vector a)
s1, Prod -> Signal (Vector b) -> Signal b
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p2 Signal (Vector b)
s2, Prod -> Signal (Vector c) -> Signal c
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p3 Signal (Vector c)
s3,
Prod -> Signal (Vector d) -> Signal d
forall a. Prod -> Signal (Vector a) -> Signal a
toSDF1' Prod
p4 Signal (Vector d)
s4)
zipx ::V.Vector (SY.Signal a) -> SY.Signal (V.Vector a)
zipx :: Vector (Signal a) -> Signal (Vector a)
zipx = Vector
((Vector a -> Vector a -> Vector a)
-> Fun SY (Vector a) (Fun SY (Vector a) (Ret SY (Vector a))))
-> Vector (Signal a) -> Signal (Vector a)
forall (e :: * -> *) a.
MoC e =>
Vector
((Vector a -> Vector a -> Vector a)
-> Fun e (Vector a) (Fun e (Vector a) (Ret e (Vector a))))
-> Vector (Stream (e a)) -> Stream (e (Vector a))
V.zipx (((Vector a -> Vector a -> Vector a)
-> Vector a -> Vector a -> Vector a)
-> Vector
((Vector a -> Vector a -> Vector a)
-> Vector a -> Vector a -> Vector a)
forall t. t -> Vector t
V.fanout (\cat :: Vector a -> Vector a -> Vector a
cat a :: Vector a
a b :: Vector a
b -> Vector a
a Vector a -> Vector a -> Vector a
`cat` Vector a
b))
unzipx :: Integer -> SY.Signal (V.Vector a) -> V.Vector (SY.Signal a)
unzipx :: Integer -> Signal (Vector a) -> Vector (Signal a)
unzipx n :: Integer
n = Vector (Signal a) -> Vector (Signal a)
forall a. Vector a -> Vector a
V.reverse (Vector (Signal a) -> Vector (Signal a))
-> (Signal (Vector a) -> Vector (Signal a))
-> Signal (Vector a)
-> Vector (Signal a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector a -> Vector (Ret SY a))
-> Integer -> Signal (Vector a) -> Vector (Signal a)
forall (e :: * -> *) a.
MoC e =>
(Vector a -> Vector (Ret e a))
-> Integer -> Stream (e (Vector a)) -> Vector (Stream (e a))
V.unzipx Vector a -> Vector (Ret SY a)
forall a. a -> a
id Integer
n
unzipx' :: SY.Signal (V.Vector a) -> V.Vector (SY.Signal a)
unzipx' :: Signal (Vector a) -> Vector (Signal a)
unzipx' s :: Signal (Vector a)
s@(a :: SY (Vector a)
a:-_) = Integer -> Signal (Vector a) -> Vector (Signal a)
forall a. Integer -> Signal (Vector a) -> Vector (Signal a)
unzipx (Vector a -> Integer
forall p a. Num p => Vector a -> p
V.length (Vector a -> Integer) -> Vector a -> Integer
forall a b. (a -> b) -> a -> b
$ SY (Vector a) -> Vector a
forall a. SY a -> a
SY.val SY (Vector a)
a) Signal (Vector a)
s