Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Tickable m cla clb cl clc cld a b c d = Tickable {
- buffer1 :: ResamplingBuffer m cla clb a b
- ticksf :: SF m cl b c
- buffer2 :: ResamplingBuffer m clc cld c d
- parClockInL :: ParClockInclusion (Leftmost cl) clb
- parClockInR :: ParClockInclusion (Rightmost cl) clc
- lastTime :: LastTime cl
- initTime :: TimeDomainOf cl
- initLastTime :: SF m cl a b -> TimeDomainOf cl -> LastTime cl
- createTickable :: ResamplingBuffer m cla (Leftmost cl) a b -> SF m cl b c -> ResamplingBuffer m (Rightmost cl) cld c d -> TimeDomainOf cl -> Tickable m cla (Leftmost cl) cl (Rightmost cl) cld a b c d
- tick :: (Monad m, Clock m cl, TimeDomainOf cla ~ TimeDomainOf cl, TimeDomainOf clb ~ TimeDomainOf cl, TimeDomainOf clc ~ TimeDomainOf cl, TimeDomainOf cld ~ TimeDomainOf cl, TimeDomainOf (Leftmost cl) ~ TimeDomainOf cl, TimeDomainOf (Rightmost cl) ~ TimeDomainOf cl) => Tickable m cla clb cl clc cld a b c d -> TimeDomainOf cl -> Tag cl -> m (Tickable m cla clb cl clc cld a b c d)
- trivialResamplingBuffer :: Monad m => cl -> ResamplingBuffer m (Rightmost cl) (Leftmost cl) () ()
Documentation
data Tickable m cla clb cl clc cld a b c d Source #
A signal function (SF
) 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 theSF
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 theSF
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 theSF
c
: The output type of theSF
d
: The (irrelevant) output type of the rightResamplingBuffer
Tickable | |
|
initLastTime :: SF m cl a b -> TimeDomainOf cl -> LastTime cl Source #
Initialise the tree of last tick times.
createTickable :: ResamplingBuffer m cla (Leftmost cl) a b -> SF m cl b c -> ResamplingBuffer m (Rightmost cl) cld c d -> TimeDomainOf cl -> Tickable m cla (Leftmost cl) cl (Rightmost cl) cld a b c d Source #
Initialise a Tickable
from a signal function,
two matching enclosing resampling buffers and an initial time.
:: (Monad m, Clock m cl, TimeDomainOf cla ~ TimeDomainOf cl, TimeDomainOf clb ~ TimeDomainOf cl, TimeDomainOf clc ~ TimeDomainOf cl, TimeDomainOf cld ~ TimeDomainOf cl, TimeDomainOf (Leftmost cl) ~ TimeDomainOf cl, TimeDomainOf (Rightmost cl) ~ TimeDomainOf cl) | |
=> Tickable m cla clb cl clc cld a b c d | |
-> TimeDomainOf 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 function 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 (Rightmost cl) (Leftmost 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.)