Skip to content

Instantly share code, notes, and snippets.

@jtdaugherty
Created December 25, 2017 17:56
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save jtdaugherty/8c3eed3c4dae9e1c177886f96b5a31c3 to your computer and use it in GitHub Desktop.
Save jtdaugherty/8c3eed3c4dae9e1c177886f96b5a31c3 to your computer and use it in GitHub Desktop.
Multi-selection list demo
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Lens.Micro.Platform ((^.), _1, (%~), (&), ix)
import Control.Monad (void)
import Data.Monoid
import Data.Maybe (fromMaybe)
import qualified Graphics.Vty as V
import qualified Brick.Main as M
import qualified Brick.Types as T
import qualified Brick.Widgets.Border as B
import qualified Brick.Widgets.List as L
import qualified Brick.Widgets.Center as C
import qualified Brick.AttrMap as A
import qualified Data.Vector as Vec
import Brick.Types
( Widget
)
import Brick.Widgets.Core
( (<+>)
, str
, vLimit
, hLimit
, vBox
, withAttr
)
import Brick.Util (fg, on)
drawUI :: (Show a) => L.List () (Bool, a) -> [Widget ()]
drawUI l = [ui]
where
label = str "Item " <+> cur <+> str " of " <+> total
cur = case l^.(L.listSelectedL) of
Nothing -> str "-"
Just i -> str (show (i + 1))
total = str $ show $ Vec.length $ l^.(L.listElementsL)
box = B.borderWithLabel label $
hLimit 25 $
vLimit 15 $
L.renderList listDrawElement True l
ui = C.vCenter $ vBox [ C.hCenter box
, str " "
, C.hCenter $ str "Press +/- to add/remove list elements."
, C.hCenter $ str "Press Space to toggle element selection."
, C.hCenter $ str "Press Esc to exit."
]
appEvent :: L.List () (Bool, Char) -> T.BrickEvent () e -> T.EventM () (T.Next (L.List () (Bool, Char)))
appEvent l (T.VtyEvent e) =
case e of
V.EvKey (V.KChar ' ') [] ->
case l^.(L.listSelectedL) of
Nothing -> M.continue l
Just i -> M.continue $ l & L.listElementsL.ix i._1 %~ not
V.EvKey (V.KChar '+') [] ->
let el = nextElement (L.listElements l)
pos = Vec.length $ l^.(L.listElementsL)
in M.continue $ L.listInsert pos (False, el) l
V.EvKey (V.KChar '-') [] ->
case l^.(L.listSelectedL) of
Nothing -> M.continue l
Just i -> M.continue $ L.listRemove i l
V.EvKey V.KEsc [] -> M.halt l
ev -> M.continue =<< L.handleListEvent ev l
where
nextElement :: Vec.Vector (Bool, Char) -> Char
nextElement v = fromMaybe '?' $ Vec.find (flip Vec.notElem $ snd <$> v) (Vec.fromList ['a' .. 'z'])
appEvent l _ = M.continue l
listDrawElement :: (Show a) => Bool -> (Bool, a) -> Widget ()
listDrawElement sel (sel2, a) =
let selStr s = if sel
then withAttr customAttr (str $ "<" <> s <> ">")
else str s
sel2Str = if sel2
then withAttr multiSelectAttr
else id
in sel2Str $ C.hCenter $ str "Item " <+> (selStr $ show a)
initialState :: L.List () (Bool, Char)
initialState = L.list () (Vec.fromList ((False,) <$> ['a','b','c'])) 1
customAttr :: A.AttrName
customAttr = L.listSelectedAttr <> "custom"
multiSelectAttr :: A.AttrName
multiSelectAttr = "multiSelect"
theMap :: A.AttrMap
theMap = A.attrMap V.defAttr
[ (L.listAttr, V.white `on` V.blue)
, (L.listSelectedAttr, V.blue `on` V.white)
, (customAttr, fg V.cyan)
, (multiSelectAttr, V.white `on` V.magenta)
]
theApp :: M.App (L.List () (Bool, Char)) e ()
theApp =
M.App { M.appDraw = drawUI
, M.appChooseCursor = M.showFirstCursor
, M.appHandleEvent = appEvent
, M.appStartEvent = return
, M.appAttrMap = const theMap
}
main :: IO ()
main = void $ M.defaultMain theApp initialState
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment