-
Notifications
You must be signed in to change notification settings - Fork 164
/
CustomEventDemo.hs
86 lines (74 loc) · 1.85 KB
/
CustomEventDemo.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
module Main where
import Lens.Micro ((^.))
import Lens.Micro.TH (makeLenses)
import Lens.Micro.Mtl
import Control.Monad (void, forever)
import Control.Concurrent (threadDelay, forkIO)
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid
#endif
import qualified Graphics.Vty as V
import Brick.BChan
import Brick.Main
( App(..)
, showFirstCursor
, customMainWithDefaultVty
, halt
)
import Brick.AttrMap
( attrMap
)
import Brick.Types
( Widget
, EventM
, BrickEvent(..)
)
import Brick.Widgets.Core
( (<=>)
, str
)
data CustomEvent = Counter deriving Show
data St =
St { _stLastBrickEvent :: Maybe (BrickEvent () CustomEvent)
, _stCounter :: Int
}
makeLenses ''St
drawUI :: St -> [Widget ()]
drawUI st = [a]
where
a = (str $ "Last event: " <> (show $ st^.stLastBrickEvent))
<=>
(str $ "Counter value is: " <> (show $ st^.stCounter))
appEvent :: BrickEvent () CustomEvent -> EventM () St ()
appEvent e =
case e of
VtyEvent (V.EvKey V.KEsc []) -> halt
VtyEvent _ -> stLastBrickEvent .= (Just e)
AppEvent Counter -> do
stCounter %= (+1)
stLastBrickEvent .= (Just e)
_ -> return ()
initialState :: St
initialState =
St { _stLastBrickEvent = Nothing
, _stCounter = 0
}
theApp :: App St CustomEvent ()
theApp =
App { appDraw = drawUI
, appChooseCursor = showFirstCursor
, appHandleEvent = appEvent
, appStartEvent = return ()
, appAttrMap = const $ attrMap V.defAttr []
}
main :: IO ()
main = do
chan <- newBChan 10
void $ forkIO $ forever $ do
writeBChan chan Counter
threadDelay 1000000
(_, vty) <- customMainWithDefaultVty (Just chan) theApp initialState
V.shutdown vty