Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Combinators for composing signal networks sequentially and parallely.
Synopsis
- (>>>^) :: Monad m => SN m cl a b -> (b -> c) -> SN m cl a c
- (^>>>) :: Monad m => (a -> b) -> SN m cl b c -> SN m cl a c
- (>--^) :: (Clock m (Out cl), Time cl ~ Time (Out cl)) => SN m cl a b -> ClSF m (Out cl) b c -> SN m cl a c
- (^-->) :: (Clock m (In cl), Time cl ~ Time (In cl)) => ClSF m (In cl) a b -> SN m cl b c -> SN m cl a c
- (****) :: Monad m => SN m cl a b -> SN m cl c d -> SN m cl (a, c) (b, d)
- (||||) :: (Monad m, Clock m clL, Clock m clR, Clock m (Out clL), Clock m (Out clR), GetClockProxy clL, GetClockProxy clR, Time clL ~ Time clR, Time clL ~ Time (Out clL), Time clL ~ Time (In clL), Time clR ~ Time (Out clR), Time clR ~ Time (In clR)) => SN m clL a b -> SN m clR a b -> SN m (ParClock clL clR) a b
- (++++) :: (Monad m, Clock m clL, Clock m clR, Clock m (Out clL), Clock m (Out clR), GetClockProxy clL, GetClockProxy clR, Time clL ~ Time clR, Time clL ~ Time (Out clL), Time clL ~ Time (In clL), Time clR ~ Time (Out clR), Time clR ~ Time (In clR)) => SN m clL a b -> SN m clR a c -> SN m (ParClock clL clR) a (Either b c)
Documentation
(>>>^) :: Monad m => SN m cl a b -> (b -> c) -> SN m cl a c Source #
Postcompose a signal network with a pure function.
(^>>>) :: Monad m => (a -> b) -> SN m cl b c -> SN m cl a c Source #
Precompose a signal network with a pure function.
(>--^) :: (Clock m (Out cl), Time cl ~ Time (Out cl)) => SN m cl a b -> ClSF m (Out cl) b c -> SN m cl a c Source #
Postcompose a signal network with a ClSF
.
(^-->) :: (Clock m (In cl), Time cl ~ Time (In cl)) => ClSF m (In cl) a b -> SN m cl b c -> SN m cl a c Source #
Precompose a signal network with a ClSF
.
(****) :: Monad m => SN m cl a b -> SN m cl c d -> SN m cl (a, c) (b, d) Source #
Compose two signal networks on the same clock in data-parallel.
At one tick of cl
, both networks are stepped.
(||||) :: (Monad m, Clock m clL, Clock m clR, Clock m (Out clL), Clock m (Out clR), GetClockProxy clL, GetClockProxy clR, Time clL ~ Time clR, Time clL ~ Time (Out clL), Time clL ~ Time (In clL), Time clR ~ Time (Out clR), Time clR ~ Time (In clR)) => SN m clL a b -> SN m clR a b -> SN m (ParClock clL clR) a b Source #
Compose two signal networks on different clocks in clock-parallel.
At one tick of ParClock cl1 cl2
, one of the networks is stepped,
dependent on which constituent clock has ticked.
Note: This is essentially an infix synonym of Parallel
(++++) :: (Monad m, Clock m clL, Clock m clR, Clock m (Out clL), Clock m (Out clR), GetClockProxy clL, GetClockProxy clR, Time clL ~ Time clR, Time clL ~ Time (Out clL), Time clL ~ Time (In clL), Time clR ~ Time (Out clR), Time clR ~ Time (In clR)) => SN m clL a b -> SN m clR a c -> SN m (ParClock clL clR) a (Either b c) Source #
Compose two signal networks on different clocks in clock-parallel.
At one tick of ParClock cl1 cl2
, one of the networks is stepped,
dependent on which constituent clock has ticked.