posts `for_` publish

An Introduction to Brick+Reflex


Introduction

In ‘Introduction to Brick’ Sam Tay (re)implemented the game “snake” as a commandline application using the brick library. I very much liked this approach - snake is relatively simple but is complex enough to go past the hello-world examples provided in the brick package. (Not to say that these examples are bad; they do a good job of highlighting different features one by one.)

In this post we make use of that foundation and write snake using brick and functional-reactive programming (FRP) in the form of the reflex library. We will not do a complete rewrite, but take Sam Tay’s code and do nothing more than refactor it, so you may want to at least briefly read the explanation of the original code.

The goals of this post are to

Structure

I transformed the original source code in several relatively small steps. First some trivial refactors while I got familiar with code. Then introducing reflex and switching to the reflex interface for brick, but leaving the snake game logic as-is. Then, one by one, transforming game logic, and finally cleaning up.

While that made sense as a process I don’t think it is a good approach for this post. We could discuss each commit one-by-one (and I was careful to make sensible steps in the repository), but this would yield a rather long post.

Instead, I will firstly explain how to build the new modified project. Then the brick-reflex interface will be introduced briefly. With this knowledge, we will walk through the final source in detail, and explain how things have changed and why - focus on the complete diff instead of each commit’s diff. After that we will discuss some general advantages of the new design and how it helps when writing larger applications.

Building the New Version of Snake

The updated code is available on github:

> git clone https://github.com/lspitzner/snake.git -b master

Dependencies

brick is not natively compatible with an FRP approach, so we make use of a wrapper library that exposes a reflex interface for brick. Unfortunately this means that we need to use a fork of brick because brick does not expose the internals necessary for writing the reflex interface. And because its maintainer refused to expose the relevant internals.

All in all, the relevant additions to the project’s dependencies are:

Did the community really have to write several competing build-tools

We will be using the HEADs of several dependency repositories. This currently is easiest to set up with stack, and I have included a stack.yaml that should work out of the box. If you wish to use anything else (I did the development using cabal new-build) please refer to the stack.yaml for which additional dependencies must be installed and which commits to use.

Brick Reflex interface

The type of the main function of the bricki-reflex interface is, written in a simplified fashion:

brickWrapper
  :: (MagicReflexConstraints)
  => Event ()           -- ^ to trigger shutdown
  -> Dynamic [Widget n] -- ^ output to render
  -> Dynamic ([CursorLocation n] -> Maybe (CursorLocation n)) -- cursor stuff
  -> Dynamic AttrMap                                          -- attr stuff
  -> AppHost
       ( Event (Maybe Brick.Event)
       , Event ()
       , Event (IO a) -> AppHost (Event a)
       )

in contrast to

customMain :: (Ord n) => IO Vty -> Maybe (BChan e) -> App s e n -> s -> IO s
-- with
data App s e n =
    App { appDraw :: s -> [Widget n]
        , appChooseCursor :: s -> [CursorLocation n] -> Maybe (CursorLocation n)
        , appHandleEvent :: s -> BrickEvent n e -> EventM n (Next s)
        , appStartEvent :: s -> EventM n s
        , appAttrMap :: s -> AttrMap
        }

Some important aspects for the FRP interface: We..

  1. do not use any channels. When things happen at runtime, reflex Events fire, and the interface is expressed in terms of Events (and Dynamics).
  2. as a consequence, we do not pass functions (the App fields) that are called as required. Instead, we pass Dynamics that we will control, and obtain input from the wrapper.
  3. are in the strange situation that we seemingly have to pass output things before even seeing the input. But this is no problem, because AppHost is MonadFix, i.e. it will be possible to define the the output Dynamic [Widget n] in terms of, lets say, the input Event (Maybe Brick.Event). We will discuss this in more detail when considering the updated code below.

Still, a lot of things remain unchanged. (User) input events are still vty events. The three output Dynamics directly correspond to the appDraw, appChooseCursor and appAttrMap fields. Also, AppHost is MonadIO.

Some Brief Notes About Using Event/Behavior/Dynamic

When do we use which of the three in interfaces? To recapitulate, Dynamic is the combination of Behavior and Event, we can extract both a Behavior and an Event from a Dynamic, and while Dynamic and Behavior are Monads, Event is only Functor and Apply.

