brick/programs/EditDemo.hs

94 lines
2.8 KiB
Haskell
Raw Normal View History

2015-06-28 22:45:26 +03:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RankNTypes #-}
2015-06-28 22:45:26 +03:00
module Main where
import Lens.Micro
import Lens.Micro.TH
2015-07-10 23:12:12 +03:00
import qualified Graphics.Vty as V
2015-06-28 22:45:26 +03:00
2015-07-10 23:12:12 +03:00
import qualified Brick.Main as M
import qualified Brick.Types as T
2015-06-28 22:45:26 +03:00
import Brick.Widgets.Core
( (<+>)
, (<=>)
2015-07-10 23:12:12 +03:00
, hLimit
, vLimit
, str
2015-07-10 23:12:12 +03:00
)
import qualified Brick.Widgets.Center as C
import qualified Brick.Widgets.Edit as E
import qualified Brick.AttrMap as A
2016-03-05 01:54:43 +03:00
import qualified Brick.Focus as F
2015-07-10 23:12:12 +03:00
import Brick.Util (on)
data Name = Edit1
| Edit2
deriving (Ord, Show, Eq)
data St =
2016-03-05 01:54:43 +03:00
St { _focusRing :: F.FocusRing Name
, _edit1 :: E.Editor String Name
, _edit2 :: E.Editor String Name
}
makeLenses ''St
drawUI :: St -> [T.Widget Name]
drawUI st = [ui]
2015-06-28 22:45:26 +03:00
where
e1 = F.withFocusRing (st^.focusRing) (E.renderEditor (str . unlines)) (st^.edit1)
e2 = F.withFocusRing (st^.focusRing) (E.renderEditor (str . unlines)) (st^.edit2)
2016-03-07 19:25:02 +03:00
ui = C.center $
2016-03-07 19:25:02 +03:00
(str "Input 1 (unlimited): " <+> (hLimit 30 $ vLimit 5 e1)) <=>
str " " <=>
2016-03-07 19:25:02 +03:00
(str "Input 2 (limited to 2 lines): " <+> (hLimit 30 e2)) <=>
str " " <=>
str "Press Tab to switch between editors, Esc to quit."
2015-06-28 22:45:26 +03:00
appEvent :: St -> T.BrickEvent Name e -> T.EventM Name (T.Next St)
appEvent st (T.VtyEvent ev) =
2015-06-28 23:24:36 +03:00
case ev of
V.EvKey V.KEsc [] -> M.halt st
2016-03-05 01:54:43 +03:00
V.EvKey (V.KChar '\t') [] -> M.continue $ st & focusRing %~ F.focusNext
V.EvKey V.KBackTab [] -> M.continue $ st & focusRing %~ F.focusPrev
_ -> M.continue =<< case F.focusGetCurrent (st^.focusRing) of
Just Edit1 -> T.handleEventLensed st edit1 E.handleEditorEvent ev
Just Edit2 -> T.handleEventLensed st edit2 E.handleEditorEvent ev
Nothing -> return st
appEvent st _ = M.continue st
2015-06-28 22:45:26 +03:00
initialState :: St
initialState =
2016-05-27 21:20:34 +03:00
St (F.focusRing [Edit1, Edit2])
(E.editor Edit1 Nothing "")
(E.editor Edit2 (Just 2) "")
2015-06-28 22:45:26 +03:00
2015-07-10 23:12:12 +03:00
theMap :: A.AttrMap
theMap = A.attrMap V.defAttr
2016-03-07 19:25:02 +03:00
[ (E.editAttr, V.white `on` V.blue)
, (E.editFocusedAttr, V.black `on` V.yellow)
2015-06-28 22:45:26 +03:00
]
appCursor :: St -> [T.CursorLocation Name] -> Maybe (T.CursorLocation Name)
2016-03-05 01:54:43 +03:00
appCursor = F.focusRingCursor (^.focusRing)
theApp :: M.App St e Name
2015-06-28 22:45:26 +03:00
theApp =
2015-07-10 23:12:12 +03:00
M.App { M.appDraw = drawUI
, M.appChooseCursor = appCursor
2015-07-10 23:12:12 +03:00
, M.appHandleEvent = appEvent
, M.appStartEvent = return
, M.appAttrMap = const theMap
}
2015-06-28 22:45:26 +03:00
main :: IO ()
main = do
st <- M.defaultMain theApp initialState
putStrLn "In input 1 you entered:\n"
putStrLn $ unlines $ E.getEditContents $ st^.edit1
putStrLn "In input 2 you entered:\n"
putStrLn $ unlines $ E.getEditContents $ st^.edit2