{-# LANGUAGE TypeFamilies, FlexibleInstances, GADTs, StandaloneDeriving #-}
{-# OPTIONS_HADDOCK hide #-}
module ForSyDe.Atom.MoC.CT.Core where
import ForSyDe.Atom.MoC
import ForSyDe.Atom.MoC.Time
import ForSyDe.Atom.MoC.TimeStamp
import ForSyDe.Atom.Utility.Tuple
type SignalBase timestamp time a = Stream (CT timestamp time a)
type Signal a = SignalBase TimeStamp Time a
data CT timestamp time a where
CT :: (Num time, Num timestamp, Ord timestamp, Eq timestamp)
=> { CT timestamp time a -> timestamp
tag :: timestamp
, CT timestamp time a -> time
phase :: time
, CT timestamp time a -> time -> a
func :: time -> a
} -> CT timestamp time a
instance (Num ts, Num tm, Real ts, Fractional tm, Ord ts, Ord tm, Eq ts) =>
MoC (CT ts tm) where
type Fun (CT ts tm) a b = a -> b
type Ret (CT ts tm) b = b
-.- :: Fun (CT ts tm) a b -> Stream (CT ts tm a) -> Stream (CT ts tm b)
(-.-) = (CT ts tm a -> CT ts tm b)
-> Stream (CT ts tm a) -> Stream (CT ts tm b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((CT ts tm a -> CT ts tm b)
-> Stream (CT ts tm a) -> Stream (CT ts tm b))
-> ((a -> b) -> CT ts tm a -> CT ts tm b)
-> (a -> b)
-> Stream (CT ts tm a)
-> Stream (CT ts tm b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> CT ts tm a -> CT ts tm b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
_ -*- :: Stream (CT ts tm (Fun (CT ts tm) a b))
-> Stream (CT ts tm a) -> Stream (CT ts tm b)
-*- NullS = Stream (CT ts tm b)
forall e. Stream e
NullS
NullS -*- _ = Stream (CT ts tm b)
forall e. Stream e
NullS
(f :: CT ts tm (Fun (CT ts tm) a b)
f:-fs :: Stream (CT ts tm (Fun (CT ts tm) a b))
fs) -*- (x :: CT ts tm a
x:-xs :: Stream (CT ts tm a)
xs) = CT ts tm (Fun (CT ts tm) a b)
CT ts tm (a -> b)
f CT ts tm (a -> b) -> CT ts tm a -> CT ts tm b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CT ts tm a
x CT ts tm b -> Stream (CT ts tm b) -> Stream (CT ts tm b)
forall e. e -> Stream e -> Stream e
:- CT ts tm (a -> b)
-> CT ts tm a
-> Stream (CT ts tm (a -> b))
-> Stream (CT ts tm a)
-> Stream (CT ts tm b)
forall timestamp time a b.
(Num timestamp, Num time, Ord time, Ord timestamp) =>
CT timestamp time (a -> b)
-> CT timestamp time a
-> Stream (CT timestamp time (a -> b))
-> Stream (CT timestamp time a)
-> Stream (CT timestamp time b)
comb CT ts tm (Fun (CT ts tm) a b)
CT ts tm (a -> b)
f CT ts tm a
x Stream (CT ts tm (Fun (CT ts tm) a b))
Stream (CT ts tm (a -> b))
fs Stream (CT ts tm a)
xs
where
comb :: CT timestamp time (a -> b)
-> CT timestamp time a
-> Stream (CT timestamp time (a -> b))
-> Stream (CT timestamp time a)
-> Stream (CT timestamp time b)
comb pf :: CT timestamp time (a -> b)
pf px :: CT timestamp time a
px s1 :: Stream (CT timestamp time (a -> b))
s1@(f :: CT timestamp time (a -> b)
f :- fs :: Stream (CT timestamp time (a -> b))
fs) s2 :: Stream (CT timestamp time a)
s2@(x :: CT timestamp time a
x :- xs :: Stream (CT timestamp time a)
xs)
| CT timestamp time (a -> b) -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time (a -> b)
f timestamp -> timestamp -> Bool
forall a. Eq a => a -> a -> Bool
== CT timestamp time a -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time a
x = CT timestamp time (a -> b)
f CT timestamp time (a -> b)
-> CT timestamp time (a -> b) -> CT timestamp time (a -> b)
forall timestamp time a timestamp time a.
CT timestamp time a -> CT timestamp time a -> CT timestamp time a
%> CT timestamp time (a -> b)
f CT timestamp time (a -> b)
-> CT timestamp time a -> CT timestamp time b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CT timestamp time a
x CT timestamp time b
-> Stream (CT timestamp time b) -> Stream (CT timestamp time b)
forall e. e -> Stream e -> Stream e
:- CT timestamp time (a -> b)
-> CT timestamp time a
-> Stream (CT timestamp time (a -> b))
-> Stream (CT timestamp time a)
-> Stream (CT timestamp time b)
comb CT timestamp time (a -> b)
f CT timestamp time a
x Stream (CT timestamp time (a -> b))
fs Stream (CT timestamp time a)
xs
| CT timestamp time (a -> b) -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time (a -> b)
f timestamp -> timestamp -> Bool
forall a. Ord a => a -> a -> Bool
< CT timestamp time a -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time a
x = CT timestamp time (a -> b)
f CT timestamp time (a -> b)
-> CT timestamp time (a -> b) -> CT timestamp time (a -> b)
forall timestamp time a timestamp time a.
CT timestamp time a -> CT timestamp time a -> CT timestamp time a
%> CT timestamp time (a -> b)
f CT timestamp time (a -> b)
-> CT timestamp time a -> CT timestamp time b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CT timestamp time a
px CT timestamp time b
-> Stream (CT timestamp time b) -> Stream (CT timestamp time b)
forall e. e -> Stream e -> Stream e
:- CT timestamp time (a -> b)
-> CT timestamp time a
-> Stream (CT timestamp time (a -> b))
-> Stream (CT timestamp time a)
-> Stream (CT timestamp time b)
comb CT timestamp time (a -> b)
f CT timestamp time a
px Stream (CT timestamp time (a -> b))
fs Stream (CT timestamp time a)
s2
| CT timestamp time (a -> b) -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time (a -> b)
f timestamp -> timestamp -> Bool
forall a. Ord a => a -> a -> Bool
> CT timestamp time a -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time a
x = CT timestamp time a
x CT timestamp time a
-> CT timestamp time (a -> b) -> CT timestamp time (a -> b)
forall timestamp time a timestamp time a.
CT timestamp time a -> CT timestamp time a -> CT timestamp time a
%> CT timestamp time (a -> b)
pf CT timestamp time (a -> b)
-> CT timestamp time a -> CT timestamp time b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CT timestamp time a
x CT timestamp time b
-> Stream (CT timestamp time b) -> Stream (CT timestamp time b)
forall e. e -> Stream e -> Stream e
:- CT timestamp time (a -> b)
-> CT timestamp time a
-> Stream (CT timestamp time (a -> b))
-> Stream (CT timestamp time a)
-> Stream (CT timestamp time b)
comb CT timestamp time (a -> b)
pf CT timestamp time a
x Stream (CT timestamp time (a -> b))
s1 Stream (CT timestamp time a)
xs
comb _ px :: CT timestamp time a
px (f :: CT timestamp time (a -> b)
f :- fs :: Stream (CT timestamp time (a -> b))
fs) NullS = CT timestamp time (a -> b)
f CT timestamp time (a -> b)
-> CT timestamp time (a -> b) -> CT timestamp time (a -> b)
forall timestamp time a timestamp time a.
CT timestamp time a -> CT timestamp time a -> CT timestamp time a
%> CT timestamp time (a -> b)
f CT timestamp time (a -> b)
-> CT timestamp time a -> CT timestamp time b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CT timestamp time a
px CT timestamp time b
-> Stream (CT timestamp time b) -> Stream (CT timestamp time b)
forall e. e -> Stream e -> Stream e
:- CT timestamp time (a -> b)
-> CT timestamp time a
-> Stream (CT timestamp time (a -> b))
-> Stream (CT timestamp time a)
-> Stream (CT timestamp time b)
comb CT timestamp time (a -> b)
f CT timestamp time a
px Stream (CT timestamp time (a -> b))
fs Stream (CT timestamp time a)
forall e. Stream e
NullS
comb pf :: CT timestamp time (a -> b)
pf _ NullS (x :: CT timestamp time a
x :- xs :: Stream (CT timestamp time a)
xs) = CT timestamp time a
x CT timestamp time a
-> CT timestamp time (a -> b) -> CT timestamp time (a -> b)
forall timestamp time a timestamp time a.
CT timestamp time a -> CT timestamp time a -> CT timestamp time a
%> CT timestamp time (a -> b)
pf CT timestamp time (a -> b)
-> CT timestamp time a -> CT timestamp time b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> CT timestamp time a
x CT timestamp time b
-> Stream (CT timestamp time b) -> Stream (CT timestamp time b)
forall e. e -> Stream e -> Stream e
:- CT timestamp time (a -> b)
-> CT timestamp time a
-> Stream (CT timestamp time (a -> b))
-> Stream (CT timestamp time a)
-> Stream (CT timestamp time b)
comb CT timestamp time (a -> b)
pf CT timestamp time a
x Stream (CT timestamp time (a -> b))
forall e. Stream e
NullS Stream (CT timestamp time a)
xs
comb _ _ NullS NullS = Stream (CT timestamp time b)
forall e. Stream e
NullS
-* :: Stream (CT ts tm (Ret (CT ts tm) b)) -> Stream (CT ts tm b)
(-*) = Stream (CT ts tm (Ret (CT ts tm) b)) -> Stream (CT ts tm b)
forall a. a -> a
id
(CT _ p :: tm
p v :: tm -> a
v :- _) -<- :: Stream (CT ts tm a) -> Stream (CT ts tm a) -> Stream (CT ts tm a)
-<- xs :: Stream (CT ts tm a)
xs = (ts -> tm -> (tm -> a) -> CT ts tm a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT 0 tm
p tm -> a
v) CT ts tm a -> Stream (CT ts tm a) -> Stream (CT ts tm a)
forall e. e -> Stream e -> Stream e
:- Stream (CT ts tm a)
xs
(_ :- CT d :: ts
d _ _ :- _) -&- :: Stream (CT ts tm a) -> Stream (CT ts tm a) -> Stream (CT ts tm a)
-&- xs :: Stream (CT ts tm a)
xs
= (\(CT t :: ts
t p :: tm
p v :: tm -> a
v) -> ts -> tm -> (tm -> a) -> CT ts tm a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT (ts
t ts -> ts -> ts
forall a. Num a => a -> a -> a
+ ts
d) (tm
p tm -> tm -> tm
forall a. Num a => a -> a -> a
- ts -> tm
forall a b. (Real a, Fractional b) => a -> b
realToFrac ts
d) tm -> a
v) (CT ts tm a -> CT ts tm a)
-> Stream (CT ts tm a) -> Stream (CT ts tm a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Stream (CT ts tm a)
xs
(_ :- NullS) -&- _ = [Char] -> Stream (CT ts tm a)
forall a. HasCallStack => [Char] -> a
error "[MoC.CT] signal delayed to infinity"
instance (Num tm, Num ts, Ord ts, Eq ts) => Functor (CT tm ts) where
fmap :: (a -> b) -> CT tm ts a -> CT tm ts b
fmap f :: a -> b
f (CT t :: tm
t p :: ts
p g :: ts -> a
g) = tm -> ts -> (ts -> b) -> CT tm ts b
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT tm
t ts
p (a -> b
f (a -> b) -> (ts -> a) -> ts -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ts -> a
g)
instance (Num tm, Num ts, Ord ts, Ord tm, Eq ts) => Applicative (CT tm ts) where
pure :: a -> CT tm ts a
pure x :: a
x = tm -> ts -> (ts -> a) -> CT tm ts a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT 0 0 (\_ -> a
x)
(CT t :: tm
t p1 :: ts
p1 f :: ts -> a -> b
f) <*> :: CT tm ts (a -> b) -> CT tm ts a -> CT tm ts b
<*> (CT _ p2 :: ts
p2 g :: ts -> a
g) = tm -> ts -> (ts -> b) -> CT tm ts b
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT tm
t 0 (\x :: ts
x -> (ts -> a -> b
f (ts
xts -> ts -> ts
forall a. Num a => a -> a -> a
+ts
p1)) (ts -> a
g (ts
xts -> ts -> ts
forall a. Num a => a -> a -> a
+ts
p2)))
instance (Show a, Show ts, Real ts, Fractional tm) =>
Show (CT ts tm a) where
showsPrec :: Int -> CT ts tm a -> ShowS
showsPrec _ e :: CT ts tm a
e
= [Char] -> ShowS
forall a. [a] -> [a] -> [a]
(++) ( a -> [Char]
forall a. Show a => a -> [Char]
show (ts -> CT ts tm a -> a
forall p time timestamp p.
(Real p, Fractional time) =>
p -> CT timestamp time p -> p
evalTs (CT ts tm a -> ts
forall timestamp time a. CT timestamp time a -> timestamp
tag CT ts tm a
e) CT ts tm a
e) [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++
"@" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ ts -> [Char]
forall a. Show a => a -> [Char]
show (CT ts tm a -> ts
forall timestamp time a. CT timestamp time a -> timestamp
tag CT ts tm a
e) )
infixl 7 %>
(CT t :: timestamp
t _ _) %> :: CT timestamp time a -> CT timestamp time a -> CT timestamp time a
%> (CT _ p x) = timestamp -> time -> (time -> a) -> CT timestamp time a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT timestamp
t time
p time -> a
x
evalTm :: time -> CT timestamp time p -> p
evalTm t :: time
t (CT _ p :: time
p f :: time -> p
f) = time -> p
f (time
t time -> time -> time
forall a. Num a => a -> a -> a
+ time
p)
evalTs :: p -> CT timestamp time p -> p
evalTs t :: p
t (CT _ p :: time
p f :: time -> p
f) = time -> p
f ((p -> time
forall a b. (Real a, Fractional b) => a -> b
realToFrac p
t) time -> time -> time
forall a. Num a => a -> a -> a
+ time
p)
evalEv :: CT timestamp time p -> p
evalEv (CT t :: timestamp
t p :: time
p f :: time -> p
f) = time -> p
f ((timestamp -> time
forall a b. (Real a, Fractional b) => a -> b
realToFrac timestamp
t) time -> time -> time
forall a. Num a => a -> a -> a
+ time
p)
unit :: (Num ts, Num tm, Ord ts)
=> (ts, tm -> a) -> SignalBase ts tm a
unit2 :: (Num ts, Num tm, Ord ts)
=> ((ts, tm -> a1),(ts, tm -> a2))
-> (SignalBase ts tm a1, SignalBase ts tm a2)
unit3 :: (Num ts, Num tm, Ord ts)
=> ((ts, tm -> a1),(ts, tm -> a2),(ts, tm -> a3))
-> (SignalBase ts tm a1, SignalBase ts tm a2, SignalBase ts tm a3)
unit4 :: (Num ts, Num tm, Ord ts)
=> ((ts, tm -> a1),(ts, tm -> a2),(ts, tm -> a3),(ts, tm -> a4))
-> (SignalBase ts tm a1, SignalBase ts tm a2, SignalBase ts tm a3
,SignalBase ts tm a4)
unit :: (ts, tm -> a) -> SignalBase ts tm a
unit (t :: ts
t,f :: tm -> a
f) = (ts -> tm -> (tm -> a) -> CT ts tm a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT 0 0 tm -> a
f CT ts tm a -> SignalBase ts tm a -> SignalBase ts tm a
forall e. e -> Stream e -> Stream e
:- ts -> tm -> (tm -> a) -> CT ts tm a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT ts
t 0 tm -> a
f CT ts tm a -> SignalBase ts tm a -> SignalBase ts tm a
forall e. e -> Stream e -> Stream e
:- SignalBase ts tm a
forall e. Stream e
NullS)
unit2 :: ((ts, tm -> a1), (ts, tm -> a2))
-> (SignalBase ts tm a1, SignalBase ts tm a2)
unit2 = ((ts, tm -> a1) -> SignalBase ts tm a1,
(ts, tm -> a2) -> SignalBase ts tm a2)
-> ((ts, tm -> a1), (ts, tm -> a2))
-> (SignalBase ts tm a1, SignalBase ts tm a2)
forall a1 b1 a2 b2. (a1 -> b1, a2 -> b2) -> (a1, a2) -> (b1, b2)
($$) ((ts, tm -> a1) -> SignalBase ts tm a1
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit,(ts, tm -> a2) -> SignalBase ts tm a2
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit)
unit3 :: ((ts, tm -> a1), (ts, tm -> a2), (ts, tm -> a3))
-> (SignalBase ts tm a1, SignalBase ts tm a2, SignalBase ts tm a3)
unit3 = ((ts, tm -> a1) -> SignalBase ts tm a1,
(ts, tm -> a2) -> SignalBase ts tm a2,
(ts, tm -> a3) -> SignalBase ts tm a3)
-> ((ts, tm -> a1), (ts, tm -> a2), (ts, tm -> a3))
-> (SignalBase ts tm a1, SignalBase ts tm a2, SignalBase ts tm a3)
forall t1 a t2 b t3 c.
(t1 -> a, t2 -> b, t3 -> c) -> (t1, t2, t3) -> (a, b, c)
($$$) ((ts, tm -> a1) -> SignalBase ts tm a1
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit,(ts, tm -> a2) -> SignalBase ts tm a2
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit,(ts, tm -> a3) -> SignalBase ts tm a3
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit)
unit4 :: ((ts, tm -> a1), (ts, tm -> a2), (ts, tm -> a3), (ts, tm -> a4))
-> (SignalBase ts tm a1, SignalBase ts tm a2, SignalBase ts tm a3,
SignalBase ts tm a4)
unit4 = ((ts, tm -> a1) -> SignalBase ts tm a1,
(ts, tm -> a2) -> SignalBase ts tm a2,
(ts, tm -> a3) -> SignalBase ts tm a3,
(ts, tm -> a4) -> SignalBase ts tm a4)
-> ((ts, tm -> a1), (ts, tm -> a2), (ts, tm -> a3), (ts, tm -> a4))
-> (SignalBase ts tm a1, SignalBase ts tm a2, SignalBase ts tm a3,
SignalBase ts tm a4)
forall t1 a t2 b t3 c t4 d.
(t1 -> a, t2 -> b, t3 -> c, t4 -> d)
-> (t1, t2, t3, t4) -> (a, b, c, d)
($$$$) ((ts, tm -> a1) -> SignalBase ts tm a1
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit,(ts, tm -> a2) -> SignalBase ts tm a2
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit,(ts, tm -> a3) -> SignalBase ts tm a3
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit,(ts, tm -> a4) -> SignalBase ts tm a4
forall ts tm a.
(Num ts, Num tm, Ord ts) =>
(ts, tm -> a) -> SignalBase ts tm a
unit)
infinite :: (Num ts, Num tm, Ord ts)
=> (tm -> a) -> SignalBase ts tm a
infinite :: (tm -> a) -> SignalBase ts tm a
infinite f :: tm -> a
f = ts -> tm -> (tm -> a) -> CT ts tm a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT 0 0 tm -> a
f CT ts tm a -> SignalBase ts tm a -> SignalBase ts tm a
forall e. e -> Stream e -> Stream e
:- SignalBase ts tm a
forall e. Stream e
NullS
signal :: (Num ts, Num tm, Ord ts)
=> [(ts, tm -> a)] -> SignalBase ts tm a
signal :: [(ts, tm -> a)] -> SignalBase ts tm a
signal = SignalBase ts tm a -> SignalBase ts tm a
forall timestamp time a.
(Num timestamp, Ord timestamp) =>
Stream (CT timestamp time a) -> Stream (CT timestamp time a)
checkSignal (SignalBase ts tm a -> SignalBase ts tm a)
-> ([(ts, tm -> a)] -> SignalBase ts tm a)
-> [(ts, tm -> a)]
-> SignalBase ts tm a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CT ts tm a] -> SignalBase ts tm a
forall a. [a] -> Stream a
stream ([CT ts tm a] -> SignalBase ts tm a)
-> ([(ts, tm -> a)] -> [CT ts tm a])
-> [(ts, tm -> a)]
-> SignalBase ts tm a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ts, tm -> a) -> CT ts tm a) -> [(ts, tm -> a)] -> [CT ts tm a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(t :: ts
t, f :: tm -> a
f) -> ts -> tm -> (tm -> a) -> CT ts tm a
forall time timestamp a.
(Num time, Num timestamp, Ord timestamp, Eq timestamp) =>
timestamp -> time -> (time -> a) -> CT timestamp time a
CT ts
t 0 tm -> a
f)
checkSignal :: Stream (CT timestamp time a) -> Stream (CT timestamp time a)
checkSignal NullS = Stream (CT timestamp time a)
forall e. Stream e
NullS
checkSignal s :: Stream (CT timestamp time a)
s@(x :: CT timestamp time a
x:-_)
| CT timestamp time a -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time a
x timestamp -> timestamp -> Bool
forall a. Eq a => a -> a -> Bool
== 0 = Stream (CT timestamp time a) -> Stream (CT timestamp time a)
forall timestamp time a.
Ord timestamp =>
Stream (CT timestamp time a) -> Stream (CT timestamp time a)
checkOrder Stream (CT timestamp time a)
s
| Bool
otherwise = [Char] -> Stream (CT timestamp time a)
forall a. HasCallStack => [Char] -> a
error "[MoC.CT] signal does not tag from global 0"
where
checkOrder :: Stream (CT timestamp time a) -> Stream (CT timestamp time a)
checkOrder NullS = Stream (CT timestamp time a)
forall e. Stream e
NullS
checkOrder (x :: CT timestamp time a
x:-NullS) = (CT timestamp time a
xCT timestamp time a
-> Stream (CT timestamp time a) -> Stream (CT timestamp time a)
forall e. e -> Stream e -> Stream e
:-Stream (CT timestamp time a)
forall e. Stream e
NullS)
checkOrder (x :: CT timestamp time a
x:-y :: CT timestamp time a
y:-xs :: Stream (CT timestamp time a)
xs)
| CT timestamp time a -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time a
x timestamp -> timestamp -> Bool
forall a. Ord a => a -> a -> Bool
< CT timestamp time a -> timestamp
forall timestamp time a. CT timestamp time a -> timestamp
tag CT timestamp time a
y = CT timestamp time a
x CT timestamp time a
-> Stream (CT timestamp time a) -> Stream (CT timestamp time a)
forall e. e -> Stream e -> Stream e
:-Stream (CT timestamp time a) -> Stream (CT timestamp time a)
checkOrder (CT timestamp time a
yCT timestamp time a
-> Stream (CT timestamp time a) -> Stream (CT timestamp time a)
forall e. e -> Stream e -> Stream e
:-Stream (CT timestamp time a)
xs)
| Bool
otherwise = [Char] -> Stream (CT timestamp time a)
forall a. HasCallStack => [Char] -> a
error "[MoC.CT] malformed signal"