reactive-banana-1.0.0.0: Library for functional reactive programming (FRP).

Safe HaskellNone
LanguageHaskell98

Reactive.Banana.Combinators

Contents

Synopsis

Synopsis

The main types and combinators of Functional Reactive Programming (FRP).

At its core, FRP is about two data types Event and Behavior and the various ways to combine them. There is also a third type Moment, which is necessary for the higher-order combinators.

Core Combinators

Event and Behavior

data Event a Source

Event a represents a stream of events as they occur in time. Semantically, you can think of Event a as an infinite list of values that are tagged with their corresponding time of occurrence,

type Event a = [(Time,a)]

Each pair is called an event occurrence. Note that within a single event stream, no two event occurrences may happen at the same time.

data Behavior a Source

Behavior a represents a value that varies in time. Semantically, you can think of it as a function

type Behavior a = Time -> a

interpret :: (Event a -> Event b) -> [Maybe a] -> IO [Maybe b] Source

Interpret an event processing function. Useful for testing.

First-order

never :: Event a Source

Event that never occurs. Semantically, never = [].

unionWith :: (a -> a -> a) -> Event a -> Event a -> Event a Source

Merge two event streams of the same type. The function argument specifies how event values are to be combined in case of a simultaneous occurrence. The semantics are

unionWith f ((timex,x):xs) ((timey,y):ys)
   | timex <  timey = (timex,x)     : unionWith f xs ((timey,y):ys)
   | timex >  timey = (timey,y)     : unionWith f ((timex,x):xs) ys
   | timex == timey = (timex,f x y) : unionWith f xs ys

filterE :: (a -> Bool) -> Event a -> Event a Source

Allow all events that fulfill the predicate, discard the rest. Semantically,

filterE p es = [(time,a) | (time,a) <- es, p a]

apply :: Behavior (a -> b) -> Event a -> Event b Source

Apply a time-varying function to a stream of events. Semantically,

apply bf ex = [(time, bf time x) | (time, x) <- ex]

This function is generally used in its infix variant <@>.

Further combinators that Haddock can't document properly.

instance Applicative Behavior

Behavior is an applicative functor. In particular, we have the following functions.

pure :: a -> Behavior a

The constant time-varying value. Semantically, pure x = \time -> x.

(<*>) :: Behavior (a -> b) -> Behavior a -> Behavior b

Combine behaviors in applicative style. The semantics are: bf <*> bx = \time -> bf time $ bx time.

Moment and accumulation

data Moment a Source

The Moment monad denotes a pure computation that happens at one particular moment in time. Semantically, it as a reader monad

type Moment a = Time -> a

When run, the argument tells the time at which this computation happens.

Note that in this context, time really means to logical time. Of course, every calculation on a computer takes some amount of wall-clock time to complete. Instead, what is meant here is the time as it relates to Events and Behaviors. We use the fiction that every calculation within the Moment monad takes zero logical time to perform.

class Monad m => MonadMoment m where Source

An instance of the MonadMoment class denotes a computation that happens at one particular moment in time.

Unlike the Moment monad, it need not be pure anymore.

Methods

liftMoment :: Moment a -> m a Source

accumE :: MonadMoment m => a -> Event (a -> a) -> m (Event a) Source

The accumE function accumulates a stream of event values, similar to a strict left scan, scanl'. It starts with an initial value and emits a new value whenever an event occurrence happens. The new value is calculated by applying the function in the event to the old value.

Example:

accumE "x" [(time1,(++"y")),(time2,(++"z"))]
    = trimE [(time1,"xy"),(time2,"xyz")]
    where
    trimE e start = [(time,x) | (time,x) <- e, start <= time]

Note: It makes sense to list the accumE function as a primitive combinator, but keep in mind that it can actually be expressed in terms of stepper and apply by using recursion:

accumE a e1 = mdo
   let e2 = (\a f -> f a) <$> b <@> e1
   b <- stepper a e2
   return e2

stepper :: MonadMoment m => a -> Event a -> m (Behavior a) Source

Construct a time-varying function from an initial value and a stream of new values. The result will be a step function. Semantically,

