reactive-0.10.1: Simple foundation for functional reactive programmingSource codeContentsIndex
FRP.Reactive.PrimReactive
Stabilityexperimental
Maintainerconal@conal.net
Contents
Events and reactive values
Operations on events and reactive values
To be moved elsewhere
To be removed when it gets used somewhere
Testing
Description

Functional events and reactive values. Semantically, an Event is stream of future values in time order. A Reactive value is a discretly time-varying value.

Many of the operations on events and reactive values are packaged as instances of the standard type classes Monoid, Functor, Applicative, and Monad.

This module focuses on representation and primitives defined in terms of the representation. See also FRP.Reactive.Reactive, which re-exports this module, plus extras that do not exploit the representation. My intention for this separation is to ease experimentation with alternative representations.

Although the basic Reactive type describes discretely-changing values, continuously-changing values can be modeled simply as reactive functions. See FRP.Reactive.Behavior for a convenient 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
data EventG t a
data ReactiveG t a
stepper :: a -> EventG t a -> ReactiveG t a
switcher :: Ord t => ReactiveG t a -> EventG t (ReactiveG t a) -> ReactiveG t a
withTimeGE :: EventG t a -> EventG t (a, Time t)
withTimeGR :: Time t -> ReactiveG t a -> ReactiveG t (a, Time t)
futuresE :: Ord t => [FutureG t a] -> EventG t a
listEG :: Ord t => [(t, a)] -> EventG t a
atTimesG :: Ord t => [t] -> EventG t ()
atTimeG :: Ord t => t -> EventG t ()
snapshotWith :: Ord t => (a -> b -> c) -> ReactiveG t b -> EventG t a -> EventG t c
accumE :: a -> EventG t (a -> a) -> EventG t a
accumR :: a -> EventG t (a -> a) -> ReactiveG t a
once :: Ord t => EventG t a -> EventG t a
withRestE :: EventG t a -> EventG t (a, EventG t a)
untilE :: Ord t => EventG t a -> EventG t b -> 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
eventOcc :: Ord t => EventG t a -> FutureG t (a, EventG t a)
joinMaybes :: MonadPlus m => m (Maybe a) -> m a
filterMP :: MonadPlus m => (a -> Bool) -> m a -> m a
result :: (b -> b') -> (a -> b) -> a -> b'
isMonotoneR :: Ord t => ReactiveG t a -> Bool
batch :: TestBatch
infE :: EventG NumT NumT
Events and reactive values
data EventG t a Source

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.
show/hide Instances
Ord t => Monad (EventG t)
Functor (EventG t)
Ord t => MonadPlus (EventG t)
Ord t => Applicative (EventG t)
Unzip (EventG t)
Ord t => Monoid_f (EventG t)
Ord t => Alternative (EventG t)
Monoid t => Comonad (EventG t)
Monoid t => Copointed (EventG t)
(Show a, Show b) => Show (EventG a b)
(Arbitrary t, Ord t, Num t, Arbitrary a) => Arbitrary (EventG t a)
Ord t => Monoid (EventG t a)
(Eq a, Eq b, EqProp a, EqProp b) => EqProp (EventG a b)
data ReactiveG t a Source

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 at :: ReactiveG t a -> (t -> a). A reactive value may also be thought of (and in this module is implemented as) a current value and an event (stream of future values).

The semantics of ReactiveG instances are given by corresponding instances for the semantic model (functions):

  • 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).
show/hide Instances
Operations on events and reactive values
stepper :: a -> EventG t a -> ReactiveG t aSource
Reactive value from an initial value and a new-value event.
switcher :: Ord t => ReactiveG t a -> EventG t (ReactiveG t a) -> ReactiveG t aSource
Switch between reactive values.
withTimeGE :: EventG t a -> EventG t (a, Time t)Source
Access occurrence times in an event. See also withTimeGR.
withTimeGR :: Time t -> ReactiveG t a -> ReactiveG t (a, Time t)Source
Access occurrence times in a reactive value. See also withTimeGE.
futuresE :: Ord t => [FutureG t a] -> EventG t aSource
Convert a temporally monotonic list of futures to an event
listEG :: Ord t => [(t, a)] -> EventG t aSource
Convert a temporally monotonic list of futures to an event. See also the specialization listE
atTimesG :: Ord t => [t] -> EventG t ()Source
Event at given times. See also atTimeG.
atTimeG :: Ord t => t -> EventG t ()Source
Single-occurrence event at given time.
snapshotWith :: Ord t => (a -> b -> c) -> ReactiveG t b -> EventG t a -> EventG t cSource
Snapshot a reactive value whenever an event occurs and apply a combining function to the event and reactive's values.
accumE :: a -> EventG t (a -> a) -> EventG t aSource
Accumulating event, starting from an initial value and a update-function event. See also accumR.
accumR :: a -> EventG t (a -> a) -> ReactiveG t aSource
Reactive value from an initial value and an updater event. See also accumE.
once :: Ord t => EventG t a -> EventG t aSource
Just the first occurrence of an event.
withRestE :: EventG t a -> EventG t (a, EventG t a)Source
Access the remainder with each event occurrence.
untilE :: Ord t => EventG t a -> EventG t b -> EventG t aSource
Truncate first event at first occurrence of second event.
justE :: Ord t => EventG t (Maybe a) -> EventG t aSource
Pass through the Just occurrences, stripped. Experimental specialization of joinMaybes.
filterE :: (Ord t, Show a) => (a -> Bool) -> EventG t a -> EventG t aSource
Pass through values satisfying a given predicate. Experimental specialization of filterMP.
eventOcc :: Ord t => EventG t a -> FutureG t (a, EventG t a)Source
Extract a future representing the first occurrence of the event together with the event of all occurrences after that one.
To be moved elsewhere
joinMaybes :: MonadPlus m => m (Maybe a) -> m aSource
Pass through Just occurrences.
filterMP :: MonadPlus m => (a -> Bool) -> m a -> m aSource
Pass through values satisfying p.
result :: (b -> b') -> (a -> b) -> a -> b'Source
Apply a given function inside the results of other functions. Equivalent to '(.)', but has a nicer reading when composed
To be removed when it gets used somewhere
isMonotoneR :: Ord t => ReactiveG t a -> BoolSource
Testing
batch :: TestBatchSource
infE :: EventG NumT NumTSource
Produced by Haddock version 2.4.2