Differences in Detail

Brace yourself, we’ll dive right in. We’ll mostly consider the new code; old code will be declared as such.

data OutputState = OutputState
  { _out_dead :: Bool
  , _out_score :: Int
  , _out_snake :: Seq Coord
  , _out_food :: Coord
  }

This seems to replace the Game record, which had some similar fields (but more in total). However, this is used for output only: A description of what to render each frame. All actual state has moved into reflex Behaviors or Dynamics. We will look at those below.

The basic types and constants have not changed:

type Coord = V2 Int
type Snake = Seq Coord

data Direction
  = North
  | ..
  deriving (Eq, Show)

-- Constants

height, width :: Int
height = 20
width = 20

For the following “game logic helper functions”, not much has changed really, but they were renamed and refactored slightly. We also removed the IO from the functions, but Sam Tay has done the same in some commit pushed after releasing the blog post.

‘But half the methods are missing now!’ you say. Correct: A lot of the game logic has moved into the “reflex network”. This definitely deserves a subsection.

“network” is the term used to refer to the monadic values for the reflex “host” monad in which we connect events, dynamics and behaviors.

Core Game Logic

The type of gameNetwork might look scary, but if we gloss over the constraints, it is not too terrible:

gameNetwork
  :: forall t m
   . ( ScaryReflexConstraints t m) -- ignore these for now
  => R.Event t ()        -- ^ restart event
  -> R.Event t Direction -- ^ direction change event
  -> R.Event t ()        -- ^ tick event
  -> m (R.Dynamic t OutputState)

This function will connect several types of input events and produce a Dynamic OutputState - essentially a stream of OutputStates to be rendered. The argument events will “tick” whenever

  1. the user triggers a game restart
  2. the user presses a direction key
  3. a timer fires

Now the meat of the game: the implementation.

gameNetwork restartEvent directionEvent tickEvent = mdo
  -- the state changes affect each other, so we use recursive do here.

  startEvent                 <- R.headE tickEvent

stateEvent will fire once after program start. That’s it.

  pause :: R.Behavior t Bool <- R.hold True
    $ R.mergeWith (||) [restartEvent $> True, directionEvent $> False]

pause is a time-varying Bool that is initially True. Any direction input unpauses, but triggering a restart resets to paused state. Should both happen at the same time, pause.

  dead :: R.Dynamic t Bool <- R.holdDyn False $ R.leftmost
    [ restartEvent $> False
    , R.tag (snakeDiesOnMove <$> R.current nextHeadDyn <*> R.current snakeDyn)
            tickEvent
    ]

Another time-varying Bool; initially we are alive (yay!). Restarting revives, and on every tick: Combine the current values of the “next head position” and the current snake body using snakeDiesOnMove which determines the new value. The only reason to make this Dynamic over Behavior is that we will include this is the output Dynamic and this composes easier.

  let moveEvent = R.attachWithMaybe
        (\paused dying -> [ () | not (dying || paused) ])
        pause
        (R.tagPromptlyDyn dead tickEvent) -- need promptly to prevent tick
                                          -- if dead in the same instant.

moveEvent fires when we want to actually execute a move. This is like a filtered tickEvent (or “moveEvent is a subset of tickEvent” if we abstract over the flow of time). The monad-comprehension syntax returns Just () but only if

  1. we are not dying in the same tick and
  2. the game is not paused
  snakeDyn :: R.Dynamic t (Seq Coord) <- snakeNetwork startEvent
                                                      moveEvent
                                                      (R.current nextHeadDyn)
                                                      (R.current foodDyn)

A time-varying Seq Coord which fires on state-changing, calculated from a sub-network which depends on several Events/Behaviors. A Behavior would not do as we observe the state-changes in the food sub-network.

  nextHeadDyn :: R.Dynamic t (Maybe Coord) <- snakeHeadNetwork moveEvent
                                                               dead
                                                               snakeDyn

  foodDyn :: R.Dynamic t Coord <- foodNetwork startEvent snakeDyn

  scoreDyn :: R.Dynamic t Int  <- scoreNetwork (R.current foodDyn) snakeDyn

Same, but for the potential next head coordinate, the coordinate with food and the game score. These sub-networks will be rather small, but this matches the spirit of splitting the game logic into several small functions. Finally,

  pure $ OutputState <$> dead <*> scoreDyn <*> snakeDyn <*> foodDyn

