Skip to content

Instantly share code, notes, and snippets.

@andrevdm
Last active November 12, 2017 08:02
Show Gist options
  • Save andrevdm/b67cee0c4533bd11102d727eda9c4271 to your computer and use it in GitHub Desktop.
Save andrevdm/b67cee0c4533bd11102d727eda9c4271 to your computer and use it in GitHub Desktop.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Protolude
import Brick ((<+>))
import qualified Brick as B
import qualified Brick.Widgets.List as BL
import qualified Brick.Widgets.Center as BC
import qualified Brick.BChan as BCh
import qualified Brick.Widgets.Border as BB
import qualified Brick.Widgets.Border.Style as BBS
import qualified Graphics.Vty as V
import qualified Brick.AttrMap as BA
import qualified Data.Vector as Vec
main :: IO ()
main = do
chan <- BCh.newBChan 10
let items = Vec.fromList ["a", "b", "ccc"]
let g = St $ BL.list () items 1
void $ B.customMain (V.mkVty V.defaultConfig) (Just chan) app g
type Name = ()
data Event = Event
data St = St { stList :: BL.List Name Text }
app :: B.App St Event Name
app = B.App { B.appDraw = drawUI
, B.appChooseCursor = B.showFirstCursor
, B.appHandleEvent = handleEvent
, B.appStartEvent = pure
, B.appAttrMap = const theMap
}
handleEvent :: St -> B.BrickEvent Name Event -> B.EventM Name (B.Next St)
handleEvent g (B.VtyEvent (V.EvKey V.KEsc [])) = B.halt g
handleEvent g (B.VtyEvent e) = do
r <- BL.handleListEvent e (stList g)
B.continue $ g { stList = r }
handleEvent g _ = B.continue g
-- Drawing
drawUI :: St -> [B.Widget Name]
drawUI g =
[ B.hLimit 50 $
B.withBorderStyle BBS.unicodeRounded $
BB.borderWithLabel (B.str "menu") $
B.padAll 1 $
BL.renderList listDrawElement True (stList g)
]
listDrawElement :: (Show a) => Bool -> a -> B.Widget ()
listDrawElement sel a =
let selStr s = if sel
then B.withAttr customAttr (B.str $ "<" <> s <> ">")
else B.str s
in BC.hCenter $ B.str "Item " <+> selStr (show a)
customAttr :: BA.AttrName
customAttr = BL.listSelectedAttr <> "custom"
theMap :: BA.AttrMap
theMap = BA.attrMap V.defAttr [ (BL.listAttr, V.white `B.on` V.blue)
, (BL.listSelectedAttr, V.blue `B.on` V.white)
, (customAttr, B.fg V.cyan)
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment