zenith/src/Zenith/CLI.hs

139 lines
3.5 KiB
Haskell
Raw Normal View History

{-# LANGUAGE TemplateHaskell #-}
2024-02-08 19:26:54 +00:00
module Zenith.CLI where
import Control.Monad (void)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import qualified Graphics.Vty as V
2024-02-11 16:33:22 +00:00
import Lens.Micro ((&), (.~), (^.), set)
import Lens.Micro.Mtl
import Lens.Micro.TH
import qualified Brick.AttrMap as A
import qualified Brick.Main as M
import qualified Brick.Types as BT
import Brick.Types (Widget)
import Brick.Util (fg, on)
import qualified Brick.Widgets.Border as B
2024-02-08 19:26:54 +00:00
import Brick.Widgets.Border.Style (unicode)
import qualified Brick.Widgets.Center as C
import Brick.Widgets.Core
2024-02-11 16:33:22 +00:00
( Padding(..)
, (<+>)
, (<=>)
, hLimit
, joinBorders
2024-02-11 16:33:22 +00:00
, padRight
, str
, vBox
, vLimit
, withAttr
, withBorderStyle
)
import qualified Brick.Widgets.List as L
import qualified Data.Vector as Vec
import Zenith.Core
data Name
= WList
| AList
| TList
deriving (Eq, Show, Ord)
data State = State
2024-02-11 16:33:22 +00:00
{ _network :: !String
, _wallets :: !(L.List Name String)
, _addresses :: !(L.List Name String)
, _transactions :: !(L.List Name String)
, _msg :: !String
} deriving (Show)
makeLenses ''State
drawUI :: State -> [Widget Name]
drawUI s = [ui s]
where
ui :: State -> Widget Name
ui s =
joinBorders $
withBorderStyle unicode $
B.borderWithLabel (str $ "Zenith - " <> s ^. network) $
(C.center (listBox "Addresses" (s ^. addresses)) <+>
2024-02-11 16:33:22 +00:00
B.vBorder <+> C.center (listBox "Transactions" (s ^. transactions))) <=>
msgBox (s ^. msg)
listBox :: String -> L.List Name String -> Widget Name
listBox titleLabel l =
C.vCenter $
vBox
[ C.hCenter
(B.borderWithLabel (str titleLabel) $
hLimit 25 $ vLimit 15 $ L.renderList listDrawElement True l)
, str " "
, C.hCenter $ str "Select "
]
2024-02-11 16:33:22 +00:00
msgBox :: String -> Widget Name
msgBox m =
vBox
[B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m]
listDrawElement :: (Show a) => Bool -> a -> Widget Name
listDrawElement sel a =
let selStr s =
if sel
then withAttr customAttr (str $ "<" <> s <> ">")
else str s
in C.hCenter $ selStr $ show a
initialState :: State
initialState =
State
"Main"
(L.list WList (Vec.fromList ["wall1"]) 1)
(L.list AList (Vec.fromList ["addr1", "addr2"]) 1)
(L.list TList (Vec.fromList ["tx1", "tx2", "tx3"]) 1)
2024-02-11 16:33:22 +00:00
"Start up Ok!"
customAttr :: A.AttrName
customAttr = L.listSelectedAttr <> A.attrName "custom"
appEvent :: BT.BrickEvent Name e -> BT.EventM Name State ()
appEvent (BT.VtyEvent e) =
case e of
V.EvKey V.KEsc [] -> M.halt
2024-02-11 16:33:22 +00:00
V.EvKey (V.KChar 'c') [] -> printMsg "You pressed C!"
V.EvKey (V.KChar 's') [] -> printMsg "You pressed S!"
ev -> BT.zoom addresses $ L.handleListEvent ev
2024-02-11 16:33:22 +00:00
where
printMsg :: String -> BT.EventM Name State ()
printMsg s = BT.modify $ updateMsg s
updateMsg :: String -> State -> State
updateMsg = set msg
theMap :: A.AttrMap
theMap =
A.attrMap
V.defAttr
[ (L.listAttr, V.white `on` V.blue)
, (L.listSelectedAttr, V.blue `on` V.white)
, (customAttr, fg V.cyan)
]
theApp :: M.App State e Name
theApp =
M.App
{ M.appDraw = drawUI
, M.appChooseCursor = M.showFirstCursor
, M.appHandleEvent = appEvent
, M.appStartEvent = return ()
, M.appAttrMap = const theMap
}
runZenithCLI :: T.Text -> IO ()
runZenithCLI dbName = do
w <- checkWallets dbName
if (null w)
then void $ M.defaultMain theApp initialState
else do
print "No wallet found. Create one? Y/N"