brick/programs/DialogDemo.hs

69 lines
1.7 KiB
Haskell
Raw Normal View History

2015-07-09 00:47:39 +03:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
2015-07-09 00:47:39 +03:00
module Main where
#if !(MIN_VERSION_base(4,11,0))
2015-07-09 00:47:39 +03:00
import Data.Monoid
#endif
2015-07-10 23:09:10 +03:00
import qualified Graphics.Vty as V
2015-07-09 00:47:39 +03:00
2015-07-10 23:09:10 +03:00
import qualified Brick.Main as M
import Brick.Types
2015-07-10 23:09:10 +03:00
( Widget
, BrickEvent(..)
)
import Brick.Widgets.Core
( padAll
2015-07-10 23:09:10 +03:00
, str
)
import qualified Brick.Widgets.Dialog as D
import qualified Brick.Widgets.Center as C
import qualified Brick.AttrMap as A
import Brick.Util (on, bg)
import qualified Brick.Types as T
2015-07-09 00:47:39 +03:00
data Choice = Red | Blue | Green
deriving Show
drawUI :: D.Dialog Choice -> [Widget ()]
2015-07-09 00:47:39 +03:00
drawUI d = [ui]
where
ui = D.renderDialog d $ C.hCenter $ padAll 1 $ str "This is the dialog body."
2015-07-09 00:47:39 +03:00
appEvent :: D.Dialog Choice -> BrickEvent () e -> T.EventM () (T.Next (D.Dialog Choice))
appEvent d (VtyEvent ev) =
2015-07-09 00:47:39 +03:00
case ev of
2015-07-10 23:09:10 +03:00
V.EvKey V.KEsc [] -> M.halt d
V.EvKey V.KEnter [] -> M.halt d
_ -> M.continue =<< D.handleDialogEvent ev d
appEvent d _ = M.continue d
2015-07-09 00:47:39 +03:00
initialState :: D.Dialog Choice
initialState = D.dialog (Just "Title") (Just (0, choices)) 50
2015-07-09 00:47:39 +03:00
where
choices = [ ("Red", Red)
, ("Blue", Blue)
, ("Green", Green)
]
2015-07-10 23:09:10 +03:00
theMap :: A.AttrMap
theMap = A.attrMap V.defAttr
[ (D.dialogAttr, V.white `on` V.blue)
, (D.buttonAttr, V.black `on` V.white)
, (D.buttonSelectedAttr, bg V.yellow)
2015-07-09 00:47:39 +03:00
]
theApp :: M.App (D.Dialog Choice) e ()
2015-07-09 00:47:39 +03:00
theApp =
2015-07-10 23:09:10 +03:00
M.App { M.appDraw = drawUI
, M.appChooseCursor = M.showFirstCursor
, M.appHandleEvent = appEvent
, M.appStartEvent = return
, M.appAttrMap = const theMap
}
2015-07-09 00:47:39 +03:00
main :: IO ()
main = do
2015-07-10 23:09:10 +03:00
d <- M.defaultMain theApp initialState
putStrLn $ "You chose: " <> show (D.dialogSelection d)