Clean up code

This commit is contained in:
Rene Vergara 2024-02-27 08:41:43 -06:00
parent ec422c1c55
commit 7b7c653d02
Signed by: pitmutt
GPG Key ID: 65122AD495A7F5B2
1 changed files with 18 additions and 19 deletions

View File

@ -4,8 +4,6 @@
module Zenith.CLI where module Zenith.CLI where
import Control.Monad (void) import Control.Monad (void)
import Control.Monad.IO.Class (liftIO)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Graphics.Vty as V import qualified Graphics.Vty as V
import Lens.Micro ((&), (.~), (^.), set) import Lens.Micro ((&), (.~), (^.), set)
@ -89,13 +87,13 @@ drawUI :: State -> [Widget Name]
drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s] drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
where where
ui :: State -> Widget Name ui :: State -> Widget Name
ui s = ui st =
joinBorders $ joinBorders $
withBorderStyle unicode $ withBorderStyle unicode $
B.borderWithLabel (str $ "Zenith - " <> s ^. network) $ B.borderWithLabel (str $ "Zenith - " <> st ^. network) $
(C.center (listBox "Addresses" (s ^. addresses)) <+> (C.center (listBox "Addresses" (st ^. addresses)) <+>
B.vBorder <+> C.center (listBox "Transactions" (s ^. transactions))) <=> B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) <=>
msgBox (s ^. msg) msgBox (st ^. msg)
listBox :: String -> L.List Name String -> Widget Name listBox :: String -> L.List Name String -> Widget Name
listBox titleLabel l = listBox titleLabel l =
C.vCenter $ C.vCenter $
@ -111,8 +109,8 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
vBox vBox
[B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m] [B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m]
helpDialog :: State -> Widget Name helpDialog :: State -> Widget Name
helpDialog s = helpDialog st =
if s ^. helpBox if st ^. helpBox
then D.renderDialog then D.renderDialog
(D.dialog (Just (str "Commands")) Nothing 55) (D.dialog (Just (str "Commands")) Nothing 55)
(vBox ([C.hCenter $ str "Key", B.hBorder] <> keyList) <+> (vBox ([C.hCenter $ str "Key", B.hBorder] <> keyList) <+>
@ -125,15 +123,15 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
(hLimit 40 . str) (hLimit 40 . str)
["Open help", "Close dialog", "Create Wallet", "Quit"] ["Open help", "Close dialog", "Create Wallet", "Quit"]
walletDialog :: State -> Widget Name walletDialog :: State -> Widget Name
walletDialog s = walletDialog st =
if s ^. walletBox if st ^. walletBox
then D.renderDialog then D.renderDialog
(D.dialog (Just (str "Create Wallet")) Nothing 50) (D.dialog (Just (str "Create Wallet")) Nothing 50)
(renderForm $ s ^. walletForm) (renderForm $ st ^. walletForm)
else emptyWidget else emptyWidget
splashDialog :: State -> Widget Name splashDialog :: State -> Widget Name
splashDialog s = splashDialog st =
if s ^. splashBox if st ^. splashBox
then withBorderStyle unicodeBold $ then withBorderStyle unicodeBold $
D.renderDialog D.renderDialog
(D.dialog Nothing Nothing 30) (D.dialog Nothing Nothing 30)
@ -180,7 +178,7 @@ appEvent (BT.VtyEvent e) = do
case e of case e of
V.EvKey V.KEsc [] -> do V.EvKey V.KEsc [] -> do
BT.modify $ set helpBox False BT.modify $ set helpBox False
ev -> return () _ev -> return ()
else do else do
if s ^. walletBox if s ^. walletBox
then do then do
@ -190,7 +188,7 @@ appEvent (BT.VtyEvent e) = do
BT.modify $ set walletBox False BT.modify $ set walletBox False
fs <- BT.zoom walletForm $ BT.gets formState fs <- BT.zoom walletForm $ BT.gets formState
printMsg $ printMsg $
"Creating new wallet " <> (T.unpack $ fs ^. walName) "Creating new wallet " <> T.unpack (fs ^. walName)
ev -> BT.zoom walletForm $ handleFormEvent (BT.VtyEvent ev) ev -> BT.zoom walletForm $ handleFormEvent (BT.VtyEvent ev)
else do else do
case e of case e of
@ -203,12 +201,13 @@ appEvent (BT.VtyEvent e) = do
case r of case r of
Just AList -> BT.zoom addresses $ L.handleListEvent ev Just AList -> BT.zoom addresses $ L.handleListEvent ev
Just TList -> BT.zoom transactions $ L.handleListEvent ev Just TList -> BT.zoom transactions $ L.handleListEvent ev
Nothing -> return () _anyName -> return ()
where where
printMsg :: String -> BT.EventM Name State () printMsg :: String -> BT.EventM Name State ()
printMsg s = BT.modify $ updateMsg s printMsg s = BT.modify $ updateMsg s
updateMsg :: String -> State -> State updateMsg :: String -> State -> State
updateMsg = set msg updateMsg = set msg
appEvent _ = return ()
theMap :: A.AttrMap theMap :: A.AttrMap
theMap = theMap =
@ -233,7 +232,7 @@ theApp =
} }
runZenithCLI :: T.Text -> Int -> T.Text -> IO () runZenithCLI :: T.Text -> Int -> T.Text -> IO ()
runZenithCLI host port dbName = do runZenithCLI host port dbFilePath = do
w <- checkZebra host port w <- checkZebra host port
case (w :: Maybe ZebraGetInfo) of case (w :: Maybe ZebraGetInfo) of
Just zebra -> do Just zebra -> do
@ -241,7 +240,7 @@ runZenithCLI host port dbName = do
case (bc :: Maybe ZebraGetBlockChainInfo) of case (bc :: Maybe ZebraGetBlockChainInfo) of
Nothing -> print "Unable to determine blockchain status" Nothing -> print "Unable to determine blockchain status"
Just chainInfo -> do Just chainInfo -> do
walList <- getWallets $ zgb_net chainInfo walList <- getWallets dbFilePath $ zgb_net chainInfo
void $ void $
M.defaultMain theApp $ M.defaultMain theApp $
State State