Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- interpretAsHandler :: (Event a -> Moment (Event b)) -> AddHandler a -> AddHandler b
- compile :: MomentIO () -> IO EventNetwork
- data MomentIO a
- module Control.Event.Handler
- fromAddHandler :: AddHandler a -> MomentIO (Event a)
- fromChanges :: a -> AddHandler a -> MomentIO (Behavior a)
- fromPoll :: IO a -> MomentIO (Behavior a)
- reactimate :: Event (IO ()) -> MomentIO ()
- data Future a
- reactimate' :: Event (Future (IO ())) -> MomentIO ()
- changes :: Behavior a -> MomentIO (Event (Future a))
- imposeChanges :: Behavior a -> Event () -> Behavior a
- execute :: Event (MomentIO a) -> MomentIO (Event a)
- liftIOLater :: IO () -> MomentIO ()
- module Control.Monad.IO.Class
- interpretFrameworks :: (Event a -> MomentIO (Event b)) -> [Maybe a] -> IO [Maybe b]
- newEvent :: MomentIO (Event a, Handler a)
- mapEventIO :: (a -> IO b) -> Event a -> MomentIO (Event b)
- newBehavior :: a -> MomentIO (Behavior a, Handler a)
- data EventNetwork
- actuate :: EventNetwork -> IO ()
- pause :: EventNetwork -> IO ()
- getSize :: EventNetwork -> IO Int
Synopsis
Connect to the outside world by building EventNetwork
s
and running them.
Simple use
interpretAsHandler :: (Event a -> Moment (Event b)) -> AddHandler a -> AddHandler b Source #
Simple way to write a single event handler with functional reactive programming.
Overview
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 contrast, 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
MomentIO
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 :: MomentIO () 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 behavior1 <- accumB ... let ... event15 = union event13 event14 -- output: animate some event occurrences 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. - Use
compile
to put everything together in anEventNetwork
s and useactuate
to start handling events.
Building event networks with input/output
Core functions
compile :: MomentIO () -> IO EventNetwork Source #
Compile the description of an event network
into an EventNetwork
that you can actuate
, pause
and so on.
The MomentIO
monad is used to add inputs and outputs
to an event network.
Instances
MonadFix MomentIO Source # | |
Defined in Reactive.Banana.Types | |
MonadIO MomentIO Source # | |
Defined in Reactive.Banana.Types | |
Applicative MomentIO Source # | |
Functor MomentIO Source # | |
Monad MomentIO Source # | |
MonadMoment MomentIO Source # | |
Defined in Reactive.Banana.Types liftMoment :: Moment a -> MomentIO a Source # | |
Monoid a => Monoid (MomentIO a) Source # | |
Semigroup a => Semigroup (MomentIO a) Source # | |
module Control.Event.Handler
fromAddHandler :: AddHandler a -> MomentIO (Event 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 -> MomentIO (Behavior 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 -> MomentIO (Behavior 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 (IO ()) -> MomentIO () 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.
Fortunately, 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.
The Future
monad is just a helper type for the changes
function.
A value of type Future a
is only available in the context
of a reactimate
but not during event processing.
reactimate' :: Event (Future (IO ())) -> MomentIO () Source #
Output.
Execute the IO
action whenever the event occurs.
This version of reactimate
can deal with values obtained
from the changes
function.
changes :: Behavior a -> MomentIO (Event (Future a)) Source #
Output,
return an Event
that is adapted to the changes of a Behavior
.
Remember that semantically, a Behavior
is a function Behavior a = Time -> a
.
This means that a Behavior does not have a notion of "changes" associated with it.
For instance, the following Behaviors are equal:
stepper 0 [] = stepper 0 [(time1, 0), (time2, 0)] = stepper 0 $ zip [time1,time2..] (repeat 0)
In principle, to perform IO actions with the value of a Behavior,
one has to sample it using an Event
and the apply
function.
However, in practice, Behaviors are usually step functions. For reasons of efficiency, the library provides a way to obtain an Event that mostly coincides with the steps of a Behavior, so that sampling is only done at a few select points in time. The idea is that
changes =<< stepper x e = return e
Please use changes
only in a ways that do not distinguish
between the different expressions for the same Behavior above.
Note that the value of the event is actually the new value,
i.e. that value slightly after this point in time. (See the documentation of stepper
).
This is more convenient.
However, the value will not become available until after event processing is complete;
this is indicated by the type Future
.
It can be used only in the context of reactimate'
.
Note: If you need a variant of the changes
function that does not
have the additional Future
type, then the following code snippet
may be useful:
plainChanges :: Behavior a -> MomentIO (Event a) plainChanges b = do (e, handle) <- newEvent eb <- changes b reactimate' $ (fmap handle) <$> eb return e
However, this approach is not recommended, because the result Event
will occur slightly later than the event returned by changes
.
In fact, there is no guarantee whatsoever about what slightly means
in this context. Still, it is useful in some cases.
execute :: Event (MomentIO a) -> MomentIO (Event a) Source #
Dynamically add input and output to an existing event network.
Note: You can perform IO
actions here, which is useful if you want
to register additional event handlers dynamically.
However, if two arguments to execute
occur simultaneously,
then the order in which the IO
therein are executed is unspecified.
For instance, in the following code
example e = do e1 <- execute (liftIO (putStrLn "A") <$ e) e2 <- execute (liftIO (putStrLn "B") <$ e) return (e1,e2)
it is unspecified whether A
or B
are printed first.
Moreover, if the result Event
of this function has been garbage collected,
it may also happen that the actions are not executed at all.
In the example above, if the events e1
and e2
are not used any further,
then it can be that neither A
nor B
will be printed.
If your main goal is to reliably turn events into IO
actions,
use the reactimate
and reactimate'
functions instead.
liftIOLater :: IO () -> MomentIO () Source #
module Control.Monad.IO.Class
Utility functions
This section collects a few convience functions built from the core functions.
interpretFrameworks :: (Event a -> MomentIO (Event b)) -> [Maybe a] -> IO [Maybe b] Source #
Interpret an event processing function by building an EventNetwork
and running it. Useful for testing, but uses MomentIO
.
See interpret
for a plain variant.
newEvent :: MomentIO (Event 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
.
mapEventIO :: (a -> IO b) -> Event a -> MomentIO (Event b) Source #
Build a new Event
that contains the result
of an IO computation.
The input and result events will not be simultaneous anymore,
the latter will occur later than the former.
Please use the fmap
for Event
if your computation is pure.
Implementation:
mapEventIO f e1 = do (e2, handler) <- newEvent reactimate $ (\a -> f a >>= handler) <$> e1 return e2
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. (In a future version, it will also 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.