{-# LANGUAGE TemplateHaskell #-} module Zenith.CLI where import Control.Monad (void) import Control.Monad.State (modify) import Data.Maybe (fromMaybe) import qualified Data.Text as T import qualified Graphics.Vty as V import Lens.Micro ((^.)) 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 import Brick.Widgets.Border.Style (unicode) import qualified Brick.Widgets.Center as C import Brick.Widgets.Core ( (<+>) , hLimit , joinBorders , 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 { _network :: String , _wallets :: L.List Name String , _addresses :: L.List Name String , _transactions :: L.List Name 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)) <+> B.vBorder <+> C.center (listBox "Transactions" (s ^. transactions))) 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 " ] 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) 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 ev -> BT.zoom addresses $ L.handleListEvent ev 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"