Wednesday, July 16, 2014

reactive-banana anti-tutorial

This is not a tutorial. I have never used reactive-banana nor any other FRP library. And that's the point: in this post, once again1, I will reveal my thought process as I learn this library.

Motivation


A recent tutorial called The introduction to Reactive Programming you've been missing made me realize that FRP is no longer a niche technique used by a subset of the functional programming community. Apparently, there's now a manifesto, a javascript library involving Microsoft, a conference... FRP, or at least RP, is clearly a big deal now.

As a member of the functional programming community, I feel like I ought to at least have an opinion on FRP. And of course, if I'm going to learn a reactive library, I will learn one of the Haskell variants, not a Javascript knockoff.

Why not <name-of-alternate-frp-library>?


Because I began by writing the graphics in gloss, whose play interface is based on pure functions. When I looked at sodium and elerea, I realized that I couldn't use them because they expect to be run from IO. When I googled for "gloss frp", I found a package named gloss-banana2 which allows the simple update function (InputEvent → world → world) to be replaced by an unfamiliar-looking reactive-banana type. Just what I need to get started!

forall t. Frameworks t ⇒ Event t Float
                       → Event t InputEvent
                       → Moment t (Behavior t Picture)

I suspect that it's still IO under the hood, and that a similar sodium or elerea wrapper could easily be written, but I'm not yet in a position to write such a wrapper. So reactive-banana it is.

Versions


I have been told that the APIs change a lot from version to version, so for completeness, here are the versions I am using:

ghc-7.8.2
gloss-1.8.2.1
gloss-banana-0.1.0.0 (modified to accept base-4.7.0.0)
reactive-banana-0.7.1.3

edit: Indeed, reactive-banana 1.0 ended up making a significant change to its API, so if you want to follow along, I recommend using reactive-banana-0.9.0.0, the last version which uses the API I am playing with in this post. For what it's worth, I like the 0.9 API better.

Goal


I would like to duplicate the functionality implemented in the javascript tutorial: three labels and four buttons, one of which updates all the labels, while the remaining three update one label each. For simplicity, I'll put the labels on their corresponding buttons.

Since the code is not running under IO, I won't try to make those updates fetch usernames from github, even though I suspect that interfacing with external event sources such as network connections must be a big part of learning FRP. For now, I want to learn the basics, so each update will simply pull the next available entry from an infinite list of integers.

commit 39647e:
I couldn't find any way to center text in gloss :(

First steps: Why so polymorphic?


I need to produce a value of type forall t. Frameworks t ⇒ something something. That's weird, why would they need me to write polymorphic code? Is there more than one "framework" involved?

Looking at the documentation for Frameworks, I learn that the constraint "indicates that we can add input and output to an event network". But then, why are there no typeclass methods for adding those things? Maybe they are just hidden? Looking at the source, I see that no, it really is a typeclass with no methods. Weird.

Still, using polymorphism kind of makes intuitive sense for allowing extra stuff to be added. Consider the Arrow typeclass, for example: it has a method for adding extra (untouched) input and output along your existing transformation of type f a b (if you are unfamiliar with Arrow, think of it as a → b).

first :: f a b → f (a, s) (b, s)

If I was asked to construct an f Int String, and the code who is asking me for this had to embed my f Int String inside a bigger computation, it might very well need something like first to adapt my computation into theirs. If f was not an arrow, then I might have to produce a polymorphic value of type forall s. f (Int, s) (String, s) instead. I assume that gloss-banana requests a polymorphic function for similar reasons.

Compile, Run, and Quit


The next part of the type, Event t Float → Event t InputEvent → something, is straightforward: to assist me in constructing the something, I have access to the reactive-banana representation of typical gloss events: a Float for the passage of time, or an InputEvent representing a keypress or a mouse action. For each of those, gloss typically expects me to modify a "representation of the world" of my choice, and I also need to have a way to represent this world as a gloss Picture. This time, with gloss-banana, I don't get to choose an intermediate representation, I need to produce a something-something Picture directly (a Moment t (Behavior t Picture) to be exact).

At the moment, I just want something which compiles, so let's see if I can ignore the two Event inputs and produce a constant Picture, using something like return or pure. Is Moment or Behavior a Monad or Applicative?

Looking at the documentation, yes, Moment is a Monad and Behavior is an Applicative. Piece of cake, then...

main :: IO ()
main = playBanana (InWindow "Nice Window" (200, 200) (800, 200))
                  white
                  30
                  (\_ _ -> return $ pure $ circle 10)