stepper x0 ex = \time1 -> \time2 ->
    last (x0 : [x | (timex,x) <- ex, time1 <= timex, timex < time2])

Here is an illustration of the result Behavior at a particular time:

Note: The smaller-than-sign in the comparison timex < time2 means that at time time2 == timex, the value of the Behavior will still be the previous value. In the illustration, this is indicated by the dots at the end of each step. This allows for recursive definitions.

Higher-order

valueB :: MonadMoment m => Behavior a -> m a Source

Obtain the value of the Behavior at a given moment in time. Semantically, it corresponds to

valueB b = \time -> b time

NOTE: The value is immediately available for pattern matching. Unfortunately, this means that valueB is unsuitable for use with value recursion in the Moment monad. If you need recursion, please use valueBLater instead.

valueBLater :: MonadMoment m => Behavior a -> m a Source

Obtain the value of the Behavior at a given moment in time. Semantically, it corresponds to

valueBLater b = \time -> b time

NOTE: To allow for more recursion, the value is returned lazily and not available for pattern matching immediately. It can be used safely with most combinators like stepper. If that doesn't work for you, please use valueB instead.

observeE :: Event (Moment a) -> Event a Source

Observe a value at those moments in time where event occurrences happen. Semantically,

observeE e = [(time, m time) | (time, m) <- e]

switchE :: Event (Event a) -> Event a Source

Dynamically switch between Event. Semantically,

switchE ee = concat [trim t1 t2 e | (t1,t2,e) <- intervals ee]
    where
    intervals e        = [(time1, time2, x) | ((time1,x),(time2,_)) <- zip e (tail e)]
    trim time1 time2 e = [x | (timex,x) <- e, time1 < timex, timex <= time2]

switchB :: Behavior a -> Event (Behavior a) -> Behavior a Source

Dynamically switch between Behavior. Semantically,

 switchB b0 eb = \time ->
    last (b0 : [b | (time2,b) <- eb, time2 < time]) time

Derived Combinators

Infix operators

(<@>) :: Behavior (a -> b) -> Event a -> Event b infixl 4 Source

Infix synonym for the apply combinator. Similar to <*>.

infixl 4 <@>

(<@) :: Behavior b -> Event a -> Event b infixl 4 Source

Tag all event occurrences with a time-varying value. Similar to <*.

infixl 4 <@

Filtering

filterJust :: Event (Maybe a) -> Event a Source

Allow all event occurrences that are Just values, discard the rest. Variant of filterE.

filterApply :: Behavior (a -> Bool) -> Event a -> Event a Source

Allow all events that fulfill the time-varying predicate, discard the rest. Generalization of filterE.

whenE :: Behavior Bool -> Event a -> Event a Source

Allow events only when the behavior is True. Variant of filterApply.

split :: Event (Either a b) -> (Event a, Event b) Source

Split event occurrences according to a tag. The Left values go into the left component while the Right values go into the right component of the result.

Accumulation

Note: All accumulation functions are strict in the accumulated value!

Note: The order of arguments is acc -> (x,acc) which is also the convention used by unfoldr and State.

unions :: [Event (a -> a)] -> Event (a -> a) Source

Merge event streams whose values are functions. In case of simultaneous occurrences, the functions at the beginning of the list are applied after the functions at the end.

unions [] = never
unions xs = foldr1 (unionWith (.)) xs

Very useful in conjunction with accumulation functions like accumB and accumE.

accumB :: MonadMoment m => a -> Event (a -> a) -> m (Behavior a) Source

The accumB function accumulates event occurrences into a Behavior.

The value is accumulated using accumE and converted into a time-varying value using stepper.

Example:

accumB "x" [(time1,(++"y")),(time2,(++"z"))]
   = stepper "x" [(time1,"xy"),(time2,"xyz")]

Note: As with stepper, the value of the behavior changes "slightly after" the events occur. This allows for recursive definitions.

mapAccum :: MonadMoment m => acc -> Event (acc -> (x, acc)) -> m (Event x, Behavior acc) Source

Efficient combination of accumE and accumB.