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

Safe HaskellSafe-Infered

Reactive.Banana.Frameworks

Contents

Synopsis

Synopsis

Build event networks using existing event-based frameworks and run them.

Simple use

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

Simple way to run an event graph. Very useful for testing. Uses the efficient push-driven implementation.

interpretAsHandler :: (forall t. Event t a -> Event t b) -> AddHandler a -> AddHandler bSource

Simple way to write a single event handler with functional reactive programming.

Building event networks with input/output

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

This Reactive.Banana.Implementation module allows you to obtain input events from external sources and it allows you perform output in reaction to events.

In constrast, the functions from Reactive.Banana.Model allow you to express the output events in terms of the input events. This expression is called an event graph.

An event network is an event graph together with inputs and outputs. To build an event network, describe the inputs, outputs and event graph in the NetworkDescription monad and use the compile function to obtain an event network from that.

To activate an event network, use the actuate function. The network will register its input event handlers and start producing output.

A typical setup looks like this:

 main = do
   -- initialize your GUI framework
   window <- newWindow
   ...

   -- describe the event network
   let networkDescription :: forall t. NetworkDescription t ()
       networkDescription = do
           -- input: obtain  Event  from functions that register event handlers
           emouse    <- fromAddHandler $ registerMouseEvent window
           ekeyboard <- fromAddHandler $ registerKeyEvent window
           -- input: obtain  Behavior  from changes
           btext     <- fromChanges    "" $ registerTextChange editBox
           -- input: obtain  Behavior  from mutable data by polling
           bdie      <- fromPoll       $ randomRIO (1,6)

           -- express event graph
           let
               behavior1 = accumB ...
               ...
               event15 = union event13 event14
   
           -- output: animate some event occurences
           reactimate $ fmap print event15
           reactimate $ fmap drawCircle eventCircle

       -- compile network description into a network
       network <- compile networkDescription
       -- register handlers and start producing outputs
       actuate network

In short, you use fromAddHandler to obtain input events. The library uses this to register event handlers with your event-based framework.

To animate output events, use the reactimate function.

data NetworkDescription t a Source

Monad for describing event networks.

The NetworkDescription monad is an instance of MonadIO, so IO is allowed inside.

Note: The phantom type t prevents you from smuggling values of types Event or Behavior outside the NetworkDescription monad.

compile :: (forall t. NetworkDescription t ()) -> IO EventNetworkSource

Compile a NetworkDescription into an EventNetwork that you can actuate, pause and so on.

type AddHandler a = (a -> IO ()) -> IO (IO ())Source

A value of type AddHandler a is just a facility for registering callback functions, also known as event handlers.

The type is a bit mysterious, it works like this:

 do unregisterMyHandler <- addHandler myHandler

The argument is an event handler that will be registered. The return value is an action that unregisters this very event handler again.

fromAddHandler :: AddHandler a -> NetworkDescription t (Event t a)Source

Input, obtain an Event from an AddHandler.

When the event network is actuated, this will register a callback function such that an event will occur whenever the callback function is called.

fromChanges :: a -> AddHandler a -> NetworkDescription t (Behavior t a)Source

Input, obtain a Behavior from an AddHandler that notifies changes.

This is essentially just an application of the stepper combinator.

fromPoll :: IO a -> NetworkDescription t (Behavior t a)Source

Input, obtain a Behavior by frequently polling mutable data, like the current time.

The resulting Behavior will be updated on whenever the event network processes an input event.

This function is occasionally useful, but the recommended way to obtain Behaviors is by using fromChanges.

Ideally, the argument IO action just polls a mutable variable, it should not perform expensive computations. Neither should its side effects affect the event network significantly.

reactimate :: Event t (IO ()) -> NetworkDescription t ()Source

Output. Execute the IO action whenever the event occurs.

Note: If two events occur very close to each other, there is no guarantee that the reactimates for one event will have finished before the ones for the next event start executing. This does not affect the values of events and behaviors, it only means that the reactimate for different events may interleave. Fortuantely, this is a very rare occurrence, and only happens if

  • you call an event handler from inside reactimate,
  • or you use concurrency.

In these cases, the reactimates follow the control flow of your event-based framework.

initial :: Behavior t a -> NetworkDescription t aSource

Output, observe the initial value contained in a Behavior.

Similar to updates, this function is not well-defined, but exists for reasons of efficiency.

changes :: Behavior t a -> NetworkDescription t (Event t a)Source

Output, observe when a Behavior changes.

Strictly speaking, a Behavior denotes a value that varies *continuously* in time, so there is no well-defined event which indicates when the behavior changes.

Still, for reasons of efficiency, the library provides a way to observe changes when the behavior is a step function, for instance as created by stepper. There are no formal guarantees, but the idea is that

 changes (stepper x e) = return (calm e)

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

liftIOLater :: IO () -> NetworkDescription t ()Source

Lift an IO action into the NetworkDescription monad, but defer its execution until compilation time. This can be useful for recursive definitions using MonadFix.

Running event networks

data EventNetwork Source

Data type that represents a compiled event network. It may be paused or already running.

actuate :: EventNetwork -> IO ()Source

Actuate an event network. The inputs will register their event handlers, so that the networks starts to produce outputs in response to input events.

pause :: EventNetwork -> IO ()Source

Pause an event network. Immediately stop producing output and unregister all event handlers for inputs. Hence, the network stops responding to input events, but it's state will be preserved.

You can resume the network with actuate.

Note: You can stop a network even while it is processing events, i.e. you can use pause as an argument to reactimate. The network will not stop immediately though, only after the current event has been processed completely.

Utilities

This section collects a few convenience functions for unusual use cases. For instance:

  • The event-based framework you want to hook into is poorly designed
  • You have to write your own event loop and roll a little event framework

newAddHandler :: IO (AddHandler a, a -> IO ())Source

Build a facility to register and unregister event handlers.

newEvent :: NetworkDescription t (Event t a, a -> IO ())Source

Build an Event together with an IO action that can fire occurrences of this event. Variant of newAddHandler.

This function is mainly useful for passing callback functions inside a reactimate.