| Safe Haskell | None | 
|---|
Reactive.Banana.Combinators
Contents
- data Event t a
- data Behavior t a
- interpret :: (forall t. Event t a -> Event t b) -> [[a]] -> IO [[b]]
- module Control.Applicative
- module Data.Monoid
- never :: Event t a
- union :: Event t a -> Event t a -> Event t a
- unions :: [Event t a] -> Event t a
- filterE :: (a -> Bool) -> Event t a -> Event t a
- collect :: Event t a -> Event t [a]
- spill :: Event t [a] -> Event t a
- accumE :: a -> Event t (a -> a) -> Event t a
- apply :: Behavior t (a -> b) -> Event t a -> Event t b
- stepper :: a -> Event t a -> Behavior t a
- (<@>) :: Behavior t (a -> b) -> Event t a -> Event t b
- (<@) :: Behavior t b -> Event t a -> Event t b
- filterJust :: Event t (Maybe a) -> Event t a
- filterApply :: Behavior t (a -> Bool) -> Event t a -> Event t a
- whenE :: Behavior t Bool -> Event t a -> Event t a
- split :: Event t (Either a b) -> (Event t a, Event t b)
- accumB :: a -> Event t (a -> a) -> Behavior t a
- mapAccum :: acc -> Event t (acc -> (x, acc)) -> (Event t x, Behavior t acc)
- calm :: Event t a -> Event t a
- unionWith :: (a -> a -> a) -> Event t a -> Event t a -> Event t a
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.
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)]
Behavior t a represents a value that varies in time. Think of it as
type Behavior t a = Time -> 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 Reactive.Banana.Model for more.
interpret :: (forall t. Event t a -> Event t b) -> [[a]] -> IO [[b]]Source
Interpret an event processing function. Useful for testing.
Core Combinators
module Control.Applicative
module Data.Monoid
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
unions :: [Event t a] -> Event t aSource
Merge several event streams of the same type.
unions = foldr union never
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. The first element in the list will be emitted first, and so on.
Up to strictness, we have
spill . collect = id
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]
This function is generally used in its infix variant <@>.
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 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
Infix operators
(<@) :: Behavior t b -> Event t a -> Event t bSource
Tag all event occurrences with a time-varying value. Similar to <*.
infixl 4 <@
Filtering
filterJust :: Event t (Maybe a) -> Event t aSource
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.
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.
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.