Abstraction in Reflex and CodeWorld

Chris Smith
ITNEXT
Published in
16 min readAug 14, 2021

--

I’ve put together a neat example lately of using FRP (Functional Reactive Programming) to cleanly separate and model the interactions of the pieces of an interactive application: in this case, an RPN (Reverse Polish Notation) calculator. In this article, I present the Haskell code for this application using the Reflex FRP library and the CodeWorld graphics API.

An RPN Calculator

Because CodeWorld is a relatively low-level graphics API, we’ll be reinventing abstractions like numeric entry fields. Don’t think that’s a fundamental part of FRP! Indeed, libraries like reflex-dom provide you all the power of traditional high-level component libraries using the same FRP. But I think starting from the ground up is a nice learning experience; we can see how to work up from very simple primitives to build higher-level components, and you can apply the same abstraction techniques to build application-specific abstractions in your own code.

The calculator we’ll obtain at the end of the series is at this link:

It definitely has some deficiencies:

  • Rendering of very precise numbers is lacking.
  • You cannot enter negative numbers.
  • Lots of important operations are missing.

Consider these exercises for the interested reader. I’ve only implemented enough to make the abstraction techniques clear, and never intended for this to be a production quality calculator!

Basic Definitions

If you’re not familiar with FRP, the idea is to model the interactive parts of your software in terms of two abstractions: events and behaviors. An event is a thing that occurs at discrete moments in time, such as a key press or a mouse click. (If you’re used to conventional GUI programming, beware: in FRP, an event is not a single occurrence of the thing, but rather the entire thing which can occur many times.) A behavior is a value that changes over time, such as a mouse position. (Again, a behavior isn’t a value at a specific time, but rather the entire concept of something like a mouse position that changes over time.)

Reflex adds a third abstraction that’s a sort of hybrid between the two. A dynamic value is a value that changes only at discrete points in time. Because it does change over time, its current value forms a behavior. But because it changes at discrete points in time, its updates form an event.

Starting with Buttons

One thing we’ll need for a calculator that CodeWorld doesn’t provide for us is buttons! On the one hand, buttons are pretty simple things: you click on them and they do something. However, as we’ll see, getting an intuitive and user-friendly button experience is non-trivial and worth abstracting over!

Here’s a Reflex program using CodeWorld to create a simple (not very user-friendly) button.

The source code is:

