Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Combinators to create Rhine
s (main programs) from basic components
such as ClSF
s, clocks, ResamplingBuffer
s and Schedule
s.
The combinator names are often mixed of the symbols ,
* and
>@,
and several other symbols.
The general mnemonic for combinator names is:
- @ annotates a data processing unit such as a signal function, network or buffer with temporal information like a clock or a schedule.
*
composes parallely.>
composes sequentially.
Synopsis
- (@@) :: (cl ~ In cl, cl ~ Out cl) => ClSF m cl a b -> cl -> Rhine m cl a b
- data ResamplingPoint m cla clb a b = ResamplingPoint (ResamplingBuffer m (Out cla) (In clb) a b) (Schedule m cla clb)
- (-@-) :: ResamplingBuffer m (Out cl1) (In cl2) a b -> Schedule m cl1 cl2 -> ResamplingPoint m cl1 cl2 a b
- data RhineAndResamplingPoint m cl1 cl2 a c = forall b. RhineAndResamplingPoint (Rhine m cl1 a b) (ResamplingPoint m cl1 cl2 b c)
- (>--) :: Rhine m cl1 a b -> ResamplingPoint m cl1 cl2 b c -> RhineAndResamplingPoint m cl1 cl2 a c
- (-->) :: (Clock m cl1, Clock m cl2, Time cl1 ~ Time cl2, Time (Out cl1) ~ Time cl1, Time (In cl2) ~ Time cl2, Clock m (Out cl1), Clock m (Out cl2), Clock m (In cl1), Clock m (In cl2), GetClockProxy cl1, GetClockProxy cl2) => RhineAndResamplingPoint m cl1 cl2 a b -> Rhine m cl2 b c -> Rhine m (SequentialClock m cl1 cl2) a c
- data RhineParallelAndSchedule m clL clR a b = RhineParallelAndSchedule (Rhine m clL a b) (Schedule m clL clR)
- (++@) :: Rhine m clL a b -> Schedule m clL clR -> RhineParallelAndSchedule m 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 (Out clL), Time clR ~ Time (Out clR), Time clL ~ Time (In clL), Time clR ~ Time (In clR), Time clL ~ Time clR) => RhineParallelAndSchedule m clL clR a b -> Rhine m clR a c -> Rhine m (ParallelClock m clL clR) a (Either b c)
- (||@) :: Rhine m clL a b -> Schedule m clL clR -> RhineParallelAndSchedule m 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 (Out clL), Time clR ~ Time (Out clR), Time clL ~ Time (In clL), Time clR ~ Time (In clR), Time clL ~ Time clR) => RhineParallelAndSchedule m clL clR a b -> Rhine m clR a b -> Rhine m (ParallelClock m clL clR) a b
- (@>>^) :: Monad m => Rhine m cl a b -> (b -> c) -> Rhine m cl a c
- (^>>@) :: Monad m => (a -> b) -> Rhine m cl b c -> Rhine m cl a c
- (@>-^) :: (Clock m (Out cl), Time cl ~ Time (Out cl)) => Rhine m cl a b -> ClSF m (Out cl) b c -> Rhine m cl a c
- (^->@) :: (Clock m (In cl), Time cl ~ Time (In cl)) => ClSF m (In cl) a b -> Rhine m cl b c -> Rhine m cl a c
Combinators and syntactic sugar for high-level composition of signal networks.
(@@) :: (cl ~ In cl, cl ~ Out cl) => ClSF m cl a b -> cl -> Rhine m cl a b infix 5 Source #
Create a synchronous Rhine
by combining a clocked signal function with a matching clock.
Synchronicity is ensured by requiring that data enters (In cl
)
and leaves (Out cl
) the system at the same as it is processed (cl
).
data ResamplingPoint m cla clb a b Source #
A point at which sequential asynchronous composition ("resampling") of signal networks can happen.
ResamplingPoint (ResamplingBuffer m (Out cla) (In clb) a b) (Schedule m cla clb) |
(-@-) :: ResamplingBuffer m (Out cl1) (In cl2) a b -> Schedule m cl1 cl2 -> ResamplingPoint m cl1 cl2 a b infix 8 Source #
Syntactic sugar for ResamplingPoint
.
data RhineAndResamplingPoint m cl1 cl2 a c Source #
A purely syntactical convenience construction enabling quadruple syntax for sequential composition, as described below.
forall b. RhineAndResamplingPoint (Rhine m cl1 a b) (ResamplingPoint m cl1 cl2 b c) |
(>--) :: Rhine m cl1 a b -> ResamplingPoint m cl1 cl2 b c -> RhineAndResamplingPoint m cl1 cl2 a c infix 2 Source #
Syntactic sugar for RhineAndResamplingPoint
.
(-->) :: (Clock m cl1, Clock m cl2, Time cl1 ~ Time cl2, Time (Out cl1) ~ Time cl1, Time (In cl2) ~ Time cl2, Clock m (Out cl1), Clock m (Out cl2), Clock m (In cl1), Clock m (In cl2), GetClockProxy cl1, GetClockProxy cl2) => RhineAndResamplingPoint m cl1 cl2 a b -> Rhine m cl2 b c -> Rhine m (SequentialClock m cl1 cl2) a c infixr 1 Source #
The combinators for sequential composition allow for the following syntax:
rh1 :: Rhine m cl1 a b rh1 = ... rh2 :: Rhine m cl2 c d rh2 = ... rb :: ResamplingBuffer m (Out cl1) (In cl2) b c rb = ... sched :: Schedule m cl1 cl2 sched = ... rh :: Rhine m (SequentialClock m cl1 cl2) a d rh = rh1 >-- rb -@- sched --> rh2
data RhineParallelAndSchedule m clL clR a b Source #
A purely syntactical convenience construction allowing for ternary syntax for parallel composition, described below.
RhineParallelAndSchedule (Rhine m clL a b) (Schedule m clL clR) |
(++@) :: Rhine m clL a b -> Schedule m clL clR -> RhineParallelAndSchedule m clL clR a b infix 4 Source #
Syntactic sugar for RhineParallelAndSchedule
.
(@++) :: (Monad m, Clock m clL, Clock m clR, Clock m (Out clL), Clock m (Out clR), GetClockProxy clL, GetClockProxy clR, Time clL ~ Time (Out clL), Time clR ~ Time (Out clR), Time clL ~ Time (In clL), Time clR ~ Time (In clR), Time clL ~ Time clR) => RhineParallelAndSchedule m clL clR a b -> Rhine m clR a c -> Rhine m (ParallelClock m clL clR) a (Either b c) infix 3 Source #
The combinators for parallel composition allow for the following syntax:
rh1 :: Rhine m clL a b rh1 = ... rh2 :: Rhine m clR a c rh2 = ... sched :: Schedule m clL clR sched = ... rh :: Rhine m (ParallelClock clL clR) a (Either b c) rh = rh1 ++@ sched @++ rh2
(||@) :: Rhine m clL a b -> Schedule m clL clR -> RhineParallelAndSchedule m clL clR a b infix 4 Source #
Further syntactic sugar for RhineParallelAndSchedule
.
(@||) :: (Monad m, Clock m clL, Clock m clR, Clock m (Out clL), Clock m (Out clR), GetClockProxy clL, GetClockProxy clR, Time clL ~ Time (Out clL), Time clR ~ Time (Out clR), Time clL ~ Time (In clL), Time clR ~ Time (In clR), Time clL ~ Time clR) => RhineParallelAndSchedule m clL clR a b -> Rhine m clR a b -> Rhine m (ParallelClock m clL clR) a b infix 3 Source #
The combinators for parallel composition allow for the following syntax:
rh1 :: Rhine m clL a b rh1 = ... rh2 :: Rhine m clR a b rh2 = ... sched :: Schedule m clL clR sched = ... rh :: Rhine m (ParallelClock clL clR) a b rh = rh1 ||@ sched @|| rh2
(@>>^) :: Monad m => Rhine m cl a b -> (b -> c) -> Rhine m cl a c Source #
Postcompose a Rhine
with a pure function.
(^>>@) :: Monad m => (a -> b) -> Rhine m cl b c -> Rhine m cl a c Source #
Precompose a Rhine
with a pure function.