reactive-banana-0.4.1.0: Small but solid library for functional reactive programming (FRP).

Reactive.Banana.Implementation

Contents

Synopsis

Synopsis

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

Simple use

data PushIO Source

The type index PushIO represents the efficient push-driven implementation described here. It implements the same FRP interface as the model implementation represented by Model.

interpret :: Typeable a => (Event PushIO a -> Event PushIO b) -> [a] -> IO [[b]]Source

Simple way to run an event graph. Very useful for testing.

interpretAsHandler :: Typeable a => (Event PushIO a -> Event PushIO 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
   ...

   -- build the event network
   network <- compile $ do
       -- input: obtain  Event  from functions that register event handlers
       emouse    <- fromAddHandler $ registerMouseEvent window
       ekeyboard <- fromAddHandler $ registerKeyEvent window
       -- input: obtain  Behavior  from mutable data by polling
       btext     <- fromPoll       $ getTextValue editBox
       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

   -- 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 a Source

Monad for describing event networks.

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

Note: It is forbidden to smuggle values of types Event or Behavior outside the NetworkDescription monad. This shouldn't be possible by default, but you might get clever and use IORef to circumvent this. Don't do that, it won't work and also has a 99,98% chance of destroying the earth by summoning time-traveling zygohistomorphisms.

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 :: Typeable a => AddHandler a -> NetworkDescription (Event PushIO 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.

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

Input, obtain a Behavior by polling mutable data, like mutable variables or GUI widgets.

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.

Internally, the event network will take a snapshot of each mutable datum before processing an input event, so that the obtained behavior is well-defined. This snapshot is guaranteed to happen before any reactimate is performed. The network may omit taking a snapshot altogether if the behavior is not needed.

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

Output. Execute the IO action whenever the event occurs.

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

Lift a computation from the IO monad.

liftIOLater :: IO () -> NetworkDescription ()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.