reactive-0.5.0.1: Simple foundation for functional reactive programming

Stabilityexperimental
Maintainerconal@conal.net

Data.Reactive

Contents

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

newtype Event a Source

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. An especially useful monad-based function is joinMaybes, which filters a Maybe-valued event.

Constructors

Event 

Fields

eFuture :: Future (Reactive a)
 

data Reactive 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 (%$) :: 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 

Fields

rInit :: a

initial value

rEvent :: Event a

waiting for event

type Source = ReactiveSource

Compatibility synonym (for ease of transition from DataDriven)

inEvent :: (Future (Reactive a) -> Future (Reactive b)) -> Event a -> Event bSource

Apply a unary function inside an Event representation.

inEvent2 :: (Future (Reactive a) -> Future (Reactive b) -> Future (Reactive c)) -> Event a -> Event b -> Event cSource

Apply a unary function inside an Event representation.

stepper :: a -> Event a -> Reactive aSource

Reactive value from an initial value and a new-value event.

switcher :: Reactive a -> Event (Reactive a) -> Reactive aSource

Switch between reactive values.

mkEvent :: IO (Event a, Sink a)Source

Make an event and a sink for feeding the event. Each value sent to the sink becomes an occurrence of the event.

mkEventTrace :: (a -> String) -> IO (Event a, Sink a)Source

Tracing variant of mkEvent

mkEventShow :: Show a => String -> IO (Event a, Sink a)Source

Show specialization of mkEventTrace

runE :: Event (IO b) -> IO aSource

Run an event in the current thread.

forkE :: Event (IO b) -> IO ThreadIdSource

Run an event in a new thread.

subscribe :: Event a -> Sink a -> IO ThreadIdSource

Subscribe a listener to an event. Wrapper around forkE and fmap.

forkR :: Reactive (IO b) -> IO ThreadIdSource

Run a reactive value in a new thread. The initial action happens in the current thread.

Event extras

accumE :: a -> Event (a -> a) -> Event aSource

Accumulating event, starting from an initial value and a update-function event. See also accumR.

scanlE :: (a -> b -> a) -> a -> Event b -> Event aSource

Like scanl for events. See also scanlR.

monoidE :: Monoid o => Event o -> Event oSource

Accumulate values from a monoid-valued event. Specialization of scanlE, using mappend and mempty. See also monoidR.

withPrevE :: Event a -> Event (a, a)Source

Pair each event value with the previous one, given an initial value.

countE :: Num n => Event b -> Event (b, n)Source

Count occurrences of an event, remembering the occurrence values. See also countE_.

countE_ :: Num n => Event b -> Event nSource

Count occurrences of an event, forgetting the occurrence values. See also countE. See also countR.

diffE :: Num n => Event n -> Event nSource

Difference of successive event occurrences.

snapshot :: Event a -> Reactive b -> Event (a, b)Source

Snapshot a reactive value whenever an event occurs.

snapshot_ :: Event a -> Reactive b -> Event bSource

Like snapshot but discarding event data (often a is ()).

whenE :: Event a -> Reactive Bool -> Event aSource

Filter an event according to whether a boolean source is true.

once :: Event a -> Event aSource

Just the first occurrence of an event.

traceE :: (a -> String) -> Unop (Event a)Source

Tracing of events.

eventX :: IO (Event a, Sink (Event a))Source

Make an extensible event. The returned sink is a way to add new events to mix. You can often use '(>>=)' or join instead. Warning: this function might be removed at some point.

Reactive extras

accumR :: a -> Event (a -> a) -> Reactive aSource

Reactive value from an initial value and an updater event. See also accumE.

scanlR :: (a -> b -> a) -> a -> Event b -> Reactive aSource

Like scanl for reactive values. See also scanlE.

monoidR :: Monoid a => Event a -> Reactive aSource

Accumulate values from a monoid-valued event. Specialization of scanlE, using mappend and mempty. See also monoidE.

maybeR :: Event a -> Event b -> Reactive (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 lose.

flipFlop :: Event a -> Event b -> Reactive BoolSource

Flip-flopping source. Turns true when ea occurs and false when eb occurs.

countR :: Num n => Event a -> Reactive nSource

Count occurrences of an event. See also countE.

traceR :: (a -> String) -> Unop (Reactive a)Source

Tracing of reactive values

Reactive behaviors

type Time = DoubleSource

Time for continuous behaviors

type ReactiveB = Reactive :. Fun TimeSource

Reactive behaviors. Simply a reactive Function value. Wrapped in a type composition to get Functor and Applicative for free.

To be moved elsewhere

replace :: Functor f => b -> f a -> f bSource

Replace a functor value with a given one.

forget :: Functor f => f a -> f ()Source

Forget a functor value, replace with ()

type Action = IO ()Source

Convenient alias for dropping parentheses.

type Sink a = a -> ActionSource

Value sink

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.