brick/programs/Main.hs

82 lines
2.3 KiB
Haskell
Raw Normal View History

2015-05-09 09:09:40 +03:00
{-# LANGUAGE OverloadedStrings #-}
module Main where
2015-05-11 00:56:58 +03:00
import Control.Concurrent
2015-05-09 19:56:14 +03:00
import Data.Default
2015-05-11 00:56:58 +03:00
import Data.Monoid
2015-05-09 09:09:40 +03:00
import Graphics.Vty
import System.Exit
import Brick
2015-05-09 10:18:29 +03:00
data St =
2015-05-09 18:37:16 +03:00
St { focus :: FocusRing
, stEditor :: Editor
2015-05-10 00:37:27 +03:00
, trans :: Location
2015-05-11 00:56:58 +03:00
, counter :: Int
}
2015-05-09 10:18:29 +03:00
eName :: Name
eName = Name "edit"
2015-05-10 00:28:37 +03:00
drawUI :: St -> [Widget]
drawUI st = [top]
where
2015-05-10 00:37:27 +03:00
top = translated (trans st) $
2015-05-11 01:09:52 +03:00
bordered $
2015-05-10 00:37:27 +03:00
hLimit 40 $
2015-05-11 00:56:58 +03:00
vBox [ txt $ "Top (counter: " <> show (counter st) <> ")"
2015-05-10 00:28:37 +03:00
, hBorder '-'
, hBox [ " Edit: "
, hLimit 20 $ edit (stEditor st) `withAttr` (cyan `on` blue)
]
]
2015-05-09 09:09:40 +03:00
2015-05-11 00:56:58 +03:00
handleEvent :: MyEvent -> St -> IO St
handleEvent e st =
2015-05-09 09:09:40 +03:00
case e of
2015-05-11 00:56:58 +03:00
VtyEvent vtyEv ->
case vtyEv of
EvKey KEsc [] -> exitSuccess
EvKey KEnter [] -> error $ editStr $ stEditor st
EvKey KLeft [MCtrl] -> return $ st { trans = trans st `locOffset` (Location (-1, 0)) }
EvKey KRight [MCtrl] -> return $ st { trans = trans st `locOffset` (Location (1, 0)) }
EvKey KUp [MCtrl] -> return $ st { trans = trans st `locOffset` (Location (0, -1)) }
EvKey KDown [MCtrl] -> return $ st { trans = trans st `locOffset` (Location (0, 1)) }
ev -> return $ st { stEditor = editEvent ev (stEditor st) }
CounterUpdate i -> return $ st { counter = i }
initialState :: St
initialState =
St { focus = focusRing [eName]
, stEditor = editor eName ""
2015-05-10 00:37:27 +03:00
, trans = Location (0, 0)
2015-05-11 00:56:58 +03:00
, counter = 0
}
2015-05-11 00:56:58 +03:00
data MyEvent = VtyEvent Event
| CounterUpdate Int
theApp :: App St MyEvent
theApp =
2015-05-09 19:56:14 +03:00
def { appDraw = drawUI
, appChooseCursor = focusRingCursor focus
, appHandleEvent = handleEvent
}
2015-05-11 00:56:58 +03:00
updateThread :: Chan MyEvent -> IO ()
updateThread chan = do
let run i = do
writeChan chan $ CounterUpdate i
threadDelay 1000000
run $ i + 1
run 0
2015-05-09 09:09:40 +03:00
main :: IO ()
2015-05-11 00:56:58 +03:00
main = do
chan <- newChan
withVty (mkVty def) $ \vty -> do
forkIO $ supplyVtyEvents vty VtyEvent chan
forkIO $ updateThread chan
runVty vty chan theApp initialState