{-# LANGUAGE OverloadedStrings #-}import CodeWorld.Reflex
import Control.Monad.IO.Class
import Data.Functor (($>))
import Data.Text (Text)
import Reflex
button :: ReflexCodeWorld t m => Text -> m (Event t ())
button label =
do
draw (pure (rectangle 5 2 <> lettering label))
clicks <- getPointerClick
return (ffilter inButton clicks $> ())
where
inButton (x, y) = abs x < 2.5 && abs y < 1
foreign import javascript "window.alert('clicked!');"
notify :: IO ()
app :: ReflexCodeWorld t m => m ()
app = do
clicks <- button "Click me!"
performEvent (clicks $> liftIO notify)
return ()
main :: IO ()
main = reflexOf app

If you’ve made it this far, you’re probably familiar with OverloadedStrings, which just let us write string literals for Text values in Haskell. The rest of this I’ll explain now.

First of all, the type of button says that you must provide a label, and you get back an event, whose occurrences are button clicks. ReflexCodeWorld is just a class that encapsulates all of the constraints needed to write Reflex programs that interact with CodeWorld. Any time you need access to fundamental drawing and event handling things using CodeWorld types, you need this class. Buttons draw to the screen and listen for mouse clicks, so the class is needed here.

The implementation of button draws the button on the screen by using a function called draw. If you look up the type for draw, it’s ReflexCodeWorld t m => Dynamic t Picture -> m (). The dynamic picture means you can draw a picture that changes over time. But in this case, our button doesn’t change, so we use pure to draw a constant picture of a rectangle and lettering. The next task is to determine when the button has been clicked. We use getPointerClick to retrieve an event that tells us when the mouse has been clicked, and then filter only those clicks that occur within the bounds of the button (using ffilter), and replace the points in the pointer event with () (using the $> Functor operator) because clients don’t care which specific pixel was clicked.

At this point, you may start to wonder where all these combinators are coming from. The ones that relate directly to drawing and UI events come from the CodeWorld.Reflex module, the documentation for which can be found at https://hackage.haskell.org/package/codeworld-api-0.6.0/docs/CodeWorld-Reflex.html or by clicking the Guide button from the CodeWorld tab. The general combinators for events and behaviors come from Reflex, and a good reference is the Reflex Quick Reference. Keep in mind that there are instances as well: Event, Behavior, and Dynamic are all functors, and Behavior and Dynamic are applicative functors and monads as well. (Note that the monad instance for Dynamic can be expensive, so avoid it if possible!)

This completes the generic implementation of buttons. Next I use the JavaScript FFI to define a simple action so we can tell when the button event fires, and use performEvent (another Reflex combinator) to attach that IO action to the event returned from button. To put it all together, reflexOf is a CodeWorld function that runs a ReflexCodeWorld network in the CodeWorld environment.

Building a Better Button

This button worked, but it was ugly and limited. It’s always the same size and location, doesn’t react to the user pressing it at all, and generally doesn’t behave as users are accustomed to buttons behaving in modern user interfaces. We can do better!

First, to make the size and location configurable, we should define a type for button configuration properties, and bundle all these options together. That looks like this:

data ButtonConfig = ButtonConfig
{ buttonLocation :: Point,
buttonWidth :: Double,
buttonHeight :: Double,
buttonText :: Text
}

It’s a trivial exercise to rewrite button to take a ButtonConfig and render itself in an arbitrary size and location. It looks like this.

And the source code for that button is:

button :: ReflexCodeWorld t m => ButtonConfig -> m (Event t ())
button (ButtonConfig (x, y) w h label) =
do
draw (pure pic)
clicks <- getPointerClick
return (ffilter inButton clicks $> ())
where
inButton (xx, yy) = abs (xx - x) < w / 2 && abs (yy - y) < h / 2
pic =
translated x y $
clipped w h (lettering label)
<> rectangle w h

I’ve used CodeWorld functions called translated and clipped to move the visual appearance of the button and ensure the label doesn’t extend beyond the now-configurable size. Aside from that, this is all straight-forward.

More complex is making the button respond to user input and behave as buttons tend to behave in modern user interfaces. If you try out some buttons in your favorite GUI programs, you may notice that they behave like this:

  • There may or may not be a hover effect to indicate when your pointer is over the button.
  • When you press down on the pointer, the button is held down, but its action isn’t yet triggered.
  • If you drag the pointer off the button before releasing, the action is not triggered. Similarly, if you click elsewhere and drag onto the button, the action is not triggered.
  • The button’s action is triggered only when you release the pointer while it’s over the button, and it was pressed over the button. However, the action triggers regardless of whether it was temporarily moved off of the button while the pointer was held down.

That’s a complicated behavior! But in the end, every detail is justifiable by considering the human experience of using the button. We’d like to replicate this behavior in our button.

When approaching a complex problem like this, I like to start by naming things! I ended up with the following bit of code, which I’ll explain line-by-line.

do
over <- fmap inButton <$> getPointerPosition
down <- isPointerDown
click <- getPointerClick
lastAnchored <- holdDyn False $ fmap inButton click
let anchored = (&&) <$> down <*> lastAnchored
let releases = ffilter not (updated anchored) $> ()
let triggers = gate (current over) releases

Here’s what’s going on:

  • over is a dynamic Bool value indicating whether the pointer is located over the button. We start with getPointerPosition, which is a dynamic Point, and then fmap the inButton function from above to get a dynamic Bool.
  • down is a dynamic Bool value indicating whether the pointer is currently being held down, regardless of whether it’s over the button. This is defined using isPointerDown, which is a CodeWorld Reflex primitive.
  • click is an event indicating that the pointer is pressed down, regardless of whether it’s over the button. The value associated with each event is the point where the pointer was clicked. This is defined using getPointerClick, which is again a CodeWorld Reflex primitive.
  • lastAnchored is a dynamic Bool value that remembers whether the last pointer press happened over the button or not. We start with all pointer presses (click), fmap inButton to get an Event of Bool values instead of Point values, and finally use holdDyn (a standard Reflex operation) to build a dynamic value that remembers the most recent Event occurrence.
  • anchored is a combination of lastAnchored and down, a dynamic Bool value that tells whether there’s an ongoing pointer press that started over the button. It uses Applicative operators to combine the two simpler values.
  • releases is an event takes all of the updates to anchored, and then filters out only those that change it to False. Here, updated is a standard Reflex combinator that extracts the Event of updates to a dynamic value.
  • Finally, triggers gates releases to keep only those releases that happen while over the button. Here, current is a standard Reflex combinator that gets the behavior representing the current sample of a dynamic value. Then gate is another standard Reflex combinator that gates an event by a behavior.

The triggers Event is what we want: an event representing the precise times at which the effect of a button should be triggered.

Next, we’d like the rendering of the button to differ depending on the state. Specifically, we’d like to render differently depending on anchored and over. To accomplish this, instead of using pure with draw, we’ll use applicative combinators to pass arguments to a rendering function.

draw (render <$> anchored <*> over)

The rendering function I’ve chosen uses the two parameters to choose a background color for the button.

render anchored over =
translated x y $
clipped w h (lettering label)
<> rectangle w h
<> colored (color anchored over) (solidRectangle w h)
color _ False = white
color False True = RGB 0.9 0.9 0.9
color True True = RGB 0.8 0.8 0.8

You can play with the completed button here:

The nice thing about this button is that the API stayed exactly the same as the earlier configurable button. The logic change to make the button behavior more user-friendly was entirely encapsulated inside the implementation of a reusable component. This is the case despite some pretty radical changes, like triggering the effect on mouse release instead of mouse press! That kind of abstraction is possible because the event abstraction is available for user-defined events.

Entering Numbers

The next challenge is the number entry field. Since this is a calculator, entering numbers is one of the most important things you can do, and it shouldn’t surprise us that the task gets a little complicated. We identify the following requirements.

  • If there’s no number being typed yet, we can type a number, with or without decimal points, to enter that number.
  • We can set the current number being typed to any number we desire. For example, the number entry field sometimes functions as the top element of the stack, so when we pop a number off the stack, we’ll set the entry field to that number.
  • It’s also possible that no number is being entered. For example, immediately after performing a math operation, there is no number being entered.

Following the lessons learned from the button example earlier, we’ll start with a config structure giving configuration options about the number entry field. There’s a new wrinkle though:

data NumFieldConfig t = NumFieldConfig
{ numFieldLocation :: Point,
numFieldWidth :: Double,
numFieldHeight :: Double,
setNumField :: Event t (Maybe Rational)
}

What is setNumField? Well, unlike with buttons, we need to be able to set the value of the number field from outside of the field itself. The way we do this in Reflex is to pass in what the control needs to know about the outside world, such as when the outside world wants it to change its current value. The value attached to the event is a Maybe because it’s possible (and, indeed, is the most common case) that the outside world wants to reset the field to not be entering a number at all.

Now the function to build a number field has this type:

numField ::
ReflexCodeWorld t m =>
NumFieldConfig t ->
m (Dynamic t (Maybe Rational))

That is, you pass in a NumFieldConfig (including an event that’s used for setting the value), and you get back a dynamic current value (which is possibly non-existent, hence the Maybe).

One approach here might be to implement an arbitrary text entry field, and then parse a number from that when the value is needed. Instead, though, we’ll take a different tack: keep a running number any time there’s a current number being edited. In order to enter decimals, in addition to the number itself, we need to keep track of whether a decimal point has been typed, and if so, how many decimal places have been typed beyond that point (pun intended). So we can define a state type for the internal state of the number field like this:

data NumFieldState = NumFieldState
{ numFieldValue :: Rational,
numFieldDecimalPlaces :: Maybe Int
}

Now we need to implement this. We’ll turn to what’s a pretty common trick for state machines in Reflex: use foldDyn (a standard Reflex combinator) with the function application operator to apply an event of state transition functions to the initial state. Build up that event by merging a lot of smaller events with function composition. Here’s what it looks like this time:

numField (NumFieldConfig (x, y) w h set) =
do
text <- getTextEntry
key <- getKeyPress
state <-
foldDyn ($) Nothing $
mergeWith
(.)
[ const . fmap initState <$> set,
ffilter (== "0") text $> digit 0,
ffilter (== "1") text $> digit 1,
ffilter (== "2") text $> digit 2,
ffilter (== "3") text $> digit 3,
ffilter (== "4") text $> digit 4,
ffilter (== "5") text $> digit 5,
ffilter (== "6") text $> digit 6,
ffilter (== "7") text $> digit 7,
ffilter (== "8") text $> digit 8,
ffilter (== "9") text $> digit 9,
ffilter (== ".") text $> dot,
ffilter (== "Backspace") key $> backspace
]
draw (render <$> state)
return (fmap numFieldValue <$> state)

We’re filtering out any time that a digit or dot is entered, backspace is pressed, or the current value is set using the event from the config. As explained above, when these things happen, we construct a state transition function, and yield it from the merged event using mergeWith, combining simultaneous events using function composition. Then we use foldDyn to fold over the event of state transition functions to get a dynamic current state.

There are four auxiliary functions used here to construct state transitions: initState, digit, dot, and backspace. There’s also an auxiliary render function used in the call to draw. These don’t use any Reflex functionality at all, since they are just plain functions on the state, and they also don’t use any new CodeWorld functionity. So I won’t explain them all, but will instead just link to a demo with the complete code, which you can review at your leisure.

The stack display component doesn’t introduce any new concepts at all, and is in fact a much simpler application of the same pattern since it has no input except for the setter function in the config. I’m omitting it here, but you can browse its code in the final calculator program.

Operations

Now that we have the basic components in place, we’ll start working toward wiring them together. There’s one more application-specific abstraction we can define here to make that process much more composable: operations. Operations include things like addition, subtraction, etc. But they also include pushing values onto the stack, popping them off the stack, and maybe in the future even more like dup, swap, etc.

Ultimate, an operation has two kinds of effects: setting the current number, and setting the current stack.

data OpEffect t = OpEffect
{ entryEffect :: Event t (Maybe Rational),
stackEffect :: Event t [Rational]
}

You can start to see how these are set up to be wired into the number field and stack display components, but we’ve still got some work to get there. An operation is just one way to affect the number field and stack, and a complete calculator will need to wire together a lot of different possible operations. Luckily, OpEffect forms a monoid, which lets us combine a lot of them together!

instance Reflex t => Semigroup (OpEffect t) where
OpEffect c1 s1 <> OpEffect c2 s2 =
OpEffect (leftmost [c1, c2]) (leftmost [s1, s2])
instance Reflex t => Monoid (OpEffect t) where
mempty = OpEffect never never

The empty OpEffect simply never sets anything. To combine two OpEffects, we combine their effects using leftmost. (If two effects fire simultaneously, this implementation will prefer the left one and drop the right one, but in that case it’s not clear what the right behavior is so that’s a fine choice.)

One thing worth calling out here: there is no ReflexCodeWorld class here; just Reflex. That’s because we’ve graduated a step above dealing with low-level graphics APIs, and are building the logical layer for interacting with stacks and numbers. The translation from these RPN calculator concepts down to drawings and pointer events and such was already implemented earlier. The lack of ReflexCodeWorld is a sign that we’ve succeeded in the abstraction.

At this point, we can begin implementing operations. For instance, pushing the current number field value onto the stack:

pushStack ::
Reflex t =>
Event t a ->
Dynamic t (Maybe Rational) ->
Dynamic t [Rational] ->
OpEffect t
pushStack occurred entryVal stackVal =
OpEffect
{ entryEffect = occurred $> Nothing,
stackEffect =
tag
( (:)
<$> (fromMaybe 0 <$> current entryVal)
<*> current stackVal
)
occurred
}

Here, occurred is an event that indicates when we want pushStack to happen. To push, we need access to the previous number entry and stack, and we yield an OpEffect that sets the new number entry and stack accordingly. The Reflex combinator tag is very useful here: it lets us take all occurrences of the event and replace the event value with some behavior, which we can build up from the current number entry field and stack.

We can also pop the top value off the stack, and replace the number entry field with it. This is another straightforward use of tag. Notice that we need the previous stack, but not the previous number field since we’ll be wiping out its value with a new one.

popStack ::
Reflex t =>
Event t a ->
Dynamic t [Rational] ->
OpEffect t
popStack occurred stackVal =
OpEffect
{ entryEffect = tag (listToMaybe <$> current stackVal) occurred,
stackEffect = tag (drop 1 <$> current stackVal) occurred
}

Finally, we’ll have a lot of operations that modify the stack. We want these to work in a consistent way: if there’s a current number being entered, push it onto the stack first and clear the number entry field, then perform the operation on the stack. Here’s how we can say that generically:

stackOp ::
Reflex t =>
([Rational] -> [Rational]) ->
Event t a ->
Dynamic t (Maybe Rational) ->
Dynamic t [Rational] ->
OpEffect t
stackOp f occurred entryVal stackVal =
OpEffect
{ entryEffect = occurred $> Nothing,
stackEffect = tag (f <$> input) occurred
}
where
input =
(\s -> maybe s (: s))
<$> current stackVal <*> current entryVal

We’ll need some binary operations (like addition and subtraction) and some unary operations (like square root). Let’s make wrappers for those so we can define specific operations more easily.

binaryOp ::
Reflex t =>
(Rational -> Rational -> Rational) ->
Event t a ->
Dynamic t (Maybe Rational) ->
Dynamic t [Rational] ->
OpEffect t
binaryOp op = stackOp f
where
f (x : y : xs) = op y x : xs
f other = other
unaryOp ::
Reflex t =>
(Rational -> Rational) ->
Event t a ->
Dynamic t (Maybe Rational) ->
Dynamic t [Rational] ->
OpEffect t
unaryOp op = stackOp f
where
f (x : xs) = op x : xs
f other = other

This gives us all the pieces we need to wire together a calculator.

Putting It All Together

Now it’s time to wire all this together. Because we have cyclic data dependencies among our components, we need the RecursiveDo language extension for this. This extension just lets us define recursive blocks of do notation where the bound values can refer to each other. Then we’ll just plug it all in:

calculator :: ReflexCodeWorld t m => m ()
calculator = do
key <- getKeyPress
text <- getTextEntry
sqrtButton <- button (ButtonConfig (-3.5, -3) 3 1.25 "sqrt")
sinButton <- button (ButtonConfig (0, -3) 3 1.25 "sin")
cosButton <- button (ButtonConfig (3.5, -3) 3 1.25 "cos")
rec let OpEffect entryEff stackEff =
mconcat
[ pushStack (ffilter (== "Enter") key) num stk,
popStack (ffilter (== "Esc") key) stk,
binaryOp (+) (ffilter (== "+") text) num stk,
binaryOp (-) (ffilter (== "-") text) num stk,
binaryOp (*) (ffilter (== "*") text) num stk,
binaryOp (/) (ffilter (== "/") text) num stk,
unaryOp (approx sqrt) sqrtButton num stk,
unaryOp (approx sin) sinButton num stk,
unaryOp (approx cos) cosButton num stk
]
num <- numField (NumFieldConfig (0, 5) 10 1.5 entryEff)
stk <- stack (StackConfig (0, 1) 10 6 stackEff)
return ()

The mconcat combines all the individual operations in one combined effect, which is then wired into the number field and stack components. Just to demonstrate that it’s possible, I’ve bound some operations to keys and some to buttons on the screen. The operation code doesn’t care where its events come from, which is why events are a nice abstraction. This ties it all together into one big calculator, leaving only one step left:

main :: IO ()
main = reflexOf calculator

And we’re done!

You can peruse the final calculator code here:

--

--

Software engineer, volunteer K-12 math and computer science teacher, author of the CodeWorld platform, amateur ring theorist, and Haskell enthusiast.