reactive-banana and behavior lag, among other things
backstory: i've been using the reactive-banana FRP library to handle the i/o for my haskell stuff, because if you recall i spent one of these two-week projects hacking together a haskell-style i/o management setup that i kept tying myself into knots with and eventually somebody was like "this sounds like you're reinventing the concept of FRP and you should maybe use one of these libraries". then i got wrapped up in trying to comprehend how reactive-banana works and is expected to be used, and how you can practically use it to do things. it's not exactly the most clear, so i figure it's worth it to post about my HARD-EARNED UNDERSTANDING of how it works.
this post assumes that you basically understand haskell and that you've used reactive-banana enough to have some problems with it.
a brief summary of the basic intended code flow for reactive-banana:
the two main modules you'll be using are
the core functions in
it wasn't really immediately clear to me how those fit together in practice, despite the fairly clear types. you start with
and now you have what's effectively a read/write pair.
so for example, i'm using
which uses
the other functions are about making event streams do anything: you use
outside of that do-notation block, the only thing that can really be done with that
notably, since
so that's
one thing that tripped me up initially is that i say there "you can sample a Behavior at any point to get the value in it", and looking at the functions it seems like you might want to use something like these:
but generally those just get you the initial value of the behavior, and never change. reactive-banana is very tricksy about how it works internally, and the types aren't a lot of guidance. those two functions have identical types, but the documentation for both goes into some specifics for how those work in different ways based on the mfix instance for the two
when i said earlier that a
and those will generally do what you want (sample at the event occurrence in the stream)
so here is where we reach the actual meat of this post
the
where
so in essence what's happening here goes like this: when an event happens, first its own transformations are run: an event happening in
and that's fine, until you want to read the new state.
here's some actual, non-example code that might help:
GLFW provides
(<%> is
if you have an event stream
this means that if you want an event stream of behavior updates, you can use only the event stream used to construct the behavior; you can't sample from the behavior at the time of the update. this might seem obvious, but it means that if you have some source event stream
this might seem like a problem with an easy solution -- if you want a real-time update of event values, just use the event stream that you'll definitely already have, right? except, as mentioned above,
for me this came up when i was working on form ui. i wanted a submit button to actually perform the form action, but i also wanted to see a stream of events that corresponded to every time the form was updated (to update its render state, or just to make the data available for other purposes, like e.g., to update a character creator display with the currently-selected values). but my code was only exposing a
replacing the
let's get into my actual form code
so this is what a form looks like as a data structure. that applicative instance is important, because it lets you do things like
to get a
(this, incidentally, copies this GADT applicative technique from
in the guts of my form code, there's a
(that's px on screen (
but for a while
this required writing several new combinators.
first, i found the type of
then i realized it's possible to do a kind of fold through the event stream.
another thing is that
where
this brings us all the way to the faux-ap:
aka "this is why Event isn't an Applicative". however, for my purposes, this is applicative enough to run the
there's more general form architecture stuff i could get into also (for a long time i was struggling with how to make event networks that didn't have to recursively include every possible event state for e.g., menus that might open up other menus) but this post is long enough and if anybody is interested i could write it up later.
this post assumes that you basically understand haskell and that you've used reactive-banana enough to have some problems with it.
a brief summary of the basic intended code flow for reactive-banana:
the two main modules you'll be using are
Reactive.Banana.Framework and Reactive.Banana.Combinatiors. the former lets you turn IO events happening in the real world into event streams managed by reactive-banana, and the latter provides tools to alter, filter, and combine event streams to perform IO within your FRP event network. generally speaking, all 'running' event code exists in a handler monad, MomentIO (or Moment; there are two).the core functions in
Reactive.Banana.Framework arenewtype AddHandler a = AddHandler { register :: Handler a -> IO (IO ()) }
type Handler a = a -> IO ()
newAddHandler :: IO (AddHandler a, Handler a)
fromAddHandler :: AddHandler a -> MomentIO (Event a)
Input, obtain an Event from an AddHandler.
reactimate :: Event (IO ()) -> MomentIO ()
Output. Execute the IO action whenever the event occurs.
compile :: MomentIO () -> IO EventNetwork
Compile the description of an event network into an EventNetwork that you can actuate, pause and so on.
actuate :: EventNetwork -> IO ()
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 ()
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.it wasn't really immediately clear to me how those fit together in practice, despite the fairly clear types. you start with
newAddHandler:(addHandler, fire) <- newAddHandlerand now you have what's effectively a read/write pair.
fire (full type a -> IO ()) runs in IO and writes a value a to the event stream. meanwhile, addHandler can be used with fromAddHandler when inside a MomentIO to get an event stream. so fire populates an event stream and addHandler can read from that same event stream inside a handler.so for example, i'm using
GLFW for my input event pump, and it has a bunch of callback functions that you can run IO in to handle those specific events. so what i have is a function like this:setRawCallbacks :: Window os c ds -> ContextT GLFW.Handle os IO (AddHandler RawGLFW)
setRawCallbacks win = do
(addHandler, fire) <- liftIO $ newAddHandler
GLFW.setMouseButtonCallback win $ Just $ \button state mod -> do
fire $ MouseButtonEvent button state mod
GLFW.setCursorPosCallback win $ Just $ \x y -> do
fire $ CursorPosEvent x y
GLFW.setKeyCallback win $ Just $ \key i s mod -> do
fire $ KeyAction key i s mod
GLFW.setCharCallback win $ Just $ \char -> do
fire $ CharAction char
GLFW.setWindowCloseCallback win $ Just $ do
fire $ WindowClose
return addHandlerwhich uses
newAddHandler to set all those GLFW callbacks to IO that just fires the corresponding event, which turns that IO into an event stream that i can access later through the returned addHandler.the other functions are about making event streams do anything: you use
fromAddHandler to extract the event stream from some raw input handler, and consequently reactimate is called inside or at the end of a handler block, to construct a MomentIO value that will do something. what that means is that your event inputs and outputs are solely usable inside a MomentIO, and kind of establishes that type as a wrapper for your event-processing logic.outside of that do-notation block, the only thing that can really be done with that
MomentIO handler chunk is to call compile on it in IO code; that creates the final EventNetwork value. once you have that, the event network can be actuated or paused as needed, which turns it on and off and makes the entire system actually run and start processing input and providing output.notably, since
actuate and pause are IO events, if you have an Event (IO ()) stream it's entirely valid for it to start or stop other event networks, including its own event network.so that's
Reactive.Banana.Framework in theory. there are some thorns i'll get to below.Reactive.Banana.Combinators is all about how you can transform an Event a while inside a MomentIO monad. generally, the important thing to note is that Events are functors but not applicatives -- you can't combine two arbitrary event streams because their event occurrences will generally not be occurring at the same time, and there's no state-tracking for things like "the last event to happen". however, they do provide Behavior a, which is essentially a state-retaining value that you can read at any time (while inside a Moment, which itself is defined as 'code that will execute at the same moment an event occurrence happens'). the library provides two functions for creating behaviors from event streams: stepper :: MonadMoment m => a -> Event a -> m (Behavior a) and accumB :: MonadMoment m => a -> Event (a -> a) -> m (Behavior a), where stepper directly turns an event stream into a behavior (with an initial value), and accumB takes an event stream of state updates and applies them to the prior value.one thing that tripped me up initially is that i say there "you can sample a Behavior at any point to get the value in it", and looking at the functions it seems like you might want to use something like these:
valueB :: MonadMoment m => Behavior a -> m a
valueBLater :: MonadMoment m => Behavior a -> m abut generally those just get you the initial value of the behavior, and never change. reactive-banana is very tricksy about how it works internally, and the types aren't a lot of guidance. those two functions have identical types, but the documentation for both goes into some specifics for how those work in different ways based on the mfix instance for the two
Moment monads. it's pretty confusing.when i said earlier that a
Moment is in part defined as 'code that will execute at the same time as an event occurrence', it turns out that that's... complicated in ways i don't really understand, and when using valueB or valueBLater, it's easy to end up basically getting a value at the moment at which the event network is compiled, and then using that as a static value afterwards, rather than doing what you generally want, which is to use an event stream to figure out when you should sample the behavior. they provide other functions that take an event stream explicitly:apply :: Behavior (a -> b) -> Event a -> Event b
(<@>) :: Behavior (a -> b) -> Event a -> Event band those will generally do what you want (sample at the event occurrence in the stream)
so here is where we reach the actual meat of this post
the
reactive-banana docs mention this a lot: there's a MonadFix instance for Moment and MomentIO. this means it's possible to make mutually-recursive event/behavior values, which is needed for basically any non-trivial event code. this looks like this:\evs -> mdo
let updates = toggleInto <$> click boxVals evs <%> state
state <- stepper initialToggles updates
return (state, updates)where
updates uses state to determine what the value of its event should be, and state uses updates to update its own value. this is fine, because, as the docs say:Note: The smaller-than-sign in the comparison timex < time2 means that at time time2 == timex, the value of the Behavior will still be the previous value.
so in essence what's happening here goes like this: when an event happens, first its own transformations are run: an event happening in
evs runs the toggleInto <$> click boxVals evs <%> state part to get a corresponding event occuring at the same instant in the updates event stream. and second, the Behavior values that update based on that event stream are updated, and state gets its value updated. so, during every event interval, the value of state is its 'old' value, not its 'new' value -- this is what makes value recursion possible, and lets these values be mutually dependent, since updates is always reading older state in order to generate the new state.and that's fine, until you want to read the new state.
here's some actual, non-example code that might help:
GLFW provides
CursorPosEvent, which is a mousemove with pixel coords attached. it also provides a MouseButtonEvent, which is a click event without pixel coords attached. so in order to get more useful input events, i transform the RawGFWL values into FauxGLFW values, which gloss over a lot of the details i don't yet care about and also tracks state so that when there's a click it comes with the pixel coords attached. this works by introducing an InputState behavior that's updated on cursor move, and is sampled on events in order to provide that statedata InputState = InputState
{ mousePosition :: V2 Int
}
getFauxEvStream :: AddHandler RawGLFW -> MomentIO (Event FauxGLFW)
getFauxEvStream addRawGLFWHandler = do
rawEv <- fromAddHandler addRawGLFWHandler -- Event RawGLFW
windowState <- accumB (InputState (V2 0 0))
$ filterJust $ (\ev -> case ev of
CursorPosEvent x y -> Just (\s -> s { mousePosition = floor <$> V2 x y })
_ -> Nothing)
<$> rawEv
return $ filterJust $ convertGLFW <$> rawEv <%> windowState
convertGLFW :: RawGLFW -> InputState -> Maybe FauxGLFW
convertGLFW ev pos = case ev of
MouseButtonEvent button state _ -> case (,) state <$> mapButton button of
Just (MouseButtonState'Pressed, side) -> Just $ MouseDown side (mousePosition pos)
Just (MouseButtonState'Released, side) -> Just $ MouseUp side (mousePosition pos)
_ -> Nothing
KeyAction k _ state _ -> case state of
KeyState'Pressed -> Just $ KeyDown k
KeyState'Released -> Just $ KeyUp k
KeyState'Repeating -> Just $ KeyRepeat k
CharAction c -> Just $ Typed c
CursorPosEvent x y -> Just $ MouseMove $ round <$> V2 x y
WindowClose -> Just Close
data RawGLFW
= MouseButtonEvent MouseButton MouseButtonState ModifierKeys
| CursorPosEvent Double Double
| KeyAction Key Int KeyState ModifierKeys
| CharAction Char
| WindowClose
deriving (Eq, Ord, Show, Read)
data Button = LeftClick | RightClick
deriving (Eq, Ord, Enum, Bounded, Show, Read)
data FauxGLFW
= MouseDown Button (V2 Int)
| MouseUp Button (V2 Int)
| MouseMove (V2 Int)
| KeyDown Key
| KeyUp Key
| KeyRepeat Key
| Typed Char
| Close
deriving (Eq, Ord, Show, Read)(<%> is
(<%>) :: Event (a -> b) -> Behavior a -> Event b, which is a fairly straightforward implementation from reactive-banana's <@>)if you have an event stream
evs :: Event a, from any source, (including if it happens to be recursively-defined sampling from the below state behavior, which is not shown in this example), then you can do this:\evs -> do -- evs :: Event a
state <- stepper z evs -- MonadMoment m => m (Behavior a)
let evsAgain = (const <$> state) <@> evs -- evsAgain :: Event aevsAgain will have each occurrence happening at the same instant as an occurrence in evs, but evsAgain will contain the prior value, as it's sampling from state before it's being updated by the evs event pump (in stepper). this in essence shifts all the events one 'occurrence' back.this means that if you want an event stream of behavior updates, you can use only the event stream used to construct the behavior; you can't sample from the behavior at the time of the update. this might seem obvious, but it means that if you have some source event stream
Event a that gets reshaped into Event b and Behavior c and updates both at the same occurrence, then you can never see the updated behavior state from the event (e.g., using <@>)this might seem like a problem with an easy solution -- if you want a real-time update of event values, just use the event stream that you'll definitely already have, right? except, as mentioned above,
Behaviors are Applicatives, but Events are not.for me this came up when i was working on form ui. i wanted a submit button to actually perform the form action, but i also wanted to see a stream of events that corresponded to every time the form was updated (to update its render state, or just to make the data available for other purposes, like e.g., to update a character creator display with the currently-selected values). but my code was only exposing a
Behavior formstate value, so while i could go filterE changesState ev @> formBehavior, to sample from the form state behavior on every event that changed the form's state, all those updates would lag one occurrence behind, since the actual update to the behavior would only happen after the event was processed.replacing the
Behavior with an Event was not precisely trivial.let's get into my actual form code
data Form a where
Pure :: a -> Form a -- does not generate any layout element
App :: Form (x -> a) -> Form x -> Form a
Static :: String -> a -> Form a -- generates a fixed, static layout element
Checkboxes :: [(String, a)] -> (a -> Bool) -> Form [a] -- options, initially selected
Radios :: [(String, a)] -> Int -> Form a -- options, initially selected
Textbox :: (String -> Either String a) -> Int -> String -> Maybe a -> Form (Maybe a) -- validator, length limit, initial display value, initial value; renders a textbox w/ an error display; the value returned is Nothing if the value does not currently validate
Label :: String -> Form a -> Form a -- adds a fieldset label around an existing form
instance Functor Form where
fmap f v = case v of
Pure a -> Pure $ f a
App fa fv -> App (fmap (f .) fa) fv
Static l a -> Static l $ f a
Checkboxes vs sel -> App (pure f) v
Radios vs i-> Radios ((\(l, v) -> (l, f v)) <$> vs) i
Textbox val lim l d -> App (pure f) v
Label l form -> Label l (f <$> form)
instance Applicative Form where
pure x = Pure x
f <*> a = App f aso this is what a form looks like as a data structure. that applicative instance is important, because it lets you do things like
(,)
<$> Label "animal" (Radios [("dog", Dog), ("cat", Cat), ("owl", Owl), ("toad", Toad), ("lizard", Lizard)] 0)
<*> Label "name" (Textbox Right 10 "" Nothing)to get a
Form (Animal, String).(this, incidentally, copies this GADT applicative technique from
reform, which is how i initially learned of it. apparently if you know category theory stuff (i don't) this is in some way similar or identical to coyoneda.)in the guts of my form code, there's a
constructForm function that takes a form and does all the stuff needed to be done to lay out the form onscreen and generate render events to update the rendered bits and properly transform and filter the GLFW event stream into event streams of form value updates. and within that function there's an internal helper function i've called go that has the following type:go :: MonadMoment m =>
(V2 Int, Int) ->
Form x ->
( (V2 Int, Int)
, ([RenderUpdate os], Event FauxGLFW -> m (Event x, Behavior x, Event [RenderUpdate os]))
)(that's px on screen (
::V2 Int), render index currently used (::Int), and form (::Form x) as arguments; and output is updated px on screen (::V2 Int), render index to use (::Int), a list of initial render updates to draw the basic form value (:: [RenderUpdate os]), plus a function that takes the GLFW event stream and returns the update event stream, a behavior state, and a render update stream (:: MonadMoment m => Event FauxGLFW -> m (Event x, Behavior x, Event [RenderUpdate os])). yeah that's kind of messy but that's real code for you)but for a while
go wasn't returning Event x, just Behavior x, because i couldn't figure out how to write the case for App: getting an Event a given App (Form x -> a) (Form x)this required writing several new combinators.
reactive-banana generally provides only primitives that cannot be written using any other primitives, with only a few exceptions, and that means that there are a lot more complex combinators that you have to figure out are possible all by yourself.first, i found the type of
<@> to be kind of weird, so i flipped it around some:eapply :: Behavior a -> Event (a -> b) -> Event b
eapply b ef = (flip ($) <$> b) <@> ef
infixl 4 <%>
(<%>) :: Event (a -> b) -> Behavior a -> Event b
(<%>) = flip eapplythen i realized it's possible to do a kind of fold through the event stream.
accumE is defined with a -> a functions, so basically with an update function. so e.g., if you have updateCamera :: CameraChange -> Camera -> Camera you could updateCamera <$> cameraChangeEvs to get Event (Camera -> Camera) and then use that with accumE to get an event stream of updated camera values; this is just a streamlined version of thatfoldE :: MonadMoment m => (a -> b -> b) -> b -> Event a -> m (Event b)
foldE f z ev = accumE z (f <$> ev)another thing is that
reactive-banana only lets you merge events of the same type. there's unionWith :: (a -> a -> a) -> Event a -> Event a -> Event a, (where the function is needed to handle situations where the two event streams occur at the same time -- each event stream needs to have its events occurring at distinct 'instants', so the function is only called if two events occur at the exact same 'instant'). the author of the library has mentioned using Either to merge disparate streams, except that was in an older version where simultaneous events were allowed. now that they're not allowed, Either isn't actually sufficient. so i wrote:unionDisparate :: (Beither a b -> c) -> Event a -> Event b -> Event c
unionDisparate f as bs = f <$> unionWith
(\a b -> case (a, b) of
(Le a', Ri b') -> Bo a' b'
_ -> error "bad beither stream")
(Le <$> as)
(Ri <$> bs)where
Beither a b is exactly what it looks like.this brings us all the way to the faux-ap:
updateOneOrBoth :: Beither a b -> (a, b) -> (a, b)
updateOneOrBoth be (a, b) = case be of
Le a' -> (a', b)
Ri b' -> (a, b')
Bo a' b' -> (a', b')
apEvent :: forall m a b. MonadMoment m => (a -> b) -> a -> Event (a -> b) -> Event a -> m (Event b)
apEvent f a ef ea = mergeAp beitherStream
where
beitherStream :: Event (Beither (a -> b) a)
beitherStream = unionDisparate id ef ea
mergeAp :: MonadMoment m => Event (Beither (a -> b) a) -> m (Event b)
mergeAp = (fmap . fmap $ uncurry ($)) . foldE updateOneOrBoth (f, a)aka "this is why Event isn't an Applicative". however, for my purposes, this is applicative enough to run the
App case for my form values, and thus to get an event stream of form updates that doesn't sample from an outdated behavior.there's more general form architecture stuff i could get into also (for a long time i was struggling with how to make event networks that didn't have to recursively include every possible event state for e.g., menus that might open up other menus) but this post is long enough and if anybody is interested i could write it up later.