Safe Haskell | None |
---|
- interpretAsHandler :: (forall t. Event t a -> Event t b) -> AddHandler a -> AddHandler b
- compile :: (forall t. Frameworks t => Moment t ()) -> IO EventNetwork
- class Frameworks t
- module Control.Event.Handler
- fromAddHandler :: Frameworks t => AddHandler a -> Moment t (Event t a)
- fromChanges :: Frameworks t => a -> AddHandler a -> Moment t (Behavior t a)
- fromPoll :: Frameworks t => IO a -> Moment t (Behavior t a)
- reactimate :: Frameworks t => Event t (IO ()) -> Moment t ()
- reactimate' :: Frameworks t => Event t (Future (IO ())) -> Moment t ()
- initial :: Behavior t a -> Moment t a
- changes :: Frameworks t => Behavior t a -> Moment t (Event t (Future a))
- imposeChanges :: Frameworks t => Behavior t a -> Event t () -> Behavior t a
- newtype FrameworksMoment a = FrameworksMoment {
- runFrameworksMoment :: forall t. Frameworks t => Moment t a
- execute :: Frameworks t => Event t (FrameworksMoment a) -> Moment t (Event t a)
- liftIOLater :: Frameworks t => IO () -> Moment t ()
- module Control.Monad.IO.Class
- data EventNetwork
- actuate :: EventNetwork -> IO ()
- pause :: EventNetwork -> IO ()
- newEvent :: Frameworks t => Moment t (Event t a, Handler a)
- interpretFrameworks :: (forall t. Event t a -> Event t b) -> [a] -> IO [[b]]
- showNetwork :: EventNetwork -> IO String
Synopsis
Build event networks using existing event-based frameworks and run them.
Simple use
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 Event
s and Behavior
s,
you want to hook them up to an existing event-based framework,
like wxHaskell
or Gtk2Hs
.
How do you do that?
The module presented here allows you to
- obtain input events from external sources and to
- perform output in reaction to events.
In constrast, the functions from Reactive.Banana.Combinators 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
Moment
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. Frameworks t => Moment 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,
- Use
fromAddHandler
to obtain input events. The library uses this to register event handlers with your event-based framework. - Use
reactimate
to animate output events.
compile :: (forall t. Frameworks t => Moment t ()) -> IO EventNetworkSource
Compile the description of an event network
into an EventNetwork
that you can actuate
, pause
and so on.
Event networks are described in the Moment
monad
and use the Frameworks
class constraint.
class Frameworks t Source
Class constraint on the type parameter t
of the Moment
monad.
Indicates that we can add input and output to an event network.
module Control.Event.Handler
fromAddHandler :: Frameworks t => AddHandler a -> Moment 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 :: Frameworks t => a -> AddHandler a -> Moment 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 :: Frameworks t => IO a -> Moment 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 :: Frameworks t => Event t (IO ()) -> Moment 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 reactimate
s 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 reactimate
s follow the control flow
of your event-based framework.
Note: An event network essentially behaves like a single,
huge callback function. The IO
action are not run in a separate thread.
The callback function will throw an exception if one of your IO
actions
does so as well.
Your event-based framework will have to handle this situation.
reactimate' :: Frameworks t => Event t (Future (IO ())) -> Moment t ()Source
Output.
Execute the IO
action whenever the event occurs.
This version of reactimate
can deal with values obtained
from the changes
function.
initial :: Behavior t a -> Moment t aSource
Output,
observe the initial value contained in a Behavior
.
changes :: Frameworks t => Behavior t a -> Moment t (Event t (Future 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)
Note: The values of the event will not become available
until event processing is complete.
It can be used only in the context of reactimate'
.
imposeChanges :: Frameworks t => Behavior t a -> Event t () -> Behavior t aSource
newtype FrameworksMoment a Source
Dummy type needed to simulate impredicative polymorphism.
FrameworksMoment | |
|
execute :: Frameworks t => Event t (FrameworksMoment a) -> Moment t (Event t a)Source
Dynamically add input and output to an existing event network.
Note: You can even do IO
actions here, but there is no
guarantee about the order in which they are executed.
liftIOLater :: Frameworks t => IO () -> Moment t ()Source
module Control.Monad.IO.Class
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
newEvent :: Frameworks t => Moment t (Event t a, Handler a)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
.
Internal
interpretFrameworks :: (forall t. Event t a -> Event t b) -> [a] -> IO [[b]]Source
Interpret by using a framework internally. Only useful for testing library internals.
showNetwork :: EventNetwork -> IO StringSource
A multiline description of the current Latch
es and Pulse
s in
the EventNetwork
.
Incidentally, evaluation the returned string to normal
form will also force the EventNetwork
to some kind of normal form.
This may be useful for benchmarking purposes.