brick/programs/ListDemo.hs

95 lines
2.7 KiB
Haskell
Raw Normal View History

2015-06-28 23:06:22 +03:00
{-# LANGUAGE OverloadedStrings #-}
module Main where
2015-07-10 23:25:44 +03:00
import Control.Lens ((^.))
2015-06-28 23:06:22 +03:00
import Control.Monad (void)
import Data.Monoid
2015-07-10 23:25:44 +03:00
import qualified Graphics.Vty as V
2015-06-28 23:06:22 +03:00
2015-07-10 23:25:44 +03:00
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 V
import Brick.Types
2015-07-10 23:25:44 +03:00
( Widget
)
import Brick.Widgets.Core
( (<+>)
2015-07-10 23:25:44 +03:00
, str
, vLimit
, hLimit
, vBox
, withAttr
)
2015-07-12 02:53:06 +03:00
import Brick.Util (fg, on)
2015-06-28 23:06:22 +03:00
2015-07-10 23:25:44 +03:00
drawUI :: L.List Int -> [Widget]
2015-06-28 23:22:05 +03:00
drawUI l = [ui]
2015-06-28 23:06:22 +03:00
where
label = str "Item " <+> cur <+> str " of " <+> total
2015-07-10 23:25:44 +03:00
cur = case l^.(L.listSelectedL) of
Nothing -> str "-"
2015-06-28 23:06:22 +03:00
Just i -> str (show (i + 1))
2015-08-18 19:39:58 +03:00
total = str $ show $ V.length $ l^.(L.listElementsL)
2015-07-10 23:25:44 +03:00
box = B.borderWithLabel label $
2015-06-28 23:15:15 +03:00
hLimit 25 $
vLimit 15 $
L.renderList l listDrawElement
2015-07-10 23:25:44 +03:00
ui = C.vCenter $ vBox [ C.hCenter box
, str " "
, C.hCenter $ str "Press +/- to add/remove list elements."
, C.hCenter $ str "Press Esc to exit."
2015-07-10 23:25:44 +03:00
]
2015-06-28 23:06:22 +03:00
appEvent :: L.List Int -> V.Event -> T.EventM (T.Next (L.List Int))
appEvent l e =
2015-06-28 23:06:22 +03:00
case e of
2015-07-10 23:25:44 +03:00
V.EvKey (V.KChar '+') [] ->
2015-08-18 19:39:58 +03:00
let el = V.length $ l^.(L.listElementsL)
2015-07-10 23:25:44 +03:00
in M.continue $ L.listInsert el el l
2015-06-28 23:06:22 +03:00
2015-07-10 23:25:44 +03:00
V.EvKey (V.KChar '-') [] ->
case l^.(L.listSelectedL) of
Nothing -> M.continue l
Just i -> M.continue $ L.listRemove i l
2015-06-28 23:15:15 +03:00
2015-07-10 23:25:44 +03:00
V.EvKey V.KEsc [] -> M.halt l
2015-06-28 23:06:22 +03:00
2015-08-20 05:52:34 +03:00
ev -> M.continue =<< T.handleEvent ev l
2015-06-28 23:06:22 +03:00
listDrawElement :: Bool -> Int -> Widget
listDrawElement sel i =
let selStr s = if sel
then withAttr customAttr (str $ "<" <> s <> ">")
2015-06-28 23:06:22 +03:00
else str s
in C.hCenter $ str "Item " <+> (selStr $ show i)
2015-06-28 23:06:22 +03:00
2015-07-10 23:25:44 +03:00
initialState :: L.List Int
initialState = L.list (T.Name "list") (V.fromList [0, 1, 2]) 1
2015-06-28 23:06:22 +03:00
2015-07-10 23:25:44 +03:00
customAttr :: A.AttrName
customAttr = L.listSelectedAttr <> "custom"
2015-06-28 23:06:22 +03:00
2015-07-10 23:25:44 +03:00
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)
2015-06-28 23:06:22 +03:00
]
2015-07-10 23:25:44 +03:00
theApp :: M.App (L.List Int) V.Event
2015-06-28 23:06:22 +03:00
theApp =
2015-07-10 23:25:44 +03:00
M.App { M.appDraw = drawUI
, M.appChooseCursor = M.showFirstCursor
, M.appHandleEvent = appEvent
, M.appStartEvent = return
, M.appAttrMap = const theMap
, M.appLiftVtyEvent = id
2015-07-10 23:25:44 +03:00
}
2015-06-28 23:06:22 +03:00
main :: IO ()
2015-07-10 23:25:44 +03:00
main = void $ M.defaultMain theApp initialState