{----------------------------------------------------------------------------- reactive-banana ------------------------------------------------------------------------------} {-# LANGUAGE Rank2Types #-} module Reactive.Banana.Frameworks ( -- * Synopsis -- | Connect to the outside world by building 'EventNetwork's -- and running them. -- * Simple use interpretAsHandler, -- * Overview -- $build -- * Building event networks with input/output -- ** Core functions compile, MomentIO, module Control.Event.Handler, fromAddHandler, fromChanges, fromPoll, reactimate, Future, reactimate', changes, -- $changes imposeChanges, execute, liftIOLater, -- $liftIO module Control.Monad.IO.Class, -- ** Utility functions -- | This section collects a few convience functions -- built from the core functions. interpretFrameworks, newEvent, mapEventIO, newBehavior, -- * Running event networks EventNetwork, actuate, pause, getSize, ) where import Control.Event.Handler import Control.Monad import Control.Monad.IO.Class import Data.IORef import Reactive.Banana.Combinators import qualified Reactive.Banana.Prim.High.Combinators as Prim import Reactive.Banana.Types {----------------------------------------------------------------------------- Documentation ------------------------------------------------------------------------------} {-$build 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 an 'EventNetwork's and use 'actuate' to start handling events. -} {----------------------------------------------------------------------------- Combinators ------------------------------------------------------------------------------} {- | 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. -} reactimate :: Event (IO ()) -> MomentIO () reactimate :: Event (IO ()) -> MomentIO () reactimate = forall a. Moment a -> MomentIO a MIO forall b c a. (b -> c) -> (a -> b) -> a -> c . Event (Future (IO ())) -> Moment () Prim.addReactimate forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b. (a -> b) -> Event a -> Event b Prim.mapE forall (m :: * -> *) a. Monad m => a -> m a return forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Event a -> Event a unE -- | Output. -- Execute the 'IO' action whenever the event occurs. -- -- This version of 'reactimate' can deal with values obtained -- from the 'changes' function. reactimate' :: Event (Future (IO ())) -> MomentIO () reactimate' :: Event (Future (IO ())) -> MomentIO () reactimate' = forall a. Moment a -> MomentIO a MIO forall b c a. (b -> c) -> (a -> b) -> a -> c . Event (Future (IO ())) -> Moment () Prim.addReactimate forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b. (a -> b) -> Event a -> Event b Prim.mapE forall a. Future a -> Future a unF forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Event a -> Event a unE -- | 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. fromAddHandler ::AddHandler a -> MomentIO (Event a) fromAddHandler :: forall a. AddHandler a -> MomentIO (Event a) fromAddHandler = forall a. Moment a -> MomentIO a MIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a. Event a -> Event a E forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. AddHandler a -> Moment (Event a) Prim.fromAddHandler -- | 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. fromPoll :: IO a -> MomentIO (Behavior a) fromPoll :: forall a. IO a -> MomentIO (Behavior a) fromPoll = forall a. Moment a -> MomentIO a MIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a. Behavior a -> Behavior a B forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. IO a -> Moment (Behavior a) Prim.fromPoll -- | Input, -- obtain a 'Behavior' from an 'AddHandler' that notifies changes. -- -- This is essentially just an application of the 'stepper' combinator. fromChanges :: a -> AddHandler a -> MomentIO (Behavior a) fromChanges :: forall a. a -> AddHandler a -> MomentIO (Behavior a) fromChanges a initial AddHandler a changes = do Event a e <- forall a. AddHandler a -> MomentIO (Event a) fromAddHandler AddHandler a changes forall (m :: * -> *) a. MonadMoment m => a -> Event a -> m (Behavior a) stepper a initial Event a e -- | 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''. changes :: Behavior a -> MomentIO (Event (Future a)) changes :: forall a. Behavior a -> MomentIO (Event (Future a)) changes = forall (m :: * -> *) a. Monad m => a -> m a return forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Event a -> Event a E forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b. (a -> b) -> Event a -> Event b Prim.mapE forall a. Future a -> Future a F forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Behavior a -> Event (Future a) Prim.changesB forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Behavior a -> Behavior a unB {- $changes 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. -} -- | Impose a different sampling event on a 'Behavior'. -- -- The 'Behavior' will have the same values as before, but the event returned -- by the 'changes' function will now happen simultaneously with the -- imposed event. -- -- Note: This function is useful only in very specific circumstances. imposeChanges :: Behavior a -> Event () -> Behavior a imposeChanges :: forall a. Behavior a -> Event () -> Behavior a imposeChanges Behavior a b Event () e = forall a. Behavior a -> Behavior a B forall a b. (a -> b) -> a -> b $ forall a. Behavior a -> Event () -> Behavior a Prim.imposeChanges (forall a. Behavior a -> Behavior a unB Behavior a b) (forall a b. (a -> b) -> Event a -> Event b Prim.mapE (forall a b. a -> b -> a const ()) (forall a. Event a -> Event a unE Event () e)) {- | 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. -} execute :: Event (MomentIO a) -> MomentIO (Event a) execute :: forall a. Event (MomentIO a) -> MomentIO (Event a) execute = forall a. Moment a -> MomentIO a MIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a. Event a -> Event a E forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Event (Moment a) -> Moment (Event a) Prim.executeE forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b. (a -> b) -> Event a -> Event b Prim.mapE forall a. MomentIO a -> Moment a unMIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. Event a -> Event a unE -- $liftIO -- -- > liftIO :: Frameworks t => IO a -> Moment t a -- -- Lift an 'IO' action into the 'Moment' monad. -- | Lift an 'IO' action into the 'Moment' monad, -- but defer its execution until compilation time. -- This can be useful for recursive definitions using 'MonadFix'. liftIOLater :: IO () -> MomentIO () liftIOLater :: IO () -> MomentIO () liftIOLater = forall a. Moment a -> MomentIO a MIO forall b c a. (b -> c) -> (a -> b) -> a -> c . IO () -> Moment () Prim.liftIOLater -- | Compile the description of an event network -- into an 'EventNetwork' -- that you can 'actuate', 'pause' and so on. compile :: MomentIO () -> IO EventNetwork compile :: MomentIO () -> IO EventNetwork compile = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap EventNetwork -> EventNetwork EN forall b c a. (b -> c) -> (a -> b) -> a -> c . Moment () -> IO EventNetwork Prim.compile forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. MomentIO a -> Moment a unMIO {----------------------------------------------------------------------------- Running event networks ------------------------------------------------------------------------------} -- | Data type that represents a compiled event network. -- It may be paused or already running. newtype EventNetwork = EN { EventNetwork -> EventNetwork unEN :: Prim.EventNetwork } -- | Actuate an event network. -- The inputs will register their event handlers, so that -- the networks starts to produce outputs in response to input events. actuate :: EventNetwork -> IO () actuate :: EventNetwork -> IO () actuate = EventNetwork -> IO () Prim.actuate forall b c a. (b -> c) -> (a -> b) -> a -> c . EventNetwork -> EventNetwork unEN -- | 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. pause :: EventNetwork -> IO () pause :: EventNetwork -> IO () pause = EventNetwork -> IO () Prim.pause forall b c a. (b -> c) -> (a -> b) -> a -> c . EventNetwork -> EventNetwork unEN -- | PROVISIONAL. -- Measure of the number of events in the event network. -- Useful for understanding space usage. getSize :: EventNetwork -> IO Int getSize :: EventNetwork -> IO Int getSize = EventNetwork -> IO Int Prim.getSize forall b c a. (b -> c) -> (a -> b) -> a -> c . EventNetwork -> EventNetwork unEN {----------------------------------------------------------------------------- Utilities ------------------------------------------------------------------------------} -- | 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'. newEvent :: MomentIO (Event a, Handler a) newEvent :: forall a. MomentIO (Event a, Handler a) newEvent = do (AddHandler a addHandler, Handler a fire) <- forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a. IO (AddHandler a, Handler a) newAddHandler Event a e <- forall a. AddHandler a -> MomentIO (Event a) fromAddHandler AddHandler a addHandler forall (m :: * -> *) a. Monad m => a -> m a return (Event a e,Handler a fire) -- | Build a 'Behavior' together with an 'IO' action that can -- update this behavior with new values. -- -- Implementation: -- -- > newBehavior a = do -- > (e, fire) <- newEvent -- > b <- stepper a e -- > return (b, fire) newBehavior :: a -> MomentIO (Behavior a, Handler a) newBehavior :: forall a. a -> MomentIO (Behavior a, Handler a) newBehavior a a = do (Event a e, Handler a fire) <- forall a. MomentIO (Event a, Handler a) newEvent Behavior a b <- forall (m :: * -> *) a. MonadMoment m => a -> Event a -> m (Behavior a) stepper a a Event a e forall (m :: * -> *) a. Monad m => a -> m a return (Behavior a b, Handler a fire) -- | 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 mapEventIO :: (a -> IO b) -> Event a -> MomentIO (Event b) mapEventIO :: forall a b. (a -> IO b) -> Event a -> MomentIO (Event b) mapEventIO a -> IO b f Event a e1 = do (Event b e2, Handler b handler) <- forall a. MomentIO (Event a, Handler a) newEvent Event (IO ()) -> MomentIO () reactimate forall a b. (a -> b) -> a -> b $ (a -> IO b f forall (m :: * -> *) a b c. Monad m => (a -> m b) -> (b -> m c) -> a -> m c >=> Handler b handler) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Event a e1 forall (m :: * -> *) a. Monad m => a -> m a return Event b e2 {----------------------------------------------------------------------------- Simple use ------------------------------------------------------------------------------} -- | Interpret an event processing function by building an 'EventNetwork' -- and running it. Useful for testing, but uses 'MomentIO'. -- See 'interpret' for a plain variant. interpretFrameworks :: (Event a -> MomentIO (Event b)) -> [Maybe a] -> IO [Maybe b] interpretFrameworks :: forall a b. (Event a -> MomentIO (Event b)) -> [Maybe a] -> IO [Maybe b] interpretFrameworks Event a -> MomentIO (Event b) f [Maybe a] xs = do IORef (Maybe b) output <- forall a. a -> IO (IORef a) newIORef forall a. Maybe a Nothing (AddHandler a addHandler, Handler a runHandlers) <- forall a. IO (AddHandler a, Handler a) newAddHandler EventNetwork network <- MomentIO () -> IO EventNetwork compile forall a b. (a -> b) -> a -> b $ do Event a e1 <- forall a. AddHandler a -> MomentIO (Event a) fromAddHandler AddHandler a addHandler Event b e2 <- Event a -> MomentIO (Event b) f Event a e1 Event (IO ()) -> MomentIO () reactimate forall a b. (a -> b) -> a -> b $ forall a. IORef a -> a -> IO () writeIORef IORef (Maybe b) output forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a. a -> Maybe a Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Event b e2 EventNetwork -> IO () actuate EventNetwork network forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) forM [Maybe a] xs forall a b. (a -> b) -> a -> b $ \Maybe a x -> do case Maybe a x of Maybe a Nothing -> forall (m :: * -> *) a. Monad m => a -> m a return forall a. Maybe a Nothing Just a x -> do Handler a runHandlers a x Maybe b b <- forall a. IORef a -> IO a readIORef IORef (Maybe b) output forall a. IORef a -> a -> IO () writeIORef IORef (Maybe b) output forall a. Maybe a Nothing forall (m :: * -> *) a. Monad m => a -> m a return Maybe b b -- | Simple way to write a single event handler with -- functional reactive programming. interpretAsHandler :: (Event a -> Moment (Event b)) -> AddHandler a -> AddHandler b interpretAsHandler :: forall a b. (Event a -> Moment (Event b)) -> AddHandler a -> AddHandler b interpretAsHandler Event a -> Moment (Event b) f AddHandler a addHandlerA = forall a. (Handler a -> Future (IO ())) -> AddHandler a AddHandler forall a b. (a -> b) -> a -> b $ \Handler b handlerB -> do EventNetwork network <- MomentIO () -> IO EventNetwork compile forall a b. (a -> b) -> a -> b $ do Event a e1 <- forall a. AddHandler a -> MomentIO (Event a) fromAddHandler AddHandler a addHandlerA Event b e2 <- forall (m :: * -> *) a. MonadMoment m => Moment a -> m a liftMoment (Event a -> Moment (Event b) f Event a e1) Event (IO ()) -> MomentIO () reactimate forall a b. (a -> b) -> a -> b $ Handler b handlerB forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Event b e2 EventNetwork -> IO () actuate EventNetwork network forall (m :: * -> *) a. Monad m => a -> m a return (EventNetwork -> IO () pause EventNetwork network)