reactive-banana-0.5.0.0: Practical library for functional reactive programming (FRP).

Safe HaskellSafe-Infered

Reactive.Banana.Combinators

Contents

Synopsis

Synopsis

Combinators for building event graphs.

Introduction

At its core, Functional Reactive Programming (FRP) is about two data types Event and Behavior and the various ways to combine them.

newtype Event t a Source

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

 type Event t a = [(Time,a)]

Constructors

E

(Constructor exported for internal use only.)

Fields

unE :: Event Expr [a]
 

Instances

Functor (Event t) 
Apply (Behavior t) (Event t) 
Monoid (Event t (a -> a)) 

newtype Behavior t a Source

Behavior t a represents a value that varies in time. Think of it as

 type Behavior t a = Time -> a

Constructors

B

(Constructor exported for internal use only.)

Fields

unB :: Behavior Expr a
 

Instances

As you can see, both types seem to have a superfluous parameter t. The library uses it to rule out certain gross inefficiencies, in particular in connection with dynamic event switching. For basic stuff, you can completely ignore it, except of course for the fact that it will annoy you in your type signatures.

While the type synonyms mentioned above are the way you should think about Behavior and Event, they are a bit vague for formal manipulation. To remedy this, the library provides a very simple but authoritative model implementation. See Model for more.

interpretModel :: (forall t. Event t a -> Event t b) -> [[a]] -> IO [[b]]Source

Interpret with model implementation. Useful for testing.

interpretPushGraph :: (forall t. Event t a -> Event t b) -> [[a]] -> IO [[b]]Source

Interpret with push-based implementation. Useful for testing.

Core Combinators

never :: Event t aSource

Event that never occurs. Think of it as never = [].

union :: Event t a -> Event t a -> Event t aSource

Merge two event streams of the same type. In case of simultaneous occurrences, the left argument comes first. Think of it as

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

filterE :: (a -> Bool) -> Event t a -> Event t aSource

Allow all events that fulfill the predicate, discard the rest. Think of it as

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

collect :: Event t a -> Event t [a]Source

Collect simultaneous event occurences. The result will never contain an empty list. Example:

 collect [(time1, e1), (time1, e2)] = [(time1, [e1,e2])]

spill :: Event t [a] -> Event t aSource

Emit simultaneous event occurrences. Up to strictness, we have

 spill . collect = id

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

The accumE function accumulates a stream of events. Example:

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

Note that the output events are simultaneous with the input events, there is no "delay" like in the case of accumB.

apply :: Behavior t (a -> b) -> Event t a -> Event t bSource

Apply a time-varying function to a stream of events. Think of it as

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

stepper :: a -> Event t a -> Behavior t aSource

Construct a time-varying function from an initial value and a stream of new values. Think of it as

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

Note that the smaller-than-sign in the comparision timex < time means that the value of the behavior changes "slightly after" the event occurrences. This allows for recursive definitions.

Also note that in the case of simultaneous occurrences, only the last one is kept.

Further combinators that Haddock can't document properly.

 instance Monoid (Event t (a -> a))

This monoid instance is not the straightforward instance that you would obtain from never and union. Instead of just merging event streams, we use unionWith to compose the functions. This is very useful in the context of accumE and accumB where simultaneous event occurrences are best avoided.

 instance Applicative (Behavior t)

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

 pure :: a -> Behavior t a

The constant time-varying value. Think of it as pure x = \time -> x.

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

Combine behaviors in applicative style. Think of it as bf <*> bx = \time -> bf time $ bx time.

Derived Combinators

Filtering

filterJust :: Event t (Maybe a) -> Event t aSource

Keep only the Just values. Variant of filterE.

filterApply :: Behavior t (a -> Bool) -> Event t a -> Event t aSource

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

whenE :: Behavior t Bool -> Event t a -> Event t aSource

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

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

Split event occurrences according to a tag.

Accumulation

Note: all accumulation functions are strict in the accumulated value! acc -> (x,acc) is the order used by unfoldr and State.

accumB :: a -> Event t (a -> a) -> Behavior t aSource

The accumB function is similar to a strict left fold, foldl'. It starts with an initial value and combines it with incoming events. For example, think

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

Note that the value of the behavior changes "slightly after" the events occur. This allows for recursive definitions.

mapAccum :: acc -> Event t (acc -> (x, acc)) -> (Event t x, Behavior t acc)Source

Efficient combination of accumE and accumB.

Simultaneous event occurrences

calm :: Event t a -> Event t aSource

Keep only the last occurrence when simultaneous occurrences happen.

unionWith :: (a -> a -> a) -> Event t a -> Event t a -> Event t aSource

Combine simultaneous event occurrences into a single occurrence.

 unionWith f e1 e2 = fmap (foldr1 f) <$> collect (e1 `union` e2)

Apply class

class (Functor f, Functor g) => Apply f g whereSource

Class for overloading the apply function.

Methods

(<@>) :: f (a -> b) -> g a -> g bSource

Infix operation for the apply function, similar to <*>

(<@) :: f a -> g b -> g aSource

Convenience function, similar to <*

Instances

Apply (Behavior t) (Event t) 
Apply (Behavior t) (Event t)