commit f4c25a:
At least circles are centered!

Well, it worked, but unlike the play from gloss, playBanana doesn't quit when I press ESC. Does reactive-banana have a command to terminate a Moment or a Behavior? Usually a computation which consists of a single return ends immediately, but clearly reactive-banana's monadic composition does not simply consist in executing one computation after the other.

Since I can't find anything with a quit-sounding name in the documentation, my hypothesis is that reactive-banana computations are able to provide values forever, and that it is the user of that computation who decides when to stop asking it for more values. So let's look's look at said user, the source for playBanana:

playBanana display colour frequency mPicture = do
  ...
  playIO display colour frequency ()
    (\      _ → readIORef pictureref)
    (\ ev   _ → () <$ event ev)
    (\ time _ → () <$ tick time)

Okay, so it looks like there was another version of Gloss.play which I did not know about, playIO. I bet play delegates the bulk of the work to playIO, and hardcodes the logic of quitting, probably using exitSuccess. Let's look at the code for play and playIO...

play ... worldHandleEvent ...
 = playWithBackendIO defaultBackendState 
        display backColor simResolution
        worldStart 
        (return . worldToPicture)
        (\event world -> return $ worldHandleEvent event world)
        (\time  world -> return $ worldAdvance     time  world)

playIO = playWithBackendIO defaultBackendState

Now that's weird. play doesn't seem to hardcode ESC to quit, so it must be playWithBackendIO which hardcodes it. Both versions delegate to playWithBackendIO, so both versions should quit on ESC. But the FRP version doesn't. Why? playWithBackendIO is not documented, so there is no "source" button on which I can click to view its source, but its source is available regardless. Like play and playIO before it, playWithBackendIO delegates its work to yet another internal function, createWindow.

I feel like I went deep enough into this ESC rabbit hole already, and that I should focus on the FRP part. I'll simply write my own version of playBanana3, one which abruptly quits on ESC:

playBanana display colour frequency mPicture = do
  ...
  playIO display colour frequency ()
    (\      _ → readIORef pictureref)
    (\ ev   _ → quitOnEsc ev >> () <$ event ev)
    (\ time _ → () <$ tick time)
  where
    quitOnEsc (G.EventKey (G.SpecialKey G.KeyEsc)
                          G.Down _ _) = exitSuccess
    quitOnEsc _                       = return ()

Event to Moment


On the FRP side, I now have a simple computation which ignores all events and always produces the same Picture, a small circle. One of my inputs is an Event t Float; can I display that float? I can easily convert a Float to a Picture...

uscale :: Float -> Picture -> Picture
uscale v = scale v v

renderFloat :: Float -> Picture
renderFloat = uscale 0.2 . text . show

...but how do I lift this Float → Picture function to a Event t Float → Moment t (Behavior t Picture)? From a talk on sodium I saw a while ago, I remember that some FRP systems have two kinds of streams; events and some other kind. Event streams only have values when events occur, while the other kind of stream has a value at every point in time. Scrubbing through that video, I quickly find a slide which lists "Event" and "Behaviour", reminding me that the other kind of stream is called a "behaviour". I also remember that there is a primitive for converting an event stream into a behaviour: when events occur, they have the same value, and when they don't, the behaviour holds the value of the last event. Clearly this implies that we also needs an initial value, to be held before the first event occurs. I hoogle for a -> Event t a -> Behavior t a (it took me a few attempts to remember to add the t), and I obtain (two copies of?) a function called stepper with that exact signature.

main :: IO ()
main = playBanana (InWindow "Nice Window" (200, 200) (800, 200))
                  white
                  30
                  -- Couldn't match type ‘Float’ with ‘Picture’
                  (\floats _ -> return $ stepper 0 floats)

Oh, right, I forgot to call renderFloat. I don't actually have a Float on which to call it, I only have a something something Float. Which is fine, as I can probably fmap through the somethings to reach the Float. I can either fmap over the Behavior I just constructed or over the original Event, I don't think it matters.

main :: IO ()
main = playBanana (InWindow "Nice Window" (200, 200) (800, 200))
                  white
                  30
                  (\floats _ -> return $ fmap renderFloat
                                       $ stepper 0 floats)

Youhoo!

commit ee5dd7:
The float is supposed to be the number of seconds since the last frame,
which should be 1/30 since I asked to be updated 30 times per second.
I think it's a bug in gloss.
edit: silly me, it's not 3.3333..., it's 3.3333e-2.

