|
FRP.Reactive | Stability | experimental | Maintainer | conal@conal.net |
|
|
|
|
|
Description |
A library for programming with functional reactive behaviors.
|
|
Synopsis |
|
type TimeT = Double | | type ITime = Improving TimeT | | data EventG t a | | type Event = EventG ITime | | accumE :: a -> EventG t (a -> a) -> EventG t a | | withTimeE :: Ord t => EventG (Improving t) d -> EventG (Improving t) (d, t) | | withTimeE_ :: Ord t => EventG (Improving t) d -> EventG (Improving t) t | | zipE :: Ord t => (c, d) -> (EventG t c, EventG t d) -> EventG t (c, d) | | scanlE :: Ord t => (a -> b -> a) -> a -> EventG t b -> EventG t a | | monoidE :: (Ord t, Monoid o) => EventG t o -> EventG t o | | mealy :: Ord t => s -> (s -> s) -> EventG t b -> EventG t (b, s) | | mealy_ :: Ord t => s -> (s -> s) -> EventG t b -> EventG t s | | countE :: (Ord t, Num n) => EventG t b -> EventG t (b, n) | | countE_ :: (Ord t, Num n) => EventG t b -> EventG t n | | diffE :: (Ord t, Num n) => EventG t n -> EventG t n | | withPrevE :: Ord t => EventG t a -> EventG t (a, a) | | withPrevEWith :: Ord t => (a -> a -> b) -> EventG t a -> EventG t b | | eitherE :: Ord t => EventG t a -> EventG t b -> EventG t (Either a b) | | listE :: [(TimeT, a)] -> Event a | | atTimes :: [TimeT] -> Event () | | atTime :: TimeT -> Event () | | once :: Ord t => EventG t a -> EventG t a | | firstRestE :: Ord t => EventG t a -> (a, EventG t a) | | firstE :: Ord t => EventG t a -> a | | restE :: Ord t => EventG t a -> EventG t a | | snapRemainderE :: Ord t => EventG t b -> EventG t a -> EventG t (a, EventG t b) | | withRestE :: EventG t a -> EventG t (a, EventG t a) | | untilE :: Ord t => EventG t a -> EventG t b -> EventG t a | | splitE :: Ord t => EventG t b -> EventG t a -> EventG t (a, EventG t b) | | switchE :: Ord t => EventG t (EventG t a) -> EventG t a | | justE :: Ord t => EventG t (Maybe a) -> EventG t a | | filterE :: (Ord t, Show a) => (a -> Bool) -> EventG t a -> EventG t a | | joinMaybes :: MonadPlus m => m (Maybe a) -> m a | | filterMP :: MonadPlus m => (a -> Bool) -> m a -> m a | | data BehaviorG tr tf a | | type Behavior = BehaviorI TimeT | | type Behaviour = Behavior | | time :: Ord t => BehaviorI t t | | stepper :: a -> EventI t a -> BehaviorI t a | | switcher :: Ord tr => BehaviorG tr tf a -> EventG tr (BehaviorG tr tf a) -> BehaviorG tr tf a | | snapshotWith :: Ord t => (a -> b -> c) -> BehaviorI t b -> EventI t a -> EventI t c | | snapshot :: Ord t => BehaviorI t b -> EventI t a -> EventI t (a, b) | | snapshot_ :: Ord t => BehaviorI t b -> EventI t a -> EventI t b | | whenE :: Ord t => BehaviorI t Bool -> EventI t a -> EventI t a | | accumB :: a -> EventI t (a -> a) -> BehaviorI t a | | scanlB :: forall a b tr tf. Ord tr => (b -> BehaviorG tr tf a -> BehaviorG tr tf a) -> BehaviorG tr tf a -> EventG tr b -> BehaviorG tr tf a | | monoidB :: (Ord tr, Monoid a) => EventG tr (BehaviorG tr tf a) -> BehaviorG tr tf a | | maybeB :: Ord t => EventI t a -> EventI t b -> BehaviorI t (Maybe a) | | flipFlop :: Ord t => EventI t a -> EventI t b -> BehaviorI t Bool | | countB :: (Ord t, Num n) => EventI t a -> BehaviorI t n | | sumB :: (Ord t, AdditiveGroup a) => EventI t a -> BehaviorI t a | | integral :: (Scalar v ~ t, Ord t, VectorSpace v, Num t) => EventI t a -> BehaviorI t v -> BehaviorI t v |
|
|
|
Events
|
|
|
The type of finite time values.
|
|
|
Improving doubles, as used for time values in Event, Reactive,
and ReactiveB.
|
|
|
Events. Semantically: time-ordered list 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'.
- 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.
- Applicative: pure a is an event with a single occurrence at time
-Infinity. 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 tf max tx. N.B.: I
don't expect this instance to be very useful. If ef has nf
instances and ex has nx instances, then ef <*> ex has nf*nx
instances. However, there are only nf+nx possibilities for tf
max tx, so many of the occurrences are simultaneous. If you think
you want to use this instance, consider using Reactive instead.
- Monad: return a is the same as pure a (as usual). 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 (temporal interleaving) 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. An especially useful
monad-based function is joinMaybes, which filters a Maybe-valued
event.
| Instances | |
|
|
|
Events, specialized to improving doubles for time
|
|
|
Accumulating event, starting from an initial value and a
update-function event. See also accumR.
|
|
|
Access occurrence times in an event. See withTimeGE for more
general notions of time.
withTimeE :: Event a -> Event (a, TimeT)
|
|
|
Access occurrence times in an event. Discard the rest. See also
withTimeE.
withTimeE_ :: Event a -> Event TimeT
|
|
|
Generate a pair-valued event, given a pair of initial values and a
pair of events. See also pair on Reactive. Not quite a zip,
because of the initial pair required.
|
|
|
Like scanl for events.
|
|
|
Accumulate values from a monoid-typed event. Specialization of
scanlE, using mappend and mempty.
|
|
|
Mealy-style state machine, given initial value and transition
function. Carries along event data. See also mealy_.
|
|
|
Mealy-style state machine, given initial value and transition
function. Forgetful version of mealy.
|
|
|
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. See withPrevE for a
trick to supply an initial previous value.
|
|
|
Pair each event value with the previous one. The second result is
the old one. Nothing will come out for the first occurrence of e,
but if you have an initial value a, you can do withPrevE (pure a
mappend e).
|
|
|
Same as withPrevE, but allow a function to combine the values.
Provided for convenience.
|
|
|
Combine two events into one.
|
|
More esoteric
|
|
|
Convert a temporally monotonic list of timed values to an event. See also
the generalization listEG
|
|
|
Event occuring at given times. See also atTime and atTimeG.
|
|
|
Single-occurrence event at given time. See atTimes and atTimeG.
|
|
|
Just the first occurrence of an event.
|
|
|
Decompose an event into its first occurrence value and a remainder
event. See also firstE and restE.
|
|
|
Extract the first occurrence value of an event. See also
firstRestE and restE.
|
|
|
Extract the remainder an event, after its first occurrence. See also
firstRestE and firstE.
|
|
|
Tack remainders a second event onto values of a first event. Occurs
when the first event occurs.
|
|
|
Access the remainder with each event occurrence.
|
|
|
Truncate first event at first occurrence of second event.
|
|
|
Partition an event into segments.
|
|
|
Switch from one event to another, as they occur. (Doesn't merge, as
join does.)
|
|
|
Pass through the Just occurrences, stripped. Experimental
specialization of joinMaybes.
|
|
|
Pass through values satisfying a given predicate. Experimental
specialization of filterMP.
|
|
Useful with events.
|
|
|
Pass through Just occurrences.
|
|
|
Pass through values satisfying p.
|
|
Behaviors
|
|
|
Reactive behaviors. They can be understood in terms of a simple
model (denotational semantics) as functions of time, namely at ::
BehaviorG t a -> (t -> a).
The semantics of BehaviorG instances are given by corresponding
instances for the semantic model (functions). See
http://conal.net/blog/posts/simplifying-semantics-with-type-class-morphisms/.
- Functor: at (fmap f r) == fmap f (at r), i.e., fmap f r at
t == f (r at t).
- Applicative: at (pure a) == pure a, and at (s <*> r) == at s
<*> at t. That is, pure a at t == a, and (s <*> r) at t
== (s at t) (r at t).
- Monad: at (return a) == return a, and at (join rr) == join (at
. at rr). That is, return a at t == a, and join rr at t ==
(rr at t) at t. As always, (r >>= f) == join (fmap f r).
at (r >>= f) == at r >>= at . f.
- Monoid: a typical lifted monoid. If o is a monoid, then
Reactive o is a monoid, with mempty == pure mempty, and mappend
== liftA2 mappend. That is, mempty at t == mempty, and (r
mappend s) at t == (r at t) mappend (s at t).
| Instances | |
|
|
|
Time-specialized behaviors.
Note: The signatures of all of the behavior functions can be generalized. Is
the interface generality worth the complexity?
|
|
|
|
|
The identity generalized behavior. Has value t at time t.
time :: Behavior TimeT
|
|
stepper :: a -> EventI t a -> BehaviorI t a | Source |
|
Discretely changing behavior, based on an initial value and a
new-value event.
stepper :: a -> Event a -> Behavior a
|
|
|
Switch between behaviors.
switcher :: Behavior a -> Event (Behavior a) -> Behavior a
|
|
snapshotWith :: Ord t => (a -> b -> c) -> BehaviorI t b -> EventI t a -> EventI t c | Source |
|
Snapshots a behavior whenever an event occurs and combines the values
using the combining function passed. Take careful note of the order of
arguments and results.
snapshotWith :: (a -> b -> c) -> Behavior b -> Event a -> Event c
|
|
snapshot :: Ord t => BehaviorI t b -> EventI t a -> EventI t (a, b) | Source |
|
Snapshot a behavior whenever an event occurs. See also
snapshotWith. Take careful note of the order of arguments and
results.
snapshot :: Behavior b -> Event a -> Event (a,b)
|
|
snapshot_ :: Ord t => BehaviorI t b -> EventI t a -> EventI t b | Source |
|
Like snapshot but discarding event data (often a is '()').
snapshot_ :: Behavior b -> Event a -> Event b
|
|
whenE :: Ord t => BehaviorI t Bool -> EventI t a -> EventI t a | Source |
|
Filter an event according to whether a reactive boolean is true.
whenE :: Behavior Bool -> Event a -> Event a
|
|
accumB :: a -> EventI t (a -> a) -> BehaviorI t a | Source |
|
Behavior from an initial value and an updater event. See also
accumE.
accumB :: a -> Event (a -> a) -> Behavior a
|
|
|
Like scanl for behaviors. See also scanlE.
scanlB :: forall a. (Behavior a -> Behavior a -> Behavior a) -> Behavior a
-> Event (Behavior a) -> Behavior a
|
|
|
Accumulate values from a monoid-valued event. Specialization of
scanlB, using mappend and mempty. See also monoidE.
monoidB :: Monoid a => Event (Behavior a) -> Behavior a
|
|
maybeB :: Ord t => EventI t a -> EventI t b -> BehaviorI t (Maybe a) | Source |
|
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 the second event.
maybeB :: Event a -> Event b -> Behavior (Maybe a)
|
|
flipFlop :: Ord t => EventI t a -> EventI t b -> BehaviorI t Bool | Source |
|
Flip-flopping behavior. Turns true whenever first event occurs and
false whenever the second event occurs.
flipFlop :: Event a -> Event b -> Behavior Bool
|
|
countB :: (Ord t, Num n) => EventI t a -> BehaviorI t n | Source |
|
Count occurrences of an event. See also countE.
countB :: Num n => Event a -> Behavior n
|
|
|
Like sum for behaviors.
sumB :: AdditiveGroup a => Event a -> Behavior a
|
|
|
Euler integral.
integral :: (VectorSpace v, Scalar v ~ TimeT) =>
Event () -> Behavior v -> Behavior v
|
|
Produced by Haddock version 2.4.2 |