2018-03-17 19:03:30 +03:00
|
|
|
{-# LANGUAGE CPP #-}
|
2015-06-28 23:06:22 +03:00
|
|
|
module Main where
|
|
|
|
|
2016-05-09 04:05:30 +03:00
|
|
|
import Lens.Micro ((^.))
|
2022-07-17 09:10:03 +03:00
|
|
|
import Lens.Micro.Mtl
|
2015-06-28 23:06:22 +03:00
|
|
|
import Control.Monad (void)
|
2022-07-17 09:10:03 +03:00
|
|
|
import Control.Monad.State (modify)
|
2018-03-17 19:03:30 +03:00
|
|
|
#if !(MIN_VERSION_base(4,11,0))
|
2015-06-28 23:06:22 +03:00
|
|
|
import Data.Monoid
|
2018-03-17 19:03:30 +03:00
|
|
|
#endif
|
2015-10-22 12:26:51 +03:00
|
|
|
import Data.Maybe (fromMaybe)
|
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
|
2016-05-15 19:34:07 +03:00
|
|
|
import qualified Data.Vector as Vec
|
2015-08-20 05:40:06 +03:00
|
|
|
import Brick.Types
|
2015-07-10 23:25:44 +03:00
|
|
|
( Widget
|
2015-08-20 05:40:06 +03:00
|
|
|
)
|
|
|
|
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
|
|
|
|
2016-03-05 01:42:49 +03:00
|
|
|
drawUI :: (Show a) => L.List () a -> [Widget ()]
|
2015-06-28 23:22:05 +03:00
|
|
|
drawUI l = [ui]
|
2015-06-28 23:06:22 +03:00
|
|
|
where
|
2015-08-20 05:40:06 +03:00
|
|
|
label = str "Item " <+> cur <+> str " of " <+> total
|
2015-07-10 23:25:44 +03:00
|
|
|
cur = case l^.(L.listSelectedL) of
|
2015-08-20 05:40:06 +03:00
|
|
|
Nothing -> str "-"
|
2015-06-28 23:06:22 +03:00
|
|
|
Just i -> str (show (i + 1))
|
2016-05-15 19:34:07 +03:00
|
|
|
total = str $ show $ Vec.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 $
|
2016-03-05 02:50:10 +03:00
|
|
|
L.renderList listDrawElement True l
|
2015-07-10 23:25:44 +03:00
|
|
|
ui = C.vCenter $ vBox [ C.hCenter box
|
2015-08-20 05:40:06 +03:00
|
|
|
, 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
|
|
|
|
2022-07-17 09:10:03 +03:00
|
|
|
appEvent :: T.BrickEvent () e -> T.EventM () (L.List () Char) ()
|
|
|
|
appEvent (T.VtyEvent e) =
|
2015-06-28 23:06:22 +03:00
|
|
|
case e of
|
2022-07-17 09:10:03 +03:00
|
|
|
V.EvKey (V.KChar '+') [] -> do
|
|
|
|
els <- use L.listElementsL
|
|
|
|
let el = nextElement els
|
|
|
|
pos = Vec.length els
|
|
|
|
modify $ L.listInsert pos el
|
2015-06-28 23:06:22 +03:00
|
|
|
|
2022-07-17 09:10:03 +03:00
|
|
|
V.EvKey (V.KChar '-') [] -> do
|
|
|
|
sel <- use L.listSelectedL
|
|
|
|
case sel of
|
|
|
|
Nothing -> return ()
|
|
|
|
Just i -> modify $ L.listRemove i
|
2015-06-28 23:15:15 +03:00
|
|
|
|
2022-07-17 09:10:03 +03:00
|
|
|
V.EvKey V.KEsc [] -> M.halt
|
2015-06-28 23:06:22 +03:00
|
|
|
|
2022-07-17 09:10:03 +03:00
|
|
|
ev -> L.handleListEvent ev
|
2015-10-22 12:26:51 +03:00
|
|
|
where
|
2016-05-15 19:34:07 +03:00
|
|
|
nextElement :: Vec.Vector Char -> Char
|
|
|
|
nextElement v = fromMaybe '?' $ Vec.find (flip Vec.notElem v) (Vec.fromList ['a' .. 'z'])
|
2022-07-17 09:10:03 +03:00
|
|
|
appEvent _ = return ()
|
2015-06-28 23:06:22 +03:00
|
|
|
|
2016-03-05 01:42:49 +03:00
|
|
|
listDrawElement :: (Show a) => Bool -> a -> Widget ()
|
2015-10-22 12:26:51 +03:00
|
|
|
listDrawElement sel a =
|
2015-06-28 23:06:22 +03:00
|
|
|
let selStr s = if sel
|
2015-06-29 08:08:54 +03:00
|
|
|
then withAttr customAttr (str $ "<" <> s <> ">")
|
2015-06-28 23:06:22 +03:00
|
|
|
else str s
|
2015-10-22 12:26:51 +03:00
|
|
|
in C.hCenter $ str "Item " <+> (selStr $ show a)
|
2015-06-28 23:06:22 +03:00
|
|
|
|
2016-03-05 01:42:49 +03:00
|
|
|
initialState :: L.List () Char
|
2016-05-20 06:29:12 +03:00
|
|
|
initialState = L.list () (Vec.fromList ['a','b','c']) 1
|
2015-06-28 23:06:22 +03:00
|
|
|
|
2015-07-10 23:25:44 +03:00
|
|
|
customAttr :: A.AttrName
|
2022-08-05 04:44:57 +03:00
|
|
|
customAttr = L.listSelectedAttr <> A.attrName "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
|
|
|
]
|
|
|
|
|
2016-10-26 06:19:31 +03:00
|
|
|
theApp :: M.App (L.List () Char) e ()
|
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
|
2022-07-17 09:10:03 +03:00
|
|
|
, M.appStartEvent = return ()
|
2015-07-10 23:25:44 +03:00
|
|
|
, M.appAttrMap = const theMap
|
|
|
|
}
|
2015-06-28 23:06:22 +03:00
|
|
|
|
|
|
|
main :: IO ()
|
2015-07-10 23:25:44 +03:00
|
|
|
main = void $ M.defaultMain theApp initialState
|