|
|
|
|
|
Description |
Functional events and reactive values. An Event is stream of
future values in time order. A Reactive value is a discretly
time-varying value. These two types are closely linked: a reactive
value is defined by an initial value and an event that yields future
values; while an event is simply a future reactive value.
Many of the operations on events and reactive values are packaged as
instances of the standard type classes Monoid, Functor,
Applicative, and Monad.
Although the basic Reactive type describes discretely-changing
values, continuously-changing values are modeled simply as reactive
functions. For convenience, this module defines ReactiveB as a type
composition of Reactive and a constant-optimized representation of
functions of time.
The exact packaging of discrete vs continuous will probably change with
more experience.
|
|
Synopsis |
|
|
|
|
Events and reactive values
|
|
|
Event, i.e., a stream of future values. Instances:
- Monoid: mempty is the event that never occurs, and e mappend
e' is the event that combines occurrences from e and e'. (Fran's
neverE and (.|.).)
- Functor: fmap f e is the event that occurs whenever e occurs,
and whose occurrence values come from applying f to the values from
e. (Fran's (==>).)
- Applicative: pure a is an event with a single occurrence,
available from the beginning of time. ef <*> ex is an event whose
occurrences are made from the product of the occurrences of ef and
ex. For every occurrence f at time tf of ef and occurrence x
at time tx of ex, ef <*> ex has an occurrence f x at time max
tf tx.
- Monad: return a is the same as pure a (as always). In e >>=
f, each occurrence of e leads, through f, to a new event.
Similarly for join ee, which is somehow simpler for me to think
about. The occurrences of e >>= f (or join ee) correspond to the
union of the occurrences of all such events. For example, suppose
we're playing Asteroids and tracking collisions. Each collision can
break an asteroid into more of them, each of which has to be tracked
for more collisions. Another example: A chat room has an enter
event, whose occurrences contain new events like speak.
| Constructors | | Instances | |
|
|
|
Reactive value: a discretely changing value. Reactive values can be
understood in terms of (a) a simple denotational semantics of reactive
values as functions of time, and (b) the corresponding instances for
functions. The semantics is given by the function (%$) :: Reactive a
-> (Time -> a). A reactive value also has a current value and an
event (stream of future values).
Instances for Reactive
- Monoid: a typical lifted monoid. If o is a monoid, then
Reactive o is a monoid, with mempty = pure mempty, and mappend =
liftA2 mappend. In other words, mempty %$ t == mempty, and (r
mappend s) %$ t == (r %$ t) mappend (s %$ t).
- Functor: fmap f r %$ t == f (r %$ t).
- Applicative: pure a %$ t == a, and (s <*> r) %$ t ==
(s %$ t) (r %$ t).
- Monad: return a %$ t == a, and join rr %$ t == (rr %$ t)
%$ t. As always, (r >>= f) == join (fmap f r).
| Constructors | Stepper | | rInit :: a | initial value
| rEvent :: Event a | waiting for event
|
|
| Instances | |
|
|
|
Compatibility synonym (for ease of transition from DataDriven)
|
|
|
Apply a unary function inside an Event representation.
|
|
|
Apply a unary function inside an Event representation.
|
|
|
Reactive value from an initial value and a new-value event.
|
|
|
Switch between reactive values.
|
|
|
Make an event and a sink for feeding the event. Each value sent to
the sink becomes an occurrence of the event.
|
|
|
Tracing variant of mkEvent
|
|
|
Show specialization of mkEventTrace
|
|
|
Run an event in the current thread.
|
|
|
Run an event in a new thread.
|
|
|
Subscribe a listener to an event. Wrapper around forkE and fmap.
|
|
|
Run a reactive value in a new thread. The initial action happens in
the current thread.
|
|
Event extras
|
|
|
Accumulating event, starting from an initial value and a
update-function event.
|
|
|
Like scanl for events
|
|
|
Accumulate values from a monoid-valued event. Specialization of
scanlE, using mappend and mempty
|
|
|
Pair each event value with the previous one, given an initial value.
|
|
|
Count occurrences of an event, remembering the occurrence values.
See also countE_
|
|
|
Count occurrences of an event, forgetting the occurrence values. See
also countE.
|
|
|
Difference of successive event occurrences.
|
|
|
Snapshot a reactive value whenever an event occurs.
|
|
|
Like snapshot but discarding event data (often a is ()).
|
|
|
Filter an event according to whether a boolean source is true.
|
|
|
Just the first occurrence of an event.
|
|
|
Tracing of events.
|
|
|
Make an extensible event. The returned sink is a way to add new
events to mix.
|
|
Reactive extras
|
|
|
|
|
Reactive value from an initial value and an updater event
|
|
|
Like scanl for reactive values
|
|
|
Accumulate values from a monoid-valued event. Specialization of
scanlE, using mappend and mempty
|
|
|
Start out blank (Nothing), latching onto each new a, and blanking
on each b. If you just want to latch and not blank, then use
mempty for lose.
|
|
|
Flip-flopping source. Turns true when ea occurs and false when
eb occurs.
|
|
|
Count occurrences of an event
|
|
Reactive behaviors
|
|
|
Time for continuous behaviors
|
|
|
Reactive behaviors. Simply a reactive Function value. Wrapped in
a type composition to get Functor and Applicative for free.
|
|
To be moved elsewhere
|
|
|
Replace a functor value with a given one.
|
|
|
Forget a functor value, replace with ()
|
|
|
Convenient alias for dropping parentheses.
|
|
|
Value sink
|
|
|
Pass through Just occurrences.
|
|
|
Pass through values satisfying p.
|
|
Produced by Haddock version 2.3.0 |