Well, the output is a Dynamic obtained simply as a combination of the parts defined above. That these parts are all Dynamics makes this simple to write and it ensures that the output fires whenever anything changes.

Before we finish this part by looking at the different sub-networks, a

Brief Collections of Observations

And nothing more than observations, an attempt at evaluation will follow in a section below.

Game Logic Sub-Networks

gameNetwork restartEvent directionEvent tickEvent = mdo
  ..
  snakeDyn    <- snakeNetwork ..
  nextHeadDyn <- snakeHeadNetwork ..
  foodDyn     <- foodNetwork ..
  scoreDyn    <- scoreNetwork ..

  pure $ OutputState <$> dead <*> scoreDyn <*> snakeDyn <*> foodDyn
 where

  foodNetwork startEvent snakeDyn = do
    let genNewFoodM fs = R.sample (R.current snakeDyn) <&> genNewFood fs
        genNewFood fs snake = dropWhile (`elem` snake) fs
    let foodChange = R.leftmost
          [ startEvent $> \fs -> genNewFoodM fs
          , restartEvent $> \fs -> genNewFoodM fs
          , R.updated snakeDyn <&> \snake fs -> pure (genNewFood fs snake)
          ]
    infiniteFoodSupply <- liftIO
      [ zipWith V2 x y
      | x <- newStdGen <&> randomRs (1, width)
      , y <- newStdGen <&> randomRs (1, height)
      ]
    allTheFood :: R.Dynamic t [Coord] <- R.foldDynM id
                                                    infiniteFoodSupply
                                                    foodChange
    pure $ head <$> allTheFood

<&> is just flipped <$>, i.e. flip fmap.

Here we use IO, but only at network creation time, making use of laziness: We create an infinite list of potential food locations. Put that into the allTheFood dynamic, and on certain events drop a finite number of elements from this list. The food location is simply always the head of this list. Quite nifty!

  snakeHeadNetwork moveEvent dead snakeDyn = mdo
    lastDirDyn :: R.Dynamic t Direction <- R.holdDyn NoDir $ R.leftmost
      [restartEvent $> NoDir, R.tag (R.current nextDirDyn) moveEvent]
    nextDirDyn :: R.Dynamic t Direction <-
      R.holdDyn NoDir $ R.gate (not <$> R.current dead) $ R.attachWithMaybe
        turnDir
        (R.current lastDirDyn)
        directionEvent
    pure $ calcNextHead <$> nextDirDyn <*> snakeDyn

This does nothing more than cache next move direction and last direction between user input and next game frame event. We prevent the snake from making a 180° turn and biting its own neck. This creates the circular dependency between lastDirDyn and nextDirDyn, but it is no instantaneous circle (not in the same reflex frame) so we are fine.

  scoreNetwork foodB snakeDyn = do
    let scoreChange = R.leftmost
          [ restartEvent $> const 0
          , R.attachWith
            (\food g -> if getSnakeHead g == food then (+10) else id)
            foodB
            (R.updated snakeDyn)
          ]
    R.foldDyn id 0 scoreChange

Restarting resets score, eating food increases score. Simple as that.

  snakeNetwork startEvent moveEvent nextHeadB foodB = do
    let snakeChangeE :: R.Event t (Snake -> Snake) = R.mergeWith
          (.)
          [ R.attachWith
            id
            (   (\nextHead food () snake -> eatOrMove nextHead food snake)
            <$> nextHeadB
            <*> foodB
            )
            moveEvent
          , restartEvent <&> \() _ -> initialSnake
          , startEvent $> id -- ensures we render the initial screen
          ]
    R.foldDyn id initialSnake snakeChangeE

Snake is one fold-over-time starting with initialSnake and applying a snake-modification on certain events: Reset on restart, and calculated via eatOrMove on moveEvents. The amount of plumping operators here (attachWith, <$>, <*>, <&>, $>) is a bit sad, but is necessary to connect all the relevant events and behaviors. And it also shows the usefulness of Functor/Applicative instances nicely.

This was it! The game logic is complete. The only thing remaining is the UI, and that is relatively simple:

reflex brick UI

-- this forall is just a trick to "declare" 't' for signatures below.
main :: forall t . t ~ R.SpiderTimeline R.Global => IO ()
main = R.runSpiderHost $ RH.hostApp $ mdo

  (timerEvent, timerT) <- RH.newExternalEvent
  _                    <- RH.performPostBuild $ do
    void $ liftIO $ forkIO $ forever $ do
      _ <- timerT ()
      threadDelay 100000 -- decides how fast your game moves

Create our game frame timer event that fires every 0.1sec.

  (eventE, finE, _suspendSetupF) <- brickWrapper shouldHaltE
                                                 widgetsDyn
                                                 cursorDyn
                                                 (pure theMap)

  -- tell ReflexHost to quit once the brickWrapper has shut down.
  RH.performPostBuild_ $ do
    pure $ RH.infoQuit $ pure finE

Connect the brick interface. We pass in the dynamics that will be rendered, most importantly the widgetsDyn that contains the actual brick widgets. brickWrapper will redraw when any of the input dynamics fire.

We receive two events from the wrapper: The “user input event event” (brick (keyboard) input “event” and reflex FRP “event”) and an event that fires after shutdown. Now we only need to translate and forward to our game logic network, and define the outputs (that we already “used”/connected):

  let directionEvent = R.fforMaybe eventE $ (=<<) $ \case -- Maybe Monad tricks
        V.EvKey V.KUp         [] -> Just North
        V.EvKey V.KDown       [] -> Just South
        V.EvKey V.KRight      [] -> Just East
        V.EvKey V.KLeft       [] -> Just West
        V.EvKey (V.KChar 'k') [] -> Just North
        V.EvKey (V.KChar 'j') [] -> Just South
        V.EvKey (V.KChar 'l') [] -> Just East
        V.EvKey (V.KChar 'h') [] -> Just West
        _                        -> Nothing

  let restartEvent = R.fforMaybe eventE $ (=<<) $ \case
        V.EvKey (V.KChar 'r') [] -> Just ()
        _                        -> Nothing

  let cursorDyn = pure $ const Nothing -- never show cursor

  let shouldHaltE = R.fforMaybe eventE $ (=<<) $ \case
        V.EvKey V.KEsc        [] -> Just ()
        V.EvKey (V.KChar 'q') [] -> Just ()
        _                        -> Nothing

  outputDyn <- gameNetwork restartEvent directionEvent timerEvent

  let widgetsDyn = drawUI <$> outputDyn

  pure ()

This is relatively simple, apart from perhaps the circular dependencies. Keep in mind that we define an FRP network, so essentially we define how events are forwarded between different components. We don’t create direct data dependencies, but just connect input and output “mailboxes” for different stateful components.

Now that I think about this, I wonder how close this is to circular dependencies between different OOP singletons (or dependency-injected instances or however you else you hide the same basic pattern). Does not seem all that different..

All that is missing is the implementation of

drawUI :: OutputState -> [Widget Name]

but that is trivial, making use of the “regular” brick features, and has nothing to do with FRP, so I’ll omit it here. Better get directly to the interesting part:

Evaluation of Changes

Program Behavior

Program behavior is unchanged, apart from one detail: At game start, it is now possible to start moving down. Everything should be the same, including same-game-frame input event treatment.

Performance

Let’s look at the basic +RTS -s for two sessions of roughly equal length:

Not a proper benchmark, but nothing points to performance having decreased.

Program/Implementation Design

What did we achieve with these changes? It may have been an unfortunate example, but our code size actually increased a fair bit (~280 -> ~380 lines), to what advantage?

One clear advantage is that it is much easier to keep track of how the state of the system changes. There is no effectively global state that might be changed anywhere. Instead each time-varying value has its semantics attached to its definition. But while FRP certainly encourages this design, it is not unique to FRP. We could also define a pure calcNewPaused :: Game -> Input -> Bool, etc.

Another side-thought: To properly implement this without FRP, it seems we might want (or even require) row-types, because those would allow us to communicate in the types which fields of our compound state are accessed. So does FRP replace row-types, or just certain use-cases for row-types?

A more important advantage is the decoupling. Game logic remains independent from the UI logic, but UI logic now is also independent from game logic. Consider the previous

app = App { ..
          , appHandleEvent = handleEvent
          , ..
          }

main = do
  .. -- setup stuff
  void $ customMain (V.mkVty V.defaultConfig) (Just chan) app g

handleEvent :: Game -> BrickEvent Name Tick -> EventM Name (Next Game)
handleEvent = ..

The main loop referenced the game state, and this state even was explicitly passed through brick (App is parameterized with user state!). Instead we now have

main = R.runSpiderHost $ RH.hostApp $ mdo
  ..
  (eventE, finE, _suspendSetupF) <- brickWrapper shouldHaltE
                                                 widgetsDyn
                                                 cursorDyn
                                                 (pure theMap)
  ..
  directionEvent = _sometransformof eventE
  restartEvent   = _sometransformof eventE
  widgetsDyn     = _sometransformof outputDyn
  ..
  outputDyn <- gameNetwork restartEvent directionEvent timerEvent
  ..

That our interfaces are expressed in terms of Events and Dynamics means that time-varying state is internal to the relevant components.

Also note how brickWrapper and gameNetwork act like inverses: brickWrapper accepts widgets-to-output as argument and returns user-input. gameNetwork accepts (slightly transformed) user input as argument and produces data-to-display.

Also, we can in theory connect events not coming from brick in our game logic without this disrupting our design in any way. To demonstrate this:

A Test of Extensibility

Our team of game testers have played this game multiple days and have determined that the game is too easy and requires more action. The project lead has decided that the best change is to make food decay after some seconds. For additional excitement, it is mandatory that the food decay is not aligned with other game ticks, so it is possible that food decays right before being eaten. That will show those testers!

Without FRP, the necessary changes are quite annoying. Because decay is supposed to be independent, we need a new type of custom event. That is, in the UI.hs we need to replace data Tick = Tick with data Tick = Tick | Decay. This new thing will cause changes to trickle down: Adapt UI.hs:handleEvent, Snake.hs:step and implement the decay logic somewhere in Snake.hs as well.

Of course this example was chosen for a reason. The necessary changes are much more local with the FRP design: In fact we only need to change the food subnetwork:

  foodNetwork startEvent snakeDyn = do
    let genNewFoodM fs = R.sample (R.current snakeDyn) <&> genNewFood fs
        genNewFood fs snake = dropWhile (`elem`snake) fs
    (foodDecayEvent, decayT) <- RH.newExternalEvent                          -- added
    _                        <- RH.performPostBuild $ do                     -- added
      void $ liftIO $ forkIO $ forever $ do                                  -- added
        _ <- decayT ()                                                       -- added
        threadDelay =<< randomRIO (3000000, 10000000)                        -- added
    let foodChange = R.leftmost
          [ startEvent $> \fs -> genNewFoodM fs
          , restartEvent $> \fs -> genNewFoodM fs
          , R.updated snakeDyn <&> \snake fs -> pure (genNewFood fs snake)
          , foodDecayEvent $> \fs -> genNewFoodM $ tail fs                   -- added
          ]
    infiniteFoodSupply <- liftIO
      [ zipWith V2 x y
      | x <- newStdGen <&> randomRs (1, width)
      , y <- newStdGen <&> randomRs (1, height)
      ]
    allTheFood :: R.Dynamic t [Coord] <- R.foldDynM id
                                                    infiniteFoodSupply
                                                    foodChange
    pure $ head <$> allTheFood

Because the different networks are decoupled, it is no problem adding a new event locally - only 6 added lines of code. We have a new event that fires randomly every 3-10sec. The way it is set up the timer is not reset when food is eaten or when the game resets, but implementing that would not make things less local.

The corresponding code is available in a branch, i.e.

> git checkout decayingfood

If you look at the diff you might notice that we also had to change the context from our gameNetwork to allow us to create a new event locally. But this is a one-time change: Any further new additions/events would remain fully local.

Conclusion

We took a relatively simple snake game and refactored it to use functional reactive programming idioms. The resulting program behaves the same, including the performance aspect. Yet the new program design contains less coupling and makes future changes and extensions easier.

The switch to FRP:

Thanks to Sam Tay for writing the blog post and laying the foundation for this post with this nice example program.

Posted by Lennart Spitzner on 2017-10-30. Feedback to (blog at thisdomain) welcome!
Tags: . Source.