reactive-banana-0.1.0.2: Small but flexible functional reactive programming (FRP) library.

Reactive.Core

Contents

Synopsis

Events

The Event type constructor is one of the cornerstones of the present approach to functional reactive programmings. It represents a stream of values as they occur in time.

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 occurence,

 type Event a = [(Time,a)]

Note that this is a semantic model; the type is not actually implement that way, but you can often treat it as if it where. In particular, most of the subsequent operations will be explained in terms of this model.

Instances

Functor Event

The Functor instance allows you to map the values of type a. Semantically,

 fmap f ((time,a):es) = (time, f a) : fmap f es
Monoid (Event a)

The Monoid instance allows you to merge event streams, see the union function below.

 mempty  = never
 mappend = union

never :: Event aSource

The value never denotes the event that never happens. We can model it as the empty stream of events, never = [].

fromEventSource :: EventSource a -> Event aSource

Derive an Event from an EventSource. Apart from never, this is the only way to construct events.

reactimate :: Event (IO ()) -> Prepare ()Source

Schedule an IO event to be executed whenever it happens. This is the only way to observe events. Semantically, you could write it as something like this

 reactimate ((time,action):es) = atTime time action >> reactimate es 

The Prepare monad indicates that you should call this function during program initialization only.

mapIO :: (a -> IO b) -> Event a -> Event bSource

Version of fmap that performs an IO action for each event occurence.

filter :: (a -> Bool) -> Event a -> Event aSource

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

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

filterChanges :: Event (Change a) -> Event aSource

Unpacks event values of the form Change _ and discards everything else.

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

Merge two event streams of the same type. Semantically, we have

 union ((time1,a1):es1) ((time2,a2):es2)
    | time1 < time2 = (time1,a1) : union es1 ((time2,a2):es2)
    | time1 > time2 = (time2,a2) : union ((time1,a1):es1) es2
    | otherwise     = ... -- either of the previous two cases

Note that the order of events that happen simultaneously is undefined. This is not a problem most of the time, but sometimes you have to force a certain order. In that case, you have to combine this with the orderedDuplicate function.

merge :: Event a -> Event b -> Event (Either a b)Source

Merge two event streams that have differen types. Semantically, we have

 merge e1 e2 = fmap Left e1 `union` fmap Right e2

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

Duplicate an event stream while paying attention to ordering. Events from the first duplicate (and anything derived from them) will always happen before the events from the second duplicate. Use this function to fine-tune the order of events.

traceEvent :: Show a => String -> Event a -> Event aSource

Debugging helper. Prints the first argument and the value of the event whenever it happens to stderr.

Behaviors

The Behavior type constructor is the other cornerstone of the present approach to functional reactive programming. It represents a value that changes with time.

data Behavior a Source

Behavior a represents a value in time. Think of it as

 type Behavior a = Time -> a

However, note that this model misses an important point: we only allow piecewise constant functions. Continuous behaviors like

 badbehavior = \time -> 2*time

cannot be implemented.

Instances

Functor Behavior

The Functor instance allows you to map the values of type a. Semantically,

 fmap f behavior = \time -> f (behavior time)
Applicative Behavior

The Applicative instance is one most of the most important ways to combine behaviors. Semantically,

 pure a    = always a
 bf <*> bx = \time -> bf time $ bx time 

behavior :: a -> Event a -> Behavior aSource

Smart constructor. Supply an initial value and a sequence of changes. In particular,

 initial (behavior a es) = a
 changes (behavior a es) = es

always :: a -> Behavior aSource

The constant behavior. Semantically,

 always a = \time -> a

initial :: Behavior a -> aSource

The value that the behavior initially has.

changes :: Behavior a -> Event aSource

An event stream recording how the behavior changes Remember that behaviors are piecewise constant functions.

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

The most important way to combine behaviors and events. The apply function applies a time-varying function to a stream of events. Semantically,

 apply bf es = [(time, bf time a) | (time, a) <- es]

(Theoretically inclined people might be wondering whether we could achieve the same effect with the Applicative instance. The answer is no, the semantics of apply and <*> are subtly different. That's why we need to distinguish between behaviors and events.)

accumulate' :: (b -> a -> a) -> a -> Event b -> Behavior aSource

The most important way to create behaviors. The accumulate' function is similar to a strict left fold, foldl'. It starts with an initial value and combines it with incoming events. For example, semantically

 accumulate' (++) "x" [(time1,"y"),(time2,"z")]
    = behavior "x" [(time1,"yx"),(time2,"zyx")]

Note that the accumulated value is evaluated strictly. This prevents space leaks.

It is recommended that you use the accumulate function from Reactive.Classes to pick types automatically.

accumulateChange :: (b -> a -> Change a) -> a -> Event b -> Behavior aSource

Version of accumulate that involves the Change data type. Use the Keep constructor to indicate that the incoming event hasn't changed the value. No change event will be propagated in that case.

It is recommended that you use the accumulate function from Reactive.Classes to pick types automatically.

accumulateIO :: (b -> a -> IO a) -> a -> Event b -> Behavior aSource

Version of accumulate that performs an IO action to update the value.

It is recommended that you use the accumulate function from Reactive.Classes to pick types automatically.

accumulateIOChange :: (b -> a -> IO (Change a)) -> a -> Event b -> Behavior aSource

Version of accumulate that involves the Change data type and performs an IO action to update the value.

It is recommended that you use the accumulate function from Reactive.Classes to pick types automatically.

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

Map events while threading state. Similar to the standard mapAccumL function.

The Change data type

data Change a Source

Data type to indicate that a value has changed. Used in conjunction with the accumulate functions.

This is basically the Maybe type with a different name. Using a different name improves program readability and makes it easier to automatically select the right accumulate function by type, see the Reactive.Classes module.

Constructors

Keep

Signals that the value has not changed.

Change a

Indicates a change to some value of type a.

Instances

Functor Change 
ReactiveSyntax b (IO (Change b)) 
ReactiveSyntax b (Change b) 
Eq a => Eq (Change a) 
Read a => Read (Change a) 
Show a => Show (Change a) 

isChange :: Change a -> BoolSource

The isChange function returns True iff its argument is of the form Change _.

isKeep :: Change a -> BoolSource

The isKeep function returns True iff its argument is of the form Keep.

Event Sources

After having read all about Events and Behaviors, you want to hook things up to an existing event-based framework, like wxHaskell or Gtk2Hs. How do you do that?

EventSources are a small bookkeeping device that helps you with that. Basically, they store event handlers. Often, you can just obtain them from corresponding bookkeeping devices from your framework, but sometimes you have to create your own EventSource and use the fire function to hook it into the framework. Event sources are also useful for testing.

After creating an EventSource, you can finally obtain an Event via the fromEventSource function.

data EventSource a Source

An EventSource is a facility where you can register callback functions, aka event handlers. EventSources are the precursor of proper Events.

Constructors

EventSource 

Fields

setEventHandler :: (a -> IO ()) -> Prepare ()

Replace all event handlers by this one.

getEventHandler :: Prepare (a -> IO ())

Retrieve the currently registered event handler.

type Prepare a = IO aSource

The Prepare monad is just a type synonym for IO. The idea is that the event flow is set up in the Prepare monad; all Prepare actions should be called during the program initialization, but not while the event loop is running.

newEventSource :: Prepare (EventSource a)Source

Create a new store for callback functions. They have to be fired manually with the fire function.

fire :: EventSource a -> a -> IO ()Source

Fire the event handler of an event source manually. Useful for hooking into external event sources.

Internal