Sum


Sooner or later, I will need to keep some state between frames. As a simple exercise, can I display the sum of the floats instead of the latest one?

Let's see, I start with a value, then each time I receive an event, I update this value. Does hoogle know of any function with the type s -> (a -> s -> s) -> Event t a -> Behavior t s? Nope. Maybe I can stay inside the world of events, and only convert to behaviour at the end. Does hoogle know of any function of type s -> (a -> s -> s) -> Event t a -> Event t s? Neither. I can't stay inside the world of behaviours: since they have values at all point in time, it wouldn't be clear when to apply the update function.

Let's see, what else could it be? Oh, I know! Instead of an event broadcasting dynamic values to be accumulated with a fixed update function, maybe it could be the functions which are dynamically broadcasted? As each one would arrive, they would be accumulated on top of a fixed initial value. Does hoogle know of any function of type s -> Event t (s -> s) -> Behavior t s? Yes it does! It's called accumB, and I can use it to compute a running sum.

main = playBanana (InWindow "Nice Window" (200, 200) (800, 200))
                  white
                  30
                  reactiveMain

reactiveMain :: forall t. Frameworks t
             => Event t Float
             -> Event t InputEvent
             -> Moment t (Behavior t Picture)
reactiveMain floats _ = return pictures
  where
    partialSums :: Behavior t Float
    partialSums = accumB 0 (fmap (+) floats)
    
    pictures :: Behavior t Picture
    pictures = fmap renderFloat partialSums

commit 1386bf:
It works! And as a bonus, the timing bug is now mysteriously fixed.

Buttons


So far so good! In the same vein, I should be able to accumulate button press events to increment digits on each of the buttons. But wait; each button is only concerned with a subset of the mouse click events. How do I filter an event stream? Another easy hoogle search says filterE should do the trick.

reactiveMain floats events = return pictures
  where
    buttonClicks :: [Event t ()]
    buttonClicks = map (flip buttonClick events) buttons
    
    countA,countB,countC :: Behavior t Int
    [countA,countB,countC] = map countEventsB buttonClicks
    
    clickCounts :: Behavior t (Int,Int,Int)
    clickCounts = liftA3 (,,) countA countB countC
    
    pictures :: Behavior t Picture
    pictures = fmap render clickCounts

countEventsB :: Num a => Event t b -> Behavior t a
countEventsB = accumB 0 . fmap (+) . fmap (const 1)

buttons :: [Extent]
buttons = [extentA, extentB, extentC]

buttonClick :: Extent -> Event t InputEvent -> Event t ()
buttonClick ex = fmap (const ()) . filterE isInside
  where
    isInside (EventKey (MouseButton LeftButton)
                       Down _ p) = pointInExtent ex p
    isInside _                   = False

To combine the three different behaviours into one in clickCounts, I guessed that Behavior was probably an Applicative. Events probably aren't; because of filtering, you wouldn't be able to match individual events from one stream with individual events from the other.

commit 66f4e7:
Click-click-click-click-click! Click-click! Click-click-click!

A shared source of numbers


Currently, the buttons all start at 0 and each click increments that individual button's number by one. Instead, I would like the three buttons to start at 1, 2 and 3, and for each click to set the clicked button to the next number in that sequence. The obvious imperative implementation, however, doesn't seem very FRP-ish. In particular, I don't think the event stream from one button is allowed to have any effect on the event stream of the other buttons: a stream can only be affected by its "upstream" streams, that is, the streams from which it is computed.

So I think I need something upstream which would handle the shared state, and each of the three buttons should derive their own event streams from that. The most obvious representation for an upstream thing from which the three kinds of events could be derived would be... a stream containing all three kinds of events.

I already have a list of click streams, obtained by filtering the raw mouse events from three separate regions. To obtain a single stream containing the events from all three regions, I could filter the raw events in a different way, but can I instead merge the three event streams I already have? Hoogle doesn't have a function of type Event t a -> Event t b -> Event t (Either a b), and I don't have any other idea of the form such a combinator could look like. Looking at the documentation for Event, I quickly find union, which needs both sides to hold events of the same type. And actually, it looks even more convenient that way!

labelledClicks :: [Event t Char]
labelledClicks = zipWith (fmap . const) ['a'..] buttonClicks

clickLabels :: Event t Char
clickLabels = foldr union never labelledClicks

Now I need each of those events to increment a shared state. The accumB we used earlier generated a Behavior; from the name, I guess that there is also a variant named accumE which generates an Event? Bingo.

