{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE OverloadedStrings #-} module Zenith.CLI where import Control.Monad (void) import Data.Maybe (fromMaybe) import qualified Data.Text as T import qualified Graphics.Vty as V 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 import Brick.Widgets.Border.Style (unicode) import qualified Brick.Widgets.Center as C import Brick.Widgets.Core ( Padding(..) , (<+>) , (<=>) , emptyWidget , hLimit , joinBorders , padAll , padRight , str , vBox , vLimit , withAttr , withBorderStyle ) import qualified Brick.Widgets.Dialog as D import qualified Brick.Widgets.List as L import qualified Data.Vector as Vec import Network.HTTP.Simple import ZcashHaskell.Types import Zenith.Core data Name = WList | AList | TList | HelpDialog deriving (Eq, Show, Ord) data State = State { _network :: !String , _wallets :: !(L.List Name String) , _addresses :: !(L.List Name String) , _transactions :: !(L.List Name String) , _msg :: !String , _helpBox :: !Bool } deriving (Show) makeLenses ''State drawUI :: State -> [Widget Name] drawUI s = [helpDialog 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))) <=> 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 " ] msgBox :: String -> Widget Name msgBox m = vBox [B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m] helpDialog :: State -> Widget Name helpDialog s = if s ^. helpBox then D.renderDialog (D.dialog (Just (str "Commands")) Nothing 50) (vBox ([C.hCenter $ str "Key", B.hBorder] <> keyList) <+> vBox ([str "Actions", B.hBorder] <> actionList)) else emptyWidget where keyList = map (C.hCenter . str) ["?", "Esc", "q"] actionList = map (hLimit 40 . str) ["Open help", "Close dialog", "Quit"] 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 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 [] -> BT.modify $ set helpBox False V.EvKey (V.KChar 'q') [] -> M.halt V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True 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 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 :: Int -> T.Text -> IO () runZenithCLI port dbName = do w <- checkZebra port case (w :: Maybe ZebraGetInfo) of Just zebra -> do bc <- checkBlockChain port case (bc :: Maybe ZebraGetBlockChainInfo) of Nothing -> print "Unable to determine blockchain status" Just chainInfo -> do void $ M.defaultMain theApp $ State ((show . zgb_net) chainInfo) (L.list WList (Vec.fromList ["wall1"]) 1) (L.list AList (Vec.fromList ["addr1", "addr2"]) 1) (L.list TList (Vec.fromList ["tx1", "tx2", "tx3"]) 1) ("Start up Ok! Connected to Zebra " ++ (T.unpack . zgi_build) zebra ++ " on port " ++ show port ++ ".") False Nothing -> do print $ "No Zebra node available on port " <> show port <> ". Check your configuration"