1
2# Brick Tutorial by Samuel Tay
3
4This tutorial was written by Samuel Tay, Copyright 2017
5(https://github.com/samtay, https://samtay.github.io/). It is provided
6as part of the brick distribution with permission.
7
8## Introduction
9
10I'm going to give a short introduction to
11[brick](https://hackage.haskell.org/package/brick), a Haskell library
12for building terminal user interfaces. So far I've used `brick` to
13implement [Conway's Game of Life](https://github.com/samtay/conway) and
14a [Tetris clone](https://github.com/samtay/tetris). I'll explain the
15basics, walk through an example [snake](https://github.com/samtay/snake)
16application, and then explain some more complicated scenarios.
17
18The first thing I'll say is that this package has some of the most
19impressive documentation and resources, which makes it easy to figure
20out pretty much anything you need to do. I'll try to make this useful,
21but I imagine if you're reading this then it is mostly being used as a
22reference in addition to the existing resources:
23
241. [Demo programs](https://github.com/jtdaugherty/brick/tree/master/programs)
25(clone down to explore the code and run them locally)
262. [User guide](https://github.com/jtdaugherty/brick/blob/master/docs/guide.rst)
273. [Haddock docs](https://hackage.haskell.org/package/brick-0.18)
284. [Google group](https://groups.google.com/forum/#!forum/brick-users)
29
30### The basic idea
31
32`brick` is very declarative. Once your base application logic is in
33place, the interface is generally built by two functions: drawing and
34handling events. The drawing function
35
36```haskell
37appDraw :: s -> [Widget n]
38```
39
40takes your app state `s` and produces the visuals `[Widget n]`. The
41handler
42
43```haskell
44appHandleEvent :: s -> BrickEvent n e -> EventM n (Next s)
45```
46
47takes your app state, an event (e.g. user presses the `'m'` key), and
48produces the resulting app state. *That's pretty much it.*
49
50## `snake`
51
52We're going to build the [classic
53snake](https://en.wikipedia.org/wiki/Snake_(video_game)) game that you
54might recall from arcades or the first cell phones. The full source code
55is [here](https://github.com/samtay/snake). This is the end product:
56
57![](snake-demo.gif)
58
59### Structure of the app
60
61The library makes it easy to separate the concerns of your application
62and the interface; I like to have a module with all of the core business
63logic that exports the core state of the app and functions for modifying
64it, and then have an interface module that just handles the setup,
65drawing, and handling events. So let's just use the `simple` stack
66template and add two modules
67
68```
69├── LICENSE
70├── README.md
71├── Setup.hs
72├── snake.cabal
73├── src
74│   ├── Main.hs
75│   ├── Snake.hs
76│   └── UI.hs
77└── stack.yaml
78```
79
80and our dependencies to `test.cabal`
81
82```yaml
83executable snake
84  hs-source-dirs:      src
85  main-is:             Main.hs
86  ghc-options:         -threaded
87  exposed-modules:     Snake
88                     , UI
89  default-language:    Haskell2010
90  build-depends:       base >= 4.7 && < 5
91                     , brick
92                     , containers
93                     , linear
94                     , microlens
95                     , microlens-th
96                     , random
97```
98
99### `Snake`
100
101Since this tutorial is about `brick`, I'll elide most of the
102implementation details of the actual game, but here are some of the key
103types and scaffolding:
104
105```haskell
106{-# LANGUAGE TemplateHaskell, FlexibleContexts #-}
107module Snake where
108
109import Control.Applicative ((<|>))
110import Control.Monad (guard)
111import Data.Maybe (fromMaybe)
112
113import Data.Sequence (Seq, ViewL(..), ViewR(..), (<|))
114import qualified Data.Sequence as S
115import Lens.Micro.TH (makeLenses)
116import Lens.Micro ((&), (.~), (%~), (^.))
117import Linear.V2 (V2(..), _x, _y)
118import System.Random (Random(..), newStdGen)
119
120-- Types
121
122data Game = Game
123  { _snake  :: Snake        -- ^ snake as a sequence of points in R2
124  , _dir    :: Direction    -- ^ direction
125  , _food   :: Coord        -- ^ location of the food
126  , _foods  :: Stream Coord -- ^ infinite list of random food locations
127  , _dead   :: Bool         -- ^ game over flag
128  , _paused :: Bool         -- ^ paused flag
129  , _score  :: Int          -- ^ score
130  , _frozen :: Bool         -- ^ freeze to disallow duplicate turns
131  } deriving (Show)
132
133type Coord = V2 Int
134type Snake = Seq Coord
135
136data Stream a = a :| Stream a
137  deriving (Show)
138
139data Direction
140  = North
141  | South
142  | East
143  | West
144  deriving (Eq, Show)
145```
146
147All of this is pretty self-explanatory, with the possible exception
148of lenses if you haven't seen them. At first glance they may seem
149complicated (and the underlying theory arguably is), but using them as
150getters and setters is very straightforward. So, if you are following
151along because you are writing a terminal app like this, I'd recommend
152using them, but they are not required to use `brick`.
153
154Here are the core functions for playing the game:
155
156```haskell
157-- | Step forward in time
158step :: Game -> Game
159step g = fromMaybe g $ do
160  guard (not $ g ^. paused || g ^. dead)
161  let g' = g & frozen .~ False
162  return . fromMaybe (move g') $ die g' <|> eatFood g'
163
164-- | Possibly die if next head position is disallowed
165die :: Game -> Maybe Game
166
167-- | Possibly eat food if next head position is food
168eatFood :: Game -> Maybe Game
169
170-- | Move snake along in a marquee fashion
171move :: Game -> Game
172
173-- | Turn game direction (only turns orthogonally)
174--
175-- Implicitly unpauses yet freezes game
176turn :: Direction -> Game -> Game
177
178-- | Initialize a paused game with random food location
179initGame :: IO Game
180```
181
182### `UI`
183
184To start, we need to determine what our `App s e n` type parameters are.
185This will completely describe the interface application and be passed
186to one of the library's `main` style functions for execution. Note that
187`s` is the app state, `e` is an event type, and `n` is a resource name.
188The `e` is abstracted so that we can provide custom events. The `n`
189is usually a custom sum type called `Name` which allows us to *name*
190particular viewports. This is important so that we can keep track of
191where the user currently has *focus*, such as typing in one of two
192textboxes; however, for this simple snake game we don't need to worry
193about that.
194
195In simpler cases, the state `s` can directly coincide with a core
196datatype such as our `Snake.Game`. In many cases however, it will be
197necessary to wrap the core state within the ui state `s` to keep track
198of things that are interface specific (more on this later).
199
200Let's write out our app definition and leave some undefined functions:
201
202```haskell
203{-# LANGUAGE OverloadedStrings #-}
204module UI where
205
206import Control.Monad (forever, void)
207import Control.Monad.IO.Class (liftIO)
208import Control.Concurrent (threadDelay, forkIO)
209import Data.Maybe (fromMaybe)
210
211import Snake
212
213import Brick
214  ( App(..), AttrMap, BrickEvent(..), EventM, Next, Widget
215  , customMain, neverShowCursor
216  , continue, halt
217  , hLimit, vLimit, vBox, hBox
218  , padRight, padLeft, padTop, padAll, Padding(..)
219  , withBorderStyle
220  , str
221  , attrMap, withAttr, emptyWidget, AttrName, on, fg
222  , (<+>)
223  )
224import Brick.BChan (newBChan, writeBChan)
225import qualified Brick.Widgets.Border as B
226import qualified Brick.Widgets.Border.Style as BS
227import qualified Brick.Widgets.Center as C
228import qualified Graphics.Vty as V
229import Data.Sequence (Seq)
230import qualified Data.Sequence as S
231import Linear.V2 (V2(..))
232import Lens.Micro ((^.))
233
234-- Types
235
236-- | Ticks mark passing of time
237--
238-- This is our custom event that will be constantly fed into the app.
239data Tick = Tick
240
241-- | Named resources
242--
243-- Not currently used, but will be easier to refactor
244-- if we call this "Name" now.
245type Name = ()
246
247data Cell = Snake | Food | Empty
248
249-- App definition
250
251app :: App Game Tick Name
252app = App { appDraw = drawUI
253          , appChooseCursor = neverShowCursor
254          , appHandleEvent = handleEvent
255          , appStartEvent = return
256          , appAttrMap = const theMap
257          }
258
259main :: IO ()
260main = undefined
261
262-- Handling events
263
264handleEvent :: Game -> BrickEvent Name Tick -> EventM Name (Next Game)
265handleEvent = undefined
266
267-- Drawing
268
269drawUI :: Game -> [Widget Name]
270drawUI = undefined
271
272theMap :: AttrMap
273theMap = undefined
274```
275
276#### Custom Events
277
278So far I've only used `brick` to make games which need to be redrawn
279as time passes, with or without user input. This requires using
280`Brick.customMain` with that `Tick` event type, and opening a forked
281process to `forever` feed that event type into the channel. Since this
282is a common scenario, there is a `Brick.BChan` module that makes this
283pretty quick:
284
285```haskell
286main :: IO ()
287main = do
288  chan <- newBChan 10
289  forkIO $ forever $ do
290    writeBChan chan Tick
291    threadDelay 100000 -- decides how fast your game moves
292  g <- initGame
293  let buildVty = V.mkVty V.defaultConfig
294  initialVty <- buildVty
295  void $ customMain initialVty buildVty (Just chan) app g
296```
297
298We do need to import `Vty.Graphics` since `customMain` allows us
299to specify a custom `IO Vty.Graphics.Vty` handle, but we're only
300customizing the existence of the event channel `BChan Tick`. The app
301is now bootstrapped, and all we need to do is implement `handleEvent`,
302`drawUI`, and `theMap` (handles styling).
303
304#### Handling events
305
306Handling events is largely straightforward, and can be very clean when
307your underlying application logic is taken care of in a core module. All
308we do is essentially map events to the proper state modifiers.
309
310```haskell
311handleEvent :: Game -> BrickEvent Name Tick -> EventM Name (Next Game)
312handleEvent g (AppEvent Tick)                       = continue $ step g
313handleEvent g (VtyEvent (V.EvKey V.KUp []))         = continue $ turn North g
314handleEvent g (VtyEvent (V.EvKey V.KDown []))       = continue $ turn South g
315handleEvent g (VtyEvent (V.EvKey V.KRight []))      = continue $ turn East g
316handleEvent g (VtyEvent (V.EvKey V.KLeft []))       = continue $ turn West g
317handleEvent g (VtyEvent (V.EvKey (V.KChar 'k') [])) = continue $ turn North g
318handleEvent g (VtyEvent (V.EvKey (V.KChar 'j') [])) = continue $ turn South g
319handleEvent g (VtyEvent (V.EvKey (V.KChar 'l') [])) = continue $ turn East g
320handleEvent g (VtyEvent (V.EvKey (V.KChar 'h') [])) = continue $ turn West g
321handleEvent g (VtyEvent (V.EvKey (V.KChar 'r') [])) = liftIO (initGame) >>= continue
322handleEvent g (VtyEvent (V.EvKey (V.KChar 'q') [])) = halt g
323handleEvent g (VtyEvent (V.EvKey V.KEsc []))        = halt g
324handleEvent g _                                     = continue g
325```
326
327It's probably obvious, but `continue` will continue execution with
328the supplied state value, which is then drawn. We can also `halt` to
329stop execution, which will essentially finish the evaluation of our
330`customMain` and result in `IO Game`, where the resulting game is the
331last value that we supplied to `halt`.
332
333#### Drawing
334
335Drawing is fairly simple as well but can require a good amount of code
336to position things how you want them. I like to break up the visual
337space into regions with drawing functions for each one.
338
339```haskell
340drawUI :: Game -> [Widget Name]
341drawUI g =
342  [ C.center $ padRight (Pad 2) (drawStats g) <+> drawGrid g ]
343
344drawStats :: Game -> Widget Name
345drawStats = undefined
346
347drawGrid :: Game -> Widget Name
348drawGrid = undefined
349```
350
351This will center the overall interface (`C.center`), put the stats and
352grid widgets horizontally side by side (`<+>`), and separate them by a
3532-character width (`padRight (Pad 2)`).
354
355Let's move forward with the stats column:
356
357```haskell
358drawStats :: Game -> Widget Name
359drawStats g = hLimit 11
360  $ vBox [ drawScore (g ^. score)
361         , padTop (Pad 2) $ drawGameOver (g ^. dead)
362         ]
363
364drawScore :: Int -> Widget Name
365drawScore n = withBorderStyle BS.unicodeBold
366  $ B.borderWithLabel (str "Score")
367  $ C.hCenter
368  $ padAll 1
369  $ str $ show n
370
371drawGameOver :: Bool -> Widget Name
372drawGameOver dead =
373  if dead
374     then withAttr gameOverAttr $ C.hCenter $ str "GAME OVER"
375     else emptyWidget
376
377gameOverAttr :: AttrName
378gameOverAttr = "gameOver"
379```
380
381I'm throwing in that `hLimit 11` to prevent the widget greediness caused
382by the outer `C.center`. I'm also using `vBox` to show some other
383options of aligning widgets; `vBox` and `hBox` align a list of widgets
384vertically and horizontally, respectfully. They can be thought of as
385folds over the binary `<=>` and `<+>` operations.
386
387The score is straightforward, but it is the first border in
388this tutorial. Borders are well documented in the [border
389demo](https://github.com/jtdaugherty/brick/blob/master/programs/BorderDemo.hs)
390and the Haddocks for that matter.
391
392We also only show the "game over" widget if the game is actually over.
393In that case, we are rendering the string widget with the `gameOverAttr`
394attribute name. Attribute names are basically type safe *names* that
395we can assign to widgets to apply predetermined styles, similar to
396assigning a class name to a div in HTML and defining the CSS styles for
397that class elsewhere.
398
399Attribute names implement `IsString`, so they are easy to construct with
400the `OverloadedStrings` pragma.
401
402Now for the main event:
403
404```haskell
405drawGrid :: Game -> Widget Name
406drawGrid g = withBorderStyle BS.unicodeBold
407  $ B.borderWithLabel (str "Snake")
408  $ vBox rows
409  where
410    rows         = [hBox $ cellsInRow r | r <- [height-1,height-2..0]]
411    cellsInRow y = [drawCoord (V2 x y) | x <- [0..width-1]]
412    drawCoord    = drawCell . cellAt
413    cellAt c
414      | c `elem` g ^. snake = Snake
415      | c == g ^. food      = Food
416      | otherwise           = Empty
417
418drawCell :: Cell -> Widget Name
419drawCell Snake = withAttr snakeAttr cw
420drawCell Food  = withAttr foodAttr cw
421drawCell Empty = withAttr emptyAttr cw
422
423cw :: Widget Name
424cw = str "  "
425
426snakeAttr, foodAttr, emptyAttr :: AttrName
427snakeAttr = "snakeAttr"
428foodAttr = "foodAttr"
429emptyAttr = "emptyAttr"
430
431```
432
433There's actually nothing new here! We've already covered all the
434`brick` functions necessary to draw the grid. My approach to grids is
435to render a square cell widget `cw` with different colors depending
436on the cell state. The easiest way to draw a colored square is to
437stick two characters side by side. If we assign an attribute with a
438matching foreground and background, then it doesn't matter what the two
439characters are (provided that they aren't some crazy Unicode characters
440that might render to an unexpected size). However, if we want empty
441cells to render with the same color as the user's default background
442color, then spaces are a good choice.
443
444Finally, we'll define the attribute map:
445
446```haskell
447theMap :: AttrMap
448theMap = attrMap V.defAttr
449  [ (snakeAttr, V.blue `on` V.blue)
450  , (foodAttr, V.red `on` V.red)
451  , (gameOverAttr, fg V.red `V.withStyle` V.bold)
452  ]
453```
454
455Again, styles aren't terribly complicated, but it
456will be one area where you might have to look in the
457[vty](http://hackage.haskell.org/package/vty) package (specifically
458[Graphics.Vty.Attributes](http://hackage.haskell.org/package/vty-5.15.1/docs/Graphics-Vty-Attributes.html)) to find what you need.
459
460Another thing to mention is that the attributes form a hierarchy and
461can be combined in a parent-child relationship via `mappend`. I haven't
462actually used this feature, but it does sound quite handy. For a more
463detailed discussion see the
464[Brick.AttrMap](https://hackage.haskell.org/package/brick-0.18/docs/Brick-AttrMap.html) haddocks.
465
466## Variable speed
467
468One difficult problem I encountered was implementing a variable speed in
469the GoL. I could have just used the same approach above with the minimum
470thread delay (corresponding to the maximum speed) and counted `Tick`
471events, only issuing an actual `step` in the game when the modular count
472of `Tick`s reached an amount corresponding to the current game speed,
473but that's kind of an ugly approach.
474
475Instead, I reached out to the author and he advised me to use a `TVar`
476within the app state.  I had never used `TVar`, but it's pretty easy!
477
478```haskell
479main :: IO ()
480main = do
481  chan <- newBChan 10
482  tv   <- atomically $ newTVar (spToInt initialSpeed)
483  forkIO $ forever $ do
484    writeBChan chan Tick
485    int <- atomically $ readTVar tv
486    threadDelay int
487  let buildVty = V.mkVty V.defaultConfig
488  initialVty <- buildVty
489  customMain initialVty buildVty (Just chan) app (initialGame tv)
490    >>= printResult
491```
492
493The `tv <- atomically $ newTVar (value :: a)` creates a new mutable
494reference to a value of type `a`, i.e. `TVar a`, and returns it in `IO`.
495In this case `value` is an `Int` which represents the delay between game
496steps. Then in the forked process, we read the delay from the `TVar`
497reference and use that to space out the calls to `writeBChan chan Tick`.
498
499I store that same `tv :: TVar Int` in the brick app state, so that the
500user can change the speed:
501
502```haskell
503handleEvent :: Game -> BrickEvent Name Tick -> EventM Name (Next Game)
504handleEvent g (VtyEvent (V.EvKey V.KRight [V.MCtrl])) = handleSpeed g (+)
505handleEvent g (VtyEvent (V.EvKey V.KLeft [V.MCtrl]))  = handleSpeed g (-)
506
507handleSpeed :: Game -> (Float -> Float -> Float) -> EventM n (Next Game)
508handleSpeed g (+/-) = do
509  let newSp = validS $ (g ^. speed) +/- speedInc
510  liftIO $ atomically $ writeTVar (g ^. interval) (spToInt newSp)
511  continue $ g & speed .~ newSp
512
513-- where
514
515-- | Speed increments = 0.01 gives 100 discrete speed settings
516speedInc :: Float
517speedInc = 0.01
518
519-- | Game state
520data Game = Game
521  { _board    :: Board -- ^ Board state
522  , _time     :: Int   -- ^ Time elapsed
523  , _paused   :: Bool  -- ^ Playing vs. paused
524  , _speed    :: Float -- ^ Speed in [0..1]
525  , _interval :: TVar Int -- ^ Interval kept in TVar
526  , _focus    :: F.FocusRing Name -- ^ Keeps track of grid focus
527  , _selected :: Cell -- ^ Keeps track of cell focus
528  }
529```
530
531## Conclusion
532
533`brick` let's you build TUIs very quickly. I was able to write `snake`
534along with this tutorial within a few hours. More complicated interfaces
535can be tougher, but if you can successfully separate the interface and
536core functionality, you'll have an easier time tacking on the frontend.
537
538Lastly, let me remind you to look in the
539[demo programs](https://github.com/jtdaugherty/brick/tree/master/programs)
540to figure stuff out, as *many* scenarios are covered throughout them.
541
542## Links
543* [brick](https://hackage.haskell.org/package/brick)
544* [snake](https://github.com/samtay/snake)
545* [tetris](https://github.com/samtay/tetris)
546* [conway](https://github.com/samtay/conway)
547