2015-06-26 09:34:20 +03:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
2018-03-17 19:03:30 +03:00
|
|
|
{-# LANGUAGE CPP #-}
|
2015-06-26 09:34:20 +03:00
|
|
|
module Main where
|
|
|
|
|
2016-05-09 04:05:30 +03:00
|
|
|
import Lens.Micro ((^.), (&), (.~), (%~))
|
|
|
|
import Lens.Micro.TH (makeLenses)
|
2015-06-26 09:34:20 +03:00
|
|
|
import Control.Monad (void, forever)
|
2017-01-07 11:42:59 +03:00
|
|
|
import Control.Concurrent (threadDelay, forkIO)
|
2018-03-17 19:03:30 +03:00
|
|
|
#if !(MIN_VERSION_base(4,11,0))
|
2015-06-26 09:34:20 +03:00
|
|
|
import Data.Monoid
|
2018-03-17 19:03:30 +03:00
|
|
|
#endif
|
2015-07-10 23:03:49 +03:00
|
|
|
import qualified Graphics.Vty as V
|
2015-06-26 09:34:20 +03:00
|
|
|
|
2017-01-07 11:42:59 +03:00
|
|
|
import Brick.BChan
|
2015-06-26 09:34:20 +03:00
|
|
|
import Brick.Main
|
2015-07-10 23:03:49 +03:00
|
|
|
( App(..)
|
|
|
|
, showFirstCursor
|
|
|
|
, customMain
|
|
|
|
, continue
|
|
|
|
, halt
|
|
|
|
)
|
2017-01-25 00:48:45 +03:00
|
|
|
import Brick.AttrMap
|
|
|
|
( attrMap
|
|
|
|
)
|
2015-08-20 05:40:06 +03:00
|
|
|
import Brick.Types
|
2015-07-10 23:03:49 +03:00
|
|
|
( Widget
|
2015-08-20 05:48:55 +03:00
|
|
|
, Next
|
|
|
|
, EventM
|
2016-10-26 06:19:31 +03:00
|
|
|
, BrickEvent(..)
|
2015-08-20 05:40:06 +03:00
|
|
|
)
|
|
|
|
import Brick.Widgets.Core
|
|
|
|
( (<=>)
|
2015-07-10 23:03:49 +03:00
|
|
|
, str
|
|
|
|
)
|
2015-06-26 09:34:20 +03:00
|
|
|
|
2016-10-26 06:19:31 +03:00
|
|
|
data CustomEvent = Counter deriving Show
|
|
|
|
|
2015-06-26 09:34:20 +03:00
|
|
|
data St =
|
2016-10-26 06:19:31 +03:00
|
|
|
St { _stLastBrickEvent :: Maybe (BrickEvent () CustomEvent)
|
2015-06-26 09:34:20 +03:00
|
|
|
, _stCounter :: Int
|
|
|
|
}
|
|
|
|
|
|
|
|
makeLenses ''St
|
|
|
|
|
2016-03-05 01:42:49 +03:00
|
|
|
drawUI :: St -> [Widget ()]
|
2015-06-26 09:34:20 +03:00
|
|
|
drawUI st = [a]
|
|
|
|
where
|
2016-10-26 06:19:31 +03:00
|
|
|
a = (str $ "Last event: " <> (show $ st^.stLastBrickEvent))
|
2015-06-26 09:34:20 +03:00
|
|
|
<=>
|
|
|
|
(str $ "Counter value is: " <> (show $ st^.stCounter))
|
|
|
|
|
2016-10-26 06:19:31 +03:00
|
|
|
appEvent :: St -> BrickEvent () CustomEvent -> EventM () (Next St)
|
2015-07-01 23:05:28 +03:00
|
|
|
appEvent st e =
|
2015-06-26 09:34:20 +03:00
|
|
|
case e of
|
2015-07-10 23:03:49 +03:00
|
|
|
VtyEvent (V.EvKey V.KEsc []) -> halt st
|
2016-10-26 06:19:31 +03:00
|
|
|
VtyEvent _ -> continue $ st & stLastBrickEvent .~ (Just e)
|
|
|
|
AppEvent Counter -> continue $ st & stCounter %~ (+1)
|
|
|
|
& stLastBrickEvent .~ (Just e)
|
2016-10-26 06:44:22 +03:00
|
|
|
_ -> continue st
|
2015-06-26 09:34:20 +03:00
|
|
|
|
|
|
|
initialState :: St
|
|
|
|
initialState =
|
2016-10-26 06:19:31 +03:00
|
|
|
St { _stLastBrickEvent = Nothing
|
2015-06-26 09:34:20 +03:00
|
|
|
, _stCounter = 0
|
|
|
|
}
|
|
|
|
|
2016-03-05 01:42:49 +03:00
|
|
|
theApp :: App St CustomEvent ()
|
2015-06-26 09:34:20 +03:00
|
|
|
theApp =
|
|
|
|
App { appDraw = drawUI
|
|
|
|
, appChooseCursor = showFirstCursor
|
|
|
|
, appHandleEvent = appEvent
|
2015-07-01 05:15:29 +03:00
|
|
|
, appStartEvent = return
|
2017-01-25 00:48:45 +03:00
|
|
|
, appAttrMap = const $ attrMap V.defAttr []
|
2015-06-26 09:34:20 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
main :: IO ()
|
|
|
|
main = do
|
2017-01-07 11:42:59 +03:00
|
|
|
chan <- newBChan 10
|
2015-06-26 09:34:20 +03:00
|
|
|
|
2020-02-29 02:05:48 +03:00
|
|
|
void $ forkIO $ forever $ do
|
2017-01-07 11:42:59 +03:00
|
|
|
writeBChan chan Counter
|
2015-06-26 09:34:20 +03:00
|
|
|
threadDelay 1000000
|
|
|
|
|
2019-03-19 18:25:49 +03:00
|
|
|
let buildVty = V.mkVty V.defaultConfig
|
|
|
|
initialVty <- buildVty
|
|
|
|
void $ customMain initialVty buildVty (Just chan) theApp initialState
|