brick/programs/LayerDemo.hs

68 lines
2.1 KiB
Haskell
Raw Normal View History

2015-07-04 01:49:33 +03:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
2015-07-10 23:20:05 +03:00
import Control.Lens (makeLenses, (^.), (&), (%~))
2015-07-04 01:49:33 +03:00
import Control.Monad (void)
import Data.Default
2015-07-10 23:20:05 +03:00
import qualified Graphics.Vty as V
2015-07-04 01:49:33 +03:00
2015-07-10 23:20:05 +03:00
import qualified Brick.Types as T
import Brick.Types (row, column)
import qualified Brick.Main as M
import qualified Brick.Widgets.Border as B
2015-07-04 01:49:33 +03:00
import Brick.Widgets.Core
2015-07-10 23:20:05 +03:00
( Widget
, translateBy
)
2015-07-04 01:49:33 +03:00
data St =
2015-07-10 23:20:05 +03:00
St { _topLayerLocation :: T.Location
, _bottomLayerLocation :: T.Location
2015-07-04 01:49:33 +03:00
}
makeLenses ''St
drawUi :: St -> [Widget]
drawUi st =
[ topLayer st
, bottomLayer st
]
topLayer :: St -> Widget
topLayer st =
translateBy (st^.topLayerLocation) $
2015-07-10 23:20:05 +03:00
B.border "Top layer\n(Arrow keys move)"
2015-07-04 01:49:33 +03:00
bottomLayer :: St -> Widget
bottomLayer st =
translateBy (st^.bottomLayerLocation) $
2015-07-10 23:20:05 +03:00
B.border "Bottom layer\n(Ctrl-arrow keys move)"
2015-07-04 01:49:33 +03:00
2015-07-10 23:20:05 +03:00
appEvent :: St -> V.Event -> M.EventM (M.Next St)
appEvent st (V.EvKey V.KDown []) = M.continue $ st & topLayerLocation.row %~ (+ 1)
appEvent st (V.EvKey V.KUp []) = M.continue $ st & topLayerLocation.row %~ (subtract 1)
appEvent st (V.EvKey V.KRight []) = M.continue $ st & topLayerLocation.column %~ (+ 1)
appEvent st (V.EvKey V.KLeft []) = M.continue $ st & topLayerLocation.column %~ (subtract 1)
2015-07-10 23:20:05 +03:00
appEvent st (V.EvKey V.KDown [V.MCtrl]) = M.continue $ st & bottomLayerLocation.row %~ (+ 1)
appEvent st (V.EvKey V.KUp [V.MCtrl]) = M.continue $ st & bottomLayerLocation.row %~ (subtract 1)
appEvent st (V.EvKey V.KRight [V.MCtrl]) = M.continue $ st & bottomLayerLocation.column %~ (+ 1)
appEvent st (V.EvKey V.KLeft [V.MCtrl]) = M.continue $ st & bottomLayerLocation.column %~ (subtract 1)
2015-07-10 23:20:05 +03:00
appEvent st (V.EvKey V.KEsc []) = M.halt st
appEvent st _ = M.continue st
2015-07-04 01:49:33 +03:00
2015-07-10 23:20:05 +03:00
app :: M.App St V.Event
2015-07-04 01:49:33 +03:00
app =
2015-07-10 23:20:05 +03:00
M.App { M.appDraw = drawUi
, M.appStartEvent = return
, M.appHandleEvent = appEvent
, M.appAttrMap = const def
, M.appMakeVtyEvent = id
, M.appChooseCursor = M.neverShowCursor
}
2015-07-04 01:49:33 +03:00
main :: IO ()
2015-07-10 23:20:05 +03:00
main = void $ M.defaultMain app $ St (T.Location (0, 0)) (T.Location (0, 0))