clickEvents :: Event t (Char, Int)
clickEvents = accumE (undefined, 0) (fmap mkEvent clickLabels)

mkEvent :: Char -> (Char, Int) -> (Char, Int)
mkEvent label (_, n) = (label, n+1)

Since I want to keep the Char from the original event stream, the accumulated value must contain a Char, which means I must also provide a Char for the initial state. I never use this part of the initial state, so I can use undefined.

Now that I have a single stream containing the annotated events from all three buttons, I can split them back into three separate streams via filters which happen to be mutually-exclusive. Previously, we used filterE, while this time... we must still use filterE, because strangely enough, there is no filterB.

countA,countB,countC :: Behavior t Int
[countA,countB,countC] = map countN "abc"

countN :: Char -> Behavior t Int
countN label = stepper 0
             $ fmap snd
             $ filterE ((== label) . fst) clickEvents

commit 76b052:
The buttons start at (0,0,0) instead of (1,2,3),
but otherwise increment with a shared state, as desired.

The refresh button


When the refresh button is clicked, the three other buttons should behave as if they were clicked one after the other. Faking those clicks sounds easy enough: since the real stream of clicks is just a stream of () values, I should be able to add a few extra () values to represent the fake clicks. In particular, I can simply union the stream of real clicks with the stream of refresh clicks.

refreshClicks :: Event t ()
refreshClicks = buttonClick extentR events

fakeButtonClicks :: [Event t ()]
fakeButtonClicks = map (union refreshClicks) buttonClicks

labelledClicks :: [Event t Char]
labelledClicks = zipWith (fmap . const) ['a'..] fakeButtonClicks

commit d98691:
The buttons are clicked one after the other, like I wanted.
But how did reactive-banana know to click them from top to bottom?

It worked! But... why did it? The fake clicks from the refresh button are sent to the other three buttons at the same time. How come the "callbacks" were called from top to bottom? What if I wanted the buttons to be fake-clicked in the opposite order?

Let's see. Conceptually, at least (I don't know how reactive-banana is implemented), there are no callbacks. The clicks and the fake clicks from all three buttons are merged into a single stream, which uses accumE to number the events from 1 to infinity. This numbering must necessarily visit all the events in a specific order; I didn't specify this order, but it's pretty obvious that it's a chronological order. Since the events from the refresh button happen at the same time, there is an ambiguity here. In which order does accumE visit events which occur at the same time?

Reading the documentation for union again, I see that "in case of simultaneous occurrences, the left argument comes first". In clickLabels (defined earlier), I didn't really pay attention to the order in which I passed the buttons, but indeed, I am folding the click streams from top to bottom. If I wanted the fake clicks to occur from bottom to top, I could simply reverse the input list:

clickLabels :: Event t Char
clickLabels = foldr union never (reverse labelledClicks)

commit 5881ae:
Refreshing in the reverse order, because I can!
(one screenshot ago, I could not)

One more event at the beginning


One last detail is that the buttons still start at (0,0,0). Clearly, I need to add an extra refresh event at the beginning. But how? Up to now, every single event has been derived from some external event. I don't even know if events have timestamps. How do I specify "the beginning"?

Besides, the beginning of what? If I construct a stream and I ask reactive-banana to execute it somehow, and then at some later point I ask reactive-banana to execute it again, will this count as a second "beginning"? If so, that would be a bit weird, but the more I think about it, it would be even weirder if it didn't. To remember which streams already had their "beginning" event, the streams would have to keep their state between executions. But maintaining a state implies monadic stream-creation constructs, which is not the interface I see.

Speaking of monads, we still haven't used the Moment monad. With a name like this, maybe there is a monadic command for creating time-related events such as "at the beginning" or "every 5 seconds"? Hoogling for Moment t (Event t ()), I find a function with the very relevant-sounding name now:

now :: AnyMoment f a -> forall t. Moment t (f t a)

What a strange type. Why is the forall on the right? I don't even think it makes a difference, it would have been equivalent to put it on the left or to omit it altogether.

now has no documentation, but Moment does. Kinda. It says that it is "not [a] very interesting" monad. Very well, what about AnyMoment, is that an "interesting" value? Oh, I see now! It's the type of anyMoment which explains everything:

anyMoment :: (forall t. Moment t (f t a)) -> AnyMoment f a

I have already discussed the fact that our code needs to be polymorphic in t. The type AnyMoment simply encodes this requirement, and the strangely-named now converts back from AnyMoment f a to forall t. Moment t (f t a). Hence the strangely-placed forall.

In any case, now is not the event stream I am looking for...

I browse the documentation for reactive-banana, to no avail. I notice a handy shortcut for folding streams, but nothing about creating new non-derived events.

clickLabels :: Event t Char
clickLabels = unions labelledClicks

I guess I will have to roll my own. Remember the list of float events indicating the passage of time? I should be able to make the first such event stand in for the beginning of time.

accumZip :: a -> (a -> a) -> Event t b -> Event t (a, b)
accumZip zero suc = accumE (zero, undefined)
                  . fmap go
  where
    go y (x,_) = (suc x, y)

-- (1, x1), (2, x2), ...
numberEvents :: Event t a -> Event t (Int, a)
numberEvents = accumZip 0 (+1)

firstEvent :: Event t a -> Event t a
firstEvent = fmap snd
           . filterE ((== 1) . fst)
           . numberEvents

beginning :: Event t ()
beginning = voidE (firstEvent floats)

The code for this part ended up being longer than I expected: I originally wanted to use a simple accumulator which would discard everything after the first result, but such an accumulator is not as simple as const Nothing or something like that. It needs to have two distinct non-value states: the initial state, prior to encountering the first value, and the final state, from the second value onward. If we were to go back to the initial state instead of going to a distinct final state, the third value would be treated like the first value instead of being discarded.

Anyway, I now have an event from which to trigger the initial refresh.

addFakeClicks :: Event t () -> Event t ()
addFakeClicks realClicks = unions [beginning, refreshClicks, realClicks]

fakeButtonClicks :: [Event t ()]
fakeButtonClicks = map addFakeClicks buttonClicks

And with this, I am done!

commit 965803:
You know, technically, I could have obtained all of those
screenshots from the dumb version with one counter per button.
But I wouldn't do this to you :)

Conclusion


Okay, so after my first toy FRP app, what is my opinion of FRP? Well, I must say that I was quite impressed by how often iterations worked just fine the first time I ran them. This is, of course, a generic benefit of using Haskell, but I had not yet had this experience while building a GUI application. This made me realize that even though I am using a purely functional programming language, when it comes to GUI applications, I was still using antiquated imperative methods! Where else do I repeat this error?

More formally, I would say that the advantages and disadvantages seem to be the same as those of pure functional programming: without mutable variables, all the data dependencies must be made explicit, sometimes painfully so. For large applications, where the interaction between all the mutable variables and the callbacks can quickly become difficult to visualize, I can see how FRP could be very effective at reducing the complexity.

For my application, I ended up merging all the interesting events into a single stream, applying a master accumulator in order to produce all the output values, and distributing those to the appropriate GUI elements via filters. Of course, my app was a toy; but I wonder how common this architecture is when using FRP? In a larger application, would it be feasible and/or desirable to gather the events from all the widgets in the app, so they can be handled by some pure state machine in the middle; much like IO code is often a thin wrapper around a pure core?

Anyway, I feel like I have only scratched the surface of what FRP has to offer, so please take my thoughts on the subject with a grain of salt.



[1] Last time was surprisingly popular, so I thought I should do more.
[2] The library doesn't compile with ghc 7.8, but that's only because its bounds are too strict. Simply download the source with cabal get gloss-banana, remove the version constraints on base, go back to your project and add your custom version of gloss-banana via cabal sandbox add-source ../path/to/gloss-banana.
[3] I made the change to my local copy of gloss-banana, so you won't see it on the app's github repo.

5 comments:

Anonymous said...

This was a very interesting read, thank you!

Unknown said...

A more idiomatic way to add the ESC-quit functionality would be to build it into your application:

reactimate $ quitOnEsc <$> ev

I really like this concept of ‘anti-tutorials’ — I think they're potentially very useful to help library designers understand stumbling blocks that might make their APIs harder to learn!

Ziriax said...

Very nice tutorial, thank you!

Anonymous said...

Thank you!

I've been struggling for a long time looking for something I could understand! This is it! A working example!

It was a bit of a struggle since reactive-banana is now at 1.xx and they changed the API so I had to revert back to 0.9.0.0.

I'm happy .. I now have an example I can play with!

Thanks again.

Tom

gelisam said...

Thanks for the comment, I'll add a note explaining that the API has since changed and that readers should use reactive-banana-0.9.0.0 if they want to follow along.

Personally, I was disappointed by the API change in 1.0, as I prefer pure values to monadic actions, even if the pure values have a slightly more complicated type.