Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains internals needed for the reactimation of signal functions. None of it should be relevant for a typical user of this library.
Synopsis
- data Tickable m cla clb cl clc cld a b c d = Tickable {
- buffer1 :: ResamplingBuffer m cla clb a b
- ticksn :: SN m cl b c
- buffer2 :: ResamplingBuffer m clc cld c d
- parClockIn :: ParClockInclusion (In cl) clb
- parClockOut :: ParClockInclusion (Out cl) clc
- lastTime :: LastTime cl
- initTime :: Time cl
- initLastTime :: SN m cl a b -> Time cl -> LastTime cl
- createTickable :: ResamplingBuffer m cla (In cl) a b -> SN m cl b c -> ResamplingBuffer m (Out cl) cld c d -> Time cl -> Tickable m cla (In cl) cl (Out cl) cld a b c d
- tick :: (Monad m, Clock m cl, Time cla ~ Time cl, Time clb ~ Time cl, Time clc ~ Time cl, Time cld ~ Time cl, Time (In cl) ~ Time cl, Time (Out cl) ~ Time cl) => Tickable m cla clb cl clc cld a b c d -> Time cl -> Tag cl -> m (Tickable m cla clb cl clc cld a b c d)
- trivialResamplingBuffer :: Monad m => cl -> ResamplingBuffer m (Out cl) (In cl) () ()
Documentation
data Tickable m cla clb cl clc cld a b c d Source #
A signal network (SN
) enclosed by matching ResamplingBuffer
s and further auxiliary data,
such that it can be stepped with each arriving tick from a clock cl
.
They play a similar role like ReactHandle
s in dunai.
The type parameters:
m
: The monad in which theSN
and theResamplingBuffer
s produce side effectscla
: The (irrelevant) input clock of the leftResamplingBuffer
clb
: The clock at which the leftResamplingBuffer
produces outputcl
: The clock at which theSN
ticksclc
: The clock at which the rightResamplingBuffer
accepts inputcld
: The (irrelevant) output clock of the rightResamplingBuffer
a
: The (irrelevant) input type of the leftResamplingBuffer
b
: The input type of theSN
c
: The output type of theSN
d
: The (irrelevant) output type of the rightResamplingBuffer
Tickable | |
|
initLastTime :: SN m cl a b -> Time cl -> LastTime cl Source #
Initialise the tree of last tick times.
createTickable :: ResamplingBuffer m cla (In cl) a b -> SN m cl b c -> ResamplingBuffer m (Out cl) cld c d -> Time cl -> Tickable m cla (In cl) cl (Out cl) cld a b c d Source #
Initialise a Tickable
from a signal network,
two matching enclosing resampling buffers and an initial time.
:: (Monad m, Clock m cl, Time cla ~ Time cl, Time clb ~ Time cl, Time clc ~ Time cl, Time cld ~ Time cl, Time (In cl) ~ Time cl, Time (Out cl) ~ Time cl) | |
=> Tickable m cla clb cl clc cld a b c d | |
-> Time cl | Timestamp of the present tick |
-> Tag cl |
|
-> m (Tickable m cla clb cl clc cld a b c d) |
In this function, one tick, or step of an asynchronous signal network happens.
The TimeInfo
holds the information which part of the signal tree will tick.
This information is encoded in the Tag
of the TimeInfo
,
which is of type 'Either tag1 tag2' in case of a SequentialClock
or a ParallelClock
,
encoding either a tick for the left clock or the right clock.
trivialResamplingBuffer :: Monad m => cl -> ResamplingBuffer m (Out cl) (In cl) () () Source #
A ResamplingBuffer
producing only units.
(Slightly more efficient and direct implementation than the one in Timeless
that additionally unifies the clock types in a way needed for the tick implementation.)