bhoogle - Building a simple hoogle GUI with brick
NB. This is using an old version of brick. Please see this post for a brick 1.1 updated version
Overview
bhoogle is a simple hoogle terminal GUI written using brick. This post is the annotated source code that should give you an idea of how to use brick and how easy brick makes building terminal UIs.
bhoogle
bhoogle is possibly useful as a local hoogle UI as well as a demo app. You can get the full code from github.
Setup
You will need an existing local hoogle database. If you do not already have one or are unsure, then do this
- Install hoogle (e.g.
stack install hoogle
) - Generate the default database (
hoogle generate
)
Build
You can then clone the code, or download one of the pre-build linux releases
Usage
- Enter a type search in the “type” edit box
- Press enter to search: focus goes directly to the results list
- Or press tab to search and focus will go to the “text” edit box
- You can then filter the results by typing in the “text” edit box, any result containing the sub-string typed will be shown
- Navigate the results by using arrow or vi (hjkl) keys
- Pressing ‘s’ in the results list will toggle the sort order
- Escape to exit
- Search-ahead is enable for any type search longer than three characters
Brick
There are a few conventions to get used to when building a brick UI, but I don’t think it should take you too long to get the hang of things.
The brick user guide and documentation are fantastic. Brick comes with multiple example apps that show controls and features being used. There are also third party tutorials e.g. Samuel Tay’s brick tutorial
bhoogle 0.1.1.0 source
If you have looked at the user guide or Samuel Tay’s tutorial you’ll already have some idea of the fundamental concepts. Below is the annotated source for bhoogle. As always feel free to email or contact me on twitter if anything is unclear and I’ll do my best to assist.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Protolude
import Control.Lens ((^.), (.~), (%~))
import Control.Lens.TH (makeLenses)
import qualified Data.List as Lst
import qualified Data.Time as Tm
import qualified Data.Text as Txt
import qualified Data.Vector as Vec
import Brick ((<+>), (<=>))
import qualified Brick as B
import qualified Brick.BChan as BCh
import qualified Brick.Focus as BF
import qualified Brick.AttrMap as BA
import qualified Brick.Widgets.List as BL
import qualified Brick.Widgets.Edit as BE
import qualified Brick.Widgets.Border as BB
import qualified Brick.Widgets.Border.Style as BBS
import Control.Concurrent (threadDelay, forkIO)
import qualified Graphics.Vty as V
import qualified Graphics.Vty.Input.Events as K
import qualified Hoogle as H
Import all the modules we’ll need. I’m using protolude as my custom prelude, changing to one of the others e.g. classy should be pretty simple if you prefer that.
I’m also using lens. The brick examples use lens so its worth getting used to. However I’m only using three of the simpler lenses, so if you don’t like lens or template haskell it should be easy enough to remove them.
-- | Events that can be sent
-- | Here there is just one event for updating the time
newtype Event = EventUpdateTime Tm.LocalTime
-- | Names use to identify each of the controls
data Name = TypeSearch
| TextSearch
| ListResults
deriving (Show, Eq, Ord)
Next we need to define the type of custom events that our brick application can handle and a sum type defining the “name” for each control we want to use.
In this example there is only a single event EventUpdateTime. It is sent once a second with the current time. This gets displayed by brick in the top right corner
There are three controls
- The edit box for the type to search for
- The edit box for the substring search
- The results listbox
-- | Sort order
data SortBy = SortNone
| SortAsc
| SortDec
deriving (Eq)
-- | State of the brick app. Contains the controls and any other required state
data BrickState = BrickState
{ _stEditType :: !(BE.Editor Text Name) -- ^ Editor for the type to search for
, _stEditText :: !(BE.Editor Text Name) -- ^ Editor for a text search in the results
, _stResultsList :: !(BL.List Name H.Target) -- ^ List for the search results
, _stFocus :: !(BF.FocusRing Name) -- ^ Focus ring - a circular list of focusable controls
, _stTime :: !Tm.LocalTime -- ^ The current time
, _stResults :: [H.Target] -- ^ The last set of search results from hoohle
, _stSortResults :: SortBy -- ^ Current sort order for the results
}
makeLenses ''BrickState
BrickState contains the current state of the brick application. Any event e.g. the custom update time event, or any key press event can result in the state being updated. There is a separate draw function that renders the state.
I.e. one part of the code deals with events, roughly state -> event -> state
and another handles the drawing state -> GUI
Here the state contains
- The three controls mentioned above (two edit + one listbox)
- A focus ring. (A focus ring is a circular list of control names that helps your code keep track of which control has the current focus).
- The last updated current time
- The last search result
- The current sort order, so that it can be toggled between ascending and descending
-- | Defines how the brick application will work / handle events
app :: B.App BrickState Event Name
app = B.App { B.appDraw = drawUI
, B.appChooseCursor = B.showFirstCursor
, B.appHandleEvent = handleEvent
, B.appStartEvent = pure
, B.appAttrMap = const theMap
}
The App type defines how the brick app operates, but defining how events are handled (appHandleEvent
) and how the GUI is drawn (appDraw
)
main :: IO ()
main = do
chan <- BCh.newBChan 5 -- ^ create a bounded channel for events
-- Send a tick event every 1 seconds with the current time
-- Brick will send this to our event handler which can then update the stTime field
void . forkIO $ forever $ do
t <- getTime
BCh.writeBChan chan $ EventUpdateTime t
threadDelay $ 1 * 1000000
-- Initial current time value
t <- getTime
-- Construct the initial state values
let st = BrickState { _stEditType = BE.editor TypeSearch (Just 1) ""
, _stEditText = BE.editor TextSearch (Just 1) ""
, _stResultsList = BL.list ListResults Vec.empty 1
, _stTime = t
, _stFocus = BF.focusRing [TypeSearch, TextSearch, ListResults]
, _stResults = []
, _stSortResults = SortNone
}
-- Run brick
void $ B.customMain (V.mkVty V.defaultConfig) (Just chan) app st
where
-- | Get the local time
getTime = do
t <- Tm.getCurrentTime
tz <- Tm.getCurrentTimeZone
pure $ Tm.utcToLocalTime tz t
In main some setup is preformed and then brick is started by calling customMain
.
For bhoogle the steps are
- Construct the channel for brick events (passed to
customMain
) - Create a new thread to send the current time every second
- Construct an initial state, with empty controls and search results
B.customMain
to run brick
-- | Main even handler for brick events
handleEvent :: BrickState -> B.BrickEvent Name Event -> B.EventM Name (B.Next BrickState)
handleEvent st ev =
case ev of
(B.AppEvent (EventUpdateTime time)) ->
-- Update the time in the state
B.continue $ st & stTime .~ time
handleEvent gets all the brick events, updates the state and decides how to continue.
Here the code matches the custom (B.AppEvent) event looking for our update time event (EventUpdateTime) and then updates the state with the current time. B.continue
means that brick continues after updating the state. Note that the UI is not changed in any way here, we are just altering the current state.
-- Handle keyboard events
-- k is the key
-- ms are the modifier keys
(B.VtyEvent ve@(V.EvKey k ms)) ->
case (k, ms) of
-- Escape quits the app, no matter what control has focus
(K.KEsc, []) -> B.halt st
Then the code matches any keyboard event (B.VtyEvent) here matching on the escape key (K.KEsc). So when the user clicks the escape key this handler will call B.halt
which will terminate the app. As this is done at the top level, this means that no matter which control has the focus, escape will exit.
_ ->
-- How to interpret the key press depends on which control is focused
case BF.focusGetCurrent $ st ^. stFocus of
For the rest of the key press logic, what bhoogle does depends on which control has the focus. BF.focusGetCurrent
is used to get that from the state’s focus ring.
Just TypeSearch ->
case k of
K.KChar '\t' -> do
-- Search, clear sort order, focus next
found <- doSearch st
B.continue . filterResults $ st & stFocus %~ BF.focusNext
& stResults .~ found
& stSortResults .~ SortNone
K.KBackTab ->do
-- Search, clear sort order, focus prev
found <- doSearch st
B.continue . filterResults $ st & stFocus %~ BF.focusPrev
& stResults .~ found
& stSortResults .~ SortNone
If the user is typing in the “type” edit box and tabs out (either tab or shift-tab) then
- Perform the search (see doSearch below)
- Update the current set of results
- Reset the sort order, default to the order that hoogle uses
- Move the focus to the next/previous control
K.KEnter -> do
-- Search, clear sort order, focus on results
-- This makes it faster if you want to search and navigate
-- results without tabing through the text search box
found <- doSearch st
B.continue . filterResults $ st & stResults .~ found
& stSortResults .~ SortNone
& stFocus %~ BF.focusSetCurrent ListResults
If the user presses enter while in the type search edit box, then
- Perform the search (see doSearch below)
- Update the current set of results
- Reset the sort order, default to the order that hoogle uses
- Move the focus directly to the results lisbox so they can navigate and see the current item’s details & help text
_ -> do
-- Let the editor handle all other events
r <- BE.handleEditorEvent ve $ st ^. stEditType
next <- liftIO . searchAhead doSearch $ st & stEditType .~ r
B.continue next
For all other key events for the type search, let the editor control handle the key press. This gives us editing, navigation etc for free.
Just TextSearch ->
case k of
K.KChar '\t' -> B.continue $ st & stFocus %~ BF.focusNext -- Focus next
K.KBackTab -> B.continue $ st & stFocus %~ BF.focusPrev -- Focus previous
_ -> do
-- Let the editor handle all other events
r <- BE.handleEditorEvent ve $ st ^. stEditText
B.continue . filterResults $ st & stEditText .~ r
For the text edit box
- Change focus on tab / shift-tab
- For all other keys
- Let the editor handle the key press
- Filter the hoogle results
Just ListResults ->
case k of
K.KChar '\t' -> B.continue $ st & stFocus %~ BF.focusNext -- Focus next
K.KBackTab -> B.continue $ st & stFocus %~ BF.focusPrev -- Focus previous
K.KChar 's' ->
-- Toggle the search order between ascending and descending,
-- use asc if sort order was 'none'
let sortDir = if (st ^. stSortResults) == SortAsc
then SortDec
else SortAsc
in
let sorter = if sortDir == SortDec
then (Lst.sortBy $ flip compareType)
else (Lst.sortBy compareType)
in
B.continue . filterResults $ st & stResults %~ sorter
& stSortResults .~ sortDir
_ -> do
-- Let the list handle all other events
-- Using handleListEventVi which adds vi-style keybindings for navigation
-- and the standard handleListEvent as a fallback for all other events
r <- BL.handleListEventVi BL.handleListEvent ve $ st ^. stResultsList
B.continue $ st & stResultsList .~ r
_ -> B.continue st
_ -> B.continue st
For the results listbox
- Handle tab / shift-tab
- Pressing the ‘s’ key will sort the results. Pressing it again toggles the direction, so keep track of which order was used last.
- For all other keys use
BL.handleListEventVi BL.handleListEvent
which gives us vi style navigation and uses the standard handleListEvent as the fallback, so that all the normal navigation (arrows) also work.
where
doSearch st' =
liftIO $ searchHoogle (Txt.strip . Txt.concat $ BE.getEditContents (st' ^. stEditType))
And finally for handleEvent the doSearch function which calls the searchHoogle function (below) to search on the text from the type editbox.
-- | Search ahead for type strings longer than 3 chars.
searchAhead :: (BrickState -> IO [H.Target]) -> BrickState -> IO BrickState
searchAhead search st =
let searchText = Txt.strip . Txt.concat . BE.getEditContents $ st ^. stEditType in
if Txt.length searchText > 3
then do
-- Search
found <- search st
pure . filterResults $ st & stResults .~ found
& stSortResults .~ SortNone
else
-- Just clear
pure $ st & stResults .~ []
& stResultsList %~ BL.listClear
searchAhead is a helper function that searches hoogle as the user types. As long as there are more than three characters being searched for. Without this limit hoogle seems a bit slow on my machine because of the large number of results.
-- | Filter the results from hoogle using the search text
filterResults :: BrickState -> BrickState
filterResults st =
let allResults = st ^. stResults in
let filterText = Txt.toLower . Txt.strip . Txt.concat . BE.getEditContents $ st ^. stEditText in
let results =
if Txt.null filterText
then allResults
else filter (\t -> Txt.isInfixOf filterText . Txt.toLower $ formatResult t) allResults
in
st & stResultsList .~ BL.list ListResults (Vec.fromList results) 1
Filter the hoogle results by doing a sub-string search if the user has entered one
-- | Draw the UI
drawUI :: BrickState -> [B.Widget Name]
drawUI st =
[B.padAll 1 contentBlock]
where
contentBlock =
(B.withBorderStyle BBS.unicode $ BB.border searchBlock)
<=>
B.padTop (B.Pad 1) resultsBlock
resultsBlock =
let total = show . length $ st ^. stResults in
let showing = show . length $ st ^. stResultsList ^. BL.listElementsL in
(B.withAttr "infoTitle" $ B.txt "Results: ") <+> B.txt (showing <> "/" <> total)
<=>
(B.padTop (B.Pad 1) $
resultsContent <+> resultsDetail
)
resultsContent =
BL.renderList (\_ e -> B.txt $ formatResult e) False (st ^. stResultsList)
resultsDetail =
B.padLeft (B.Pad 1) $
B.hLimit 60 $
vtitle "package:"
<=>
B.padLeft (B.Pad 2) (B.txt $ getSelectedDetail (\t -> maybe "" (Txt.pack . fst) (H.targetPackage t)))
<=>
vtitle "module:"
<=>
B.padLeft (B.Pad 2) (B.txt $ getSelectedDetail (\t -> maybe "" (Txt.pack . fst) (H.targetModule t)))
<=>
vtitle "docs:"
<=>
B.padLeft (B.Pad 2) (B.txt $ getSelectedDetail (Txt.pack . clean . H.targetDocs))
<=>
B.fill ' '
searchBlock =
((htitle "Type: " <+> editor TypeSearch (st ^. stEditType)) <+> time (st ^. stTime))
<=>
(htitle "Text: " <+> editor TextSearch (st ^. stEditText))
htitle t =
B.hLimit 20 $
B.withAttr "infoTitle" $
B.txt t
vtitle t =
B.withAttr "infoTitle" $
B.txt t
editor n e =
B.vLimit 1 $
BE.renderEditor (B.txt . Txt.unlines) (BF.focusGetCurrent (st ^. stFocus) == Just n) e
time t =
B.padLeft (B.Pad 1) $
B.hLimit 20 $
B.withAttr "time" $
B.str (Tm.formatTime Tm.defaultTimeLocale "%H-%M-%S" t)
getSelectedDetail fn =
case BL.listSelectedElement $ st ^. stResultsList of
Nothing -> ""
Just (_, e) -> fn e
drawUI renders the state and creates the GUI. At first this may take some getting used to, but you will soon be able to see the GUI structure from the code.
<=>
means horizontal break, i.e. next “line”<+>
means “next to”- I often end up formatting code slightly differently to how I would in the other functions to better communicate the structure
Create small GUI fragments/“controls” and combine them with
For example htitle creates a “title” by<+>
and<=>
- Limiting the max width to 20
- Setting the attribute to infoTitle
- Displaying the text using
B.txt
(B.txt
displays a Text,B.str
displays a string/[char])
B.fill ' '
is used to get brick to fill to the maximum width (here 60) rather that having the right detail pain growing/shrinking as the data changes.
theMap :: BA.AttrMap
theMap = BA.attrMap V.defAttr [ (BE.editAttr , V.black `B.on` V.cyan)
, (BE.editFocusedAttr , V.black `B.on` V.yellow)
, (BL.listAttr , V.white `B.on` V.blue)
, (BL.listSelectedAttr, V.blue `B.on` V.white)
, ("infoTitle" , B.fg V.cyan)
, ("time" , B.fg V.yellow)
]
The attribute map is where attributes for the controls and custom attributes are defined. This makes it easy to change how the GUI looks. There is even support for themes and basic markup.
----------------------------------------------------------------------------------------------
-- | Compare two hoogle results for sorting
compareType :: H.Target -> H.Target -> Ordering
compareType a b =
compare (formatResult a) (formatResult b)
-- | Search hoogle using the default hoogle database
searchHoogle :: Text -> IO [H.Target]
searchHoogle f = do
d <- H.defaultDatabaseLocation
H.withDatabase d (\x -> pure $ H.searchDatabase x (Txt.unpack f))
-- | Format the hoogle results so they roughly match what the terminal app would show
formatResult :: H.Target -> Text
formatResult t =
let typ = clean $ H.targetItem t in
let m = (clean . fst) <$> H.targetModule t in
Txt.pack $ fromMaybe "" m <> " :: " <> typ
clean :: [Char] -> [Char]
clean = unescapeHTML . stripTags
-- | From hoogle source: https://hackage.haskell.org/package/hoogle-5.0.16/docs/src/General-Util.html
unescapeHTML :: [Char] -> [Char]
unescapeHTML ('&':xs)
| Just x <- Lst.stripPrefix "lt;" xs = '<' : unescapeHTML x
| Just x <- Lst.stripPrefix "gt;" xs = '>' : unescapeHTML x
| Just x <- Lst.stripPrefix "amp;" xs = '&' : unescapeHTML x
| Just x <- Lst.stripPrefix "quot;" xs = '\"' : unescapeHTML x
unescapeHTML (x:xs) = x : unescapeHTML xs
unescapeHTML [] = []
-- | From hakyll source: https://hackage.haskell.org/package/hakyll-4.1.2.1/docs/src/Hakyll-Web-Html.html#stripTags
stripTags :: [Char] -> [Char]
stripTags [] = []
stripTags ('<' : xs) = stripTags $ drop 1 $ dropWhile (/= '>') xs
stripTags (x : xs) = x : stripTags xs
The remainder of the code is non-brick code for searching and formatting hoogle results
- compareType compares two results by formatting them first and then comparing the resulting text
- searchHoogle searches hoogle using the default database
- formatResults formats the hoogle results
- unescapeHTML and stripTags are used to get plain text from the HTML. Note that this code comes from the hakyll and hoogle source code
Hopefully this example helps you get started with brick and demonstrates how easy brick makes creating terminal UIs
Links
- Code on github
- Releases with prebuilt linux binaries
- Brick user guide
- Samuel Tay’s brick tutorial
- Latest version on hackage - NB code does not match the annotated source above
- Latest version on github - NB code does not match the annotated source above