Version update

This commit is contained in:
Rene Vergara 2024-06-21 12:58:31 -05:00
parent 77a0890ac8
commit 2f88c89083
Signed by: pitmutt
GPG Key ID: 65122AD495A7F5B2
3 changed files with 226 additions and 169 deletions

View File

@ -5,8 +5,19 @@ All notable changes to this project will be documented in this file.
The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/), The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),
and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html). and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html).
## [0.5.3.1-beta]
### Added
- Docker image
## [0.5.3.0-beta] ## [0.5.3.0-beta]
### Added
- Address Book functionality. Allows users to store frequently used zcash addresses and
generate transactions using them.
### Changed ### Changed
- Improved formatting of sync progress - Improved formatting of sync progress
@ -17,11 +28,6 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
## [0.5.2.0-beta] ## [0.5.2.0-beta]
### Added
- Address Book functionality. Allows users to store frequently used zcash addresses and
generate transactions using them.
### Changed ### Changed
- Update to `zcash-haskell-0.6.2.0` to increase performance of transaction creation - Update to `zcash-haskell-0.6.2.0` to increase performance of transaction creation

View File

@ -3,7 +3,6 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
module Zenith.CLI where module Zenith.CLI where
import qualified Brick.AttrMap as A import qualified Brick.AttrMap as A
@ -11,8 +10,10 @@ import qualified Brick.BChan as BC
import qualified Brick.Focus as F import qualified Brick.Focus as F
import Brick.Forms import Brick.Forms
( Form(..) ( Form(..)
, FormFieldState
, (@@=) , (@@=)
, allFieldsValid , allFieldsValid
, editShowableField
, editShowableFieldWithValidate , editShowableFieldWithValidate
, editTextField , editTextField
, focusedFormInputAttr , focusedFormInputAttr
@ -22,8 +23,6 @@ import Brick.Forms
, renderForm , renderForm
, setFieldValid , setFieldValid
, updateFormState , updateFormState
, FormFieldState
, editShowableField
) )
import qualified Brick.Main as M import qualified Brick.Main as M
import qualified Brick.Types as BT import qualified Brick.Types as BT
@ -43,8 +42,8 @@ import Brick.Widgets.Core
, joinBorders , joinBorders
, padAll , padAll
, padBottom , padBottom
, padTop
, padLeft , padLeft
, padTop
, setAvailableSize , setAvailableSize
, str , str
, strWrap , strWrap
@ -54,8 +53,8 @@ import Brick.Widgets.Core
, txtWrapWith , txtWrapWith
, updateAttrMap , updateAttrMap
, vBox , vBox
, viewport
, vLimit , vLimit
, viewport
, withAttr , withAttr
, withBorderStyle , withBorderStyle
) )
@ -197,7 +196,7 @@ data State = State
, _txForm :: !(Form SendInput () Name) , _txForm :: !(Form SendInput () Name)
, _abAddresses :: !(L.List Name (Entity AddressBook)) , _abAddresses :: !(L.List Name (Entity AddressBook))
, _abForm :: !(Form AdrBookEntry () Name) , _abForm :: !(Form AdrBookEntry () Name)
, _abCurAdrs :: !T.Text -- used for address book CRUD operations , _abCurAdrs :: !T.Text -- used for address book CRUD operations
, _sentTx :: !(Maybe HexString) , _sentTx :: !(Maybe HexString)
} }
@ -216,10 +215,11 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
show (st ^. network) <> show (st ^. network) <>
" - " <> " - " <>
(T.unpack (T.unpack
(maybe (maybe
"(None)" "(None)"
(\(_, w) -> zcashWalletName $ entityVal w) (\(_, w) -> zcashWalletName $ entityVal w)
(L.listSelectedElement (st ^. wallets)))) ++ " ")) (L.listSelectedElement (st ^. wallets)))) ++
" "))
(C.hCenter (C.hCenter
(str (str
("Account: " ++ ("Account: " ++
@ -236,7 +236,8 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
else displayTaz (st ^. balance))) <=> else displayTaz (st ^. balance))) <=>
listAddressBox " Addresses " (st ^. addresses) <+> listAddressBox " Addresses " (st ^. addresses) <+>
B.vBorder <+> B.vBorder <+>
(C.hCenter (str ("Last block seen: " ++ show (st ^. syncBlock) ++ "\n")) <=> (C.hCenter
(str ("Last block seen: " ++ show (st ^. syncBlock) ++ "\n")) <=>
listTxBox " Transactions " (st ^. network) (st ^. transactions))) <=> listTxBox " Transactions " (st ^. network) (st ^. transactions))) <=>
C.hCenter C.hCenter
(hBox (hBox
@ -313,7 +314,8 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
vBox ([str "Actions", B.hBorder] <> actionList)) vBox ([str "Actions", B.hBorder] <> actionList))
else emptyWidget else emptyWidget
where where
keyList = map (C.hCenter . str) ["?", "Esc", "w", "a", "v", "s", "b", "q"] keyList =
map (C.hCenter . str) ["?", "Esc", "w", "a", "v", "s", "b", "q"]
actionList = actionList =
map map
(hLimit 40 . str) (hLimit 40 . str)
@ -374,50 +376,55 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
-- Address Book List -- Address Book List
AdrBook -> AdrBook ->
D.renderDialog D.renderDialog
(D.dialog (Just $ str " Address Book ") Nothing 60) (D.dialog (Just $ str " Address Book ") Nothing 60)
(withAttr abDefAttr $ (withAttr abDefAttr $
setAvailableSize (50,20) $ setAvailableSize (50, 20) $
viewport ABViewport BT.Vertical $ viewport ABViewport BT.Vertical $
vLimit 20 $ vLimit 20 $
hLimit 50 $ hLimit 50 $
vBox [vLimit 16 $ vBox
hLimit 50 $ [ vLimit 16 $
vBox $ [ L.renderList listDrawAB True (s ^. abAddresses) ], hLimit 50 $
padTop Max $ vBox $ [L.renderList listDrawAB True (s ^. abAddresses)]
vLimit 4 $ , padTop Max $
hLimit 50 $ vLimit 4 $
withAttr abMBarAttr $ hLimit 50 $
vBox $ [C.hCenter $ withAttr abMBarAttr $
(capCommand "N" "ew Address" <+> vBox $
capCommand "E" "dit Address" <+> [ C.hCenter $
capCommand3 "" "C" "opy Address"), (capCommand "N" "ew Address" <+>
C.hCenter $ capCommand "E" "dit Address" <+>
(capCommand "D" "elete Address" <+> capCommand3 "" "C" "opy Address")
capCommand "S" "end Zcash" <+> , C.hCenter $
capCommand3 "E" "x" "it")]]) (capCommand "D" "elete Address" <+>
capCommand "S" "end Zcash" <+> capCommand3 "E" "x" "it")
]
])
-- Address Book new entry form -- Address Book new entry form
AdrBookForm -> AdrBookForm ->
D.renderDialog D.renderDialog
(D.dialog (Just $ str " New Address Book Entry ") Nothing 50) (D.dialog (Just $ str " New Address Book Entry ") Nothing 50)
(renderForm (st ^. abForm) <=> (renderForm (st ^. abForm) <=>
C.hCenter C.hCenter
(hBox [capCommand "" " Save", capCommand3 "" "<Esc>" " Cancel"])) (hBox [capCommand "" " Save", capCommand3 "" "<Esc>" " Cancel"]))
-- Address Book edit/update entry form -- Address Book edit/update entry form
AdrBookUpdForm -> AdrBookUpdForm ->
D.renderDialog D.renderDialog
(D.dialog (Just $ str " Edit Address Book Entry ") Nothing 50) (D.dialog (Just $ str " Edit Address Book Entry ") Nothing 50)
(renderForm (st ^. abForm) <=> (renderForm (st ^. abForm) <=>
C.hCenter C.hCenter
(hBox [capCommand "" " Save", capCommand3 "" "<Esc>" " Cancel"])) (hBox [capCommand "" " Save", capCommand3 "" "<Esc>" " Cancel"]))
-- Address Book edit/update entry form -- Address Book edit/update entry form
AdrBookDelForm -> AdrBookDelForm ->
D.renderDialog D.renderDialog
(D.dialog (Just $ str " Delete Address Book Entry ") Nothing 50) (D.dialog (Just $ str " Delete Address Book Entry ") Nothing 50)
(renderForm (st ^. abForm) <=> (renderForm (st ^. abForm) <=>
C.hCenter C.hCenter
(hBox [capCommand "C" "onfirm delete", capCommand3 "" "<Esc>" " Cancel"])) (hBox
[ capCommand "C" "onfirm delete"
, capCommand3 "" "<Esc>" " Cancel"
]))
-- --
splashDialog :: State -> Widget Name splashDialog :: State -> Widget Name
splashDialog st = splashDialog st =
if st ^. splashBox if st ^. splashBox
@ -429,16 +436,14 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(str (str
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=> " _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=>
C.hCenter C.hCenter
(withAttr titleAttr (str "Zcash Wallet v0.5.3.0-beta")) <=> (withAttr titleAttr (str "Zcash Wallet v0.5.3.1-beta")) <=>
C.hCenter (withAttr blinkAttr $ str "Press any key...")) C.hCenter (withAttr blinkAttr $ str "Press any key..."))
else emptyWidget else emptyWidget
capCommand3 :: String -> String -> String -> Widget Name capCommand3 :: String -> String -> String -> Widget Name
capCommand3 l h e = hBox [str l, withAttr titleAttr (str h), str e] capCommand3 l h e = hBox [str l, withAttr titleAttr (str h), str e]
capCommand2 :: String -> String -> String -> Widget Name capCommand2 :: String -> String -> String -> Widget Name
capCommand2 l h e = hBox [str l, withAttr titleAttr (str h), str e, str " | "] capCommand2 l h e =
hBox [str l, withAttr titleAttr (str h), str e, str " | "]
capCommand :: String -> String -> Widget Name capCommand :: String -> String -> Widget Name
capCommand k comm = hBox [withAttr titleAttr (str k), str comm, str " | "] capCommand k comm = hBox [withAttr titleAttr (str k), str comm, str " | "]
xCommand :: Widget Name xCommand :: Widget Name
@ -562,20 +567,21 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
(strWrapWith (strWrapWith
(WrapSettings False True NoFill FillAfterFirst) (WrapSettings False True NoFill FillAfterFirst)
(st ^. msg))) (st ^. msg)))
AdrBookEntryDisplay -> do AdrBookEntryDisplay -> do
case L.listSelectedElement $ st ^. abAddresses of case L.listSelectedElement $ st ^. abAddresses of
Just (_, a) -> do Just (_, a) -> do
let abentry = T.pack $ let abentry =
" Descr: " ++ T.pack $
T.unpack (addressBookAbdescrip (entityVal a)) ++ " Descr: " ++
"\n Address: " ++ T.unpack (addressBookAbdescrip (entityVal a)) ++
T.unpack (addressBookAbaddress (entityVal a)) "\n Address: " ++
T.unpack (addressBookAbaddress (entityVal a))
withBorderStyle unicodeBold $ withBorderStyle unicodeBold $
D.renderDialog D.renderDialog
(D.dialog (Just $ txt " Address Book Entry ") Nothing 60) (D.dialog (Just $ txt " Address Book Entry ") Nothing 60)
(padAll 1 $ (padAll 1 $
txtWrapWith (WrapSettings False True NoFill FillAfterFirst) $ txtWrapWith (WrapSettings False True NoFill FillAfterFirst) $
abentry) abentry)
_ -> emptyWidget _ -> emptyWidget
BlankDisplay -> emptyWidget BlankDisplay -> emptyWidget
@ -602,7 +608,7 @@ mkSendForm bal =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
mkNewABForm :: AdrBookEntry -> Form AdrBookEntry e Name mkNewABForm :: AdrBookEntry -> Form AdrBookEntry e Name
mkNewABForm = mkNewABForm =
newForm newForm
[ label "Descrip: " @@= editTextField descrip DescripField (Just 1) [ label "Descrip: " @@= editTextField descrip DescripField (Just 1)
, label "Address: " @@= editTextField address AddressField (Just 1) , label "Address: " @@= editTextField address AddressField (Just 1)
@ -684,9 +690,9 @@ listDrawAB :: Bool -> Entity AddressBook -> Widget Name
listDrawAB sel ab = listDrawAB sel ab =
let selStr s = let selStr s =
if sel if sel
then withAttr abSelAttr (txt $ " " <> s ) then withAttr abSelAttr (txt $ " " <> s)
else txt $ " " <> s else txt $ " " <> s
in selStr $ addressBookAbdescrip (entityVal ab) in selStr $ addressBookAbdescrip (entityVal ab)
customAttr :: A.AttrName customAttr :: A.AttrName
customAttr = L.listSelectedAttr <> A.attrName "custom" customAttr = L.listSelectedAttr <> A.attrName "custom"
@ -726,7 +732,8 @@ scanZebra dbP zHost zPort b eChan = do
dbBlock <- runNoLoggingT $ getMaxBlock pool dbBlock <- runNoLoggingT $ getMaxBlock pool
let sb = max dbBlock b let sb = max dbBlock b
if sb > zgb_blocks bStatus || sb < 1 if sb > zgb_blocks bStatus || sb < 1
then liftIO $ BC.writeBChan eChan $ TickMsg "Invalid starting block for scan" then liftIO $
BC.writeBChan eChan $ TickMsg "Invalid starting block for scan"
else do else do
let bList = [(sb + 1) .. (zgb_blocks bStatus)] let bList = [(sb + 1) .. (zgb_blocks bStatus)]
if not (null bList) if not (null bList)
@ -931,7 +938,7 @@ appEvent (BT.VtyEvent e) = do
_ev -> return () _ev -> return ()
SendDisplay -> BT.modify $ set displayBox BlankDisplay SendDisplay -> BT.modify $ set displayBox BlankDisplay
SyncDisplay -> BT.modify $ set displayBox BlankDisplay SyncDisplay -> BT.modify $ set displayBox BlankDisplay
AdrBookEntryDisplay -> BT.modify $ set displayBox BlankDisplay AdrBookEntryDisplay -> BT.modify $ set displayBox BlankDisplay
BlankDisplay -> do BlankDisplay -> do
case s ^. dialogBox of case s ^. dialogBox of
WName -> do WName -> do
@ -1072,19 +1079,21 @@ appEvent (BT.VtyEvent e) = do
BT.modify $ set msg "Invalid inputs" BT.modify $ set msg "Invalid inputs"
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
BT.modify $ set dialogBox Blank BT.modify $ set dialogBox Blank
ev -> BT.zoom txForm $ do ev ->
handleFormEvent (BT.VtyEvent ev) BT.zoom txForm $ do
fs <- BT.gets formState handleFormEvent (BT.VtyEvent ev)
BT.modify $ fs <- BT.gets formState
setFieldValid BT.modify $
(isRecipientValid (fs ^. sendTo)) setFieldValid
RecField (isRecipientValid (fs ^. sendTo))
RecField
AdrBook -> do AdrBook -> do
case e of case e of
V.EvKey (V.KChar 'x') [] -> V.EvKey (V.KChar 'x') [] ->
BT.modify $ set dialogBox Blank BT.modify $ set dialogBox Blank
V.EvKey (V.KChar 'c') [] -> do V.EvKey (V.KChar 'c') []
-- Copy Address to Clipboard -- Copy Address to Clipboard
-> do
case L.listSelectedElement $ s ^. abAddresses of case L.listSelectedElement $ s ^. abAddresses of
Just (_, a) -> do Just (_, a) -> do
liftIO $ liftIO $
@ -1092,53 +1101,72 @@ appEvent (BT.VtyEvent e) = do
T.unpack $ addressBookAbaddress (entityVal a) T.unpack $ addressBookAbaddress (entityVal a)
BT.modify $ BT.modify $
set msg $ set msg $
"Address copied to Clipboard from >>\n" ++ "Address copied to Clipboard from >>\n" ++
T.unpack (addressBookAbdescrip (entityVal a)) T.unpack (addressBookAbdescrip (entityVal a))
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
_ -> do _ -> do
BT.modify $ set msg "Error while copying the address!!" BT.modify $
BT.modify $ set displayBox MsgDisplay set msg "Error while copying the address!!"
BT.modify $ set displayBox MsgDisplay
-- Send Zcash transaction -- Send Zcash transaction
V.EvKey (V.KChar 's') [] -> do V.EvKey (V.KChar 's') [] -> do
case L.listSelectedElement $ s ^. abAddresses of case L.listSelectedElement $ s ^. abAddresses of
Just (_, a) -> do Just (_, a) -> do
BT.modify $ BT.modify $
set txForm $ set txForm $
mkSendForm (s ^. balance) (SendInput (addressBookAbaddress (entityVal a)) 0.0 "") mkSendForm
BT.modify $ set dialogBox SendTx (s ^. balance)
(SendInput
(addressBookAbaddress (entityVal a))
0.0
"")
BT.modify $ set dialogBox SendTx
_ -> do _ -> do
BT.modify $ set msg "No receiver address available!!" BT.modify $
BT.modify $ set displayBox MsgDisplay set msg "No receiver address available!!"
BT.modify $ set displayBox MsgDisplay
-- Edit an entry in Address Book -- Edit an entry in Address Book
V.EvKey (V.KChar 'e') [] -> do V.EvKey (V.KChar 'e') [] -> do
case L.listSelectedElement $ s ^. abAddresses of case L.listSelectedElement $ s ^. abAddresses of
Just (_, a) -> do Just (_, a) -> do
BT.modify $ set abCurAdrs (addressBookAbaddress (entityVal a)) BT.modify $
BT.modify $ set
set abForm $ abCurAdrs
mkNewABForm (AdrBookEntry (addressBookAbdescrip (entityVal a)) (addressBookAbaddress (entityVal a))) (addressBookAbaddress (entityVal a))
BT.modify $ set dialogBox AdrBookUpdForm BT.modify $
set abForm $
mkNewABForm
(AdrBookEntry
(addressBookAbdescrip (entityVal a))
(addressBookAbaddress (entityVal a)))
BT.modify $ set dialogBox AdrBookUpdForm
_ -> do _ -> do
BT.modify $ set dialogBox Blank BT.modify $ set dialogBox Blank
-- Delete an entry from Address Book -- Delete an entry from Address Book
V.EvKey (V.KChar 'd') [] -> do V.EvKey (V.KChar 'd') [] -> do
case L.listSelectedElement $ s ^. abAddresses of case L.listSelectedElement $ s ^. abAddresses of
Just (_, a) -> do Just (_, a) -> do
BT.modify $ set abCurAdrs (addressBookAbaddress (entityVal a)) BT.modify $
BT.modify $ set
set abForm $ abCurAdrs
mkNewABForm (AdrBookEntry (addressBookAbdescrip (entityVal a)) (addressBookAbaddress (entityVal a))) (addressBookAbaddress (entityVal a))
BT.modify $ set dialogBox AdrBookDelForm BT.modify $
set abForm $
mkNewABForm
(AdrBookEntry
(addressBookAbdescrip (entityVal a))
(addressBookAbaddress (entityVal a)))
BT.modify $ set dialogBox AdrBookDelForm
_ -> do _ -> do
BT.modify $ set dialogBox Blank BT.modify $ set dialogBox Blank
-- Create a new entry in Address Book -- Create a new entry in Address Book
V.EvKey (V.KChar 'n') [] -> do V.EvKey (V.KChar 'n') [] -> do
BT.modify $ set abForm $ mkNewABForm (AdrBookEntry "" "") BT.modify $
BT.modify $ set dialogBox AdrBookForm set abForm $ mkNewABForm (AdrBookEntry "" "")
BT.modify $ set dialogBox AdrBookForm
-- Show AddressBook entry data -- Show AddressBook entry data
V.EvKey V.KEnter [] -> do V.EvKey V.KEnter [] -> do
BT.modify $ set displayBox AdrBookEntryDisplay BT.modify $ set displayBox AdrBookEntryDisplay
-- Process any other event -- Process any other event
ev -> BT.zoom abAddresses $ L.handleListEvent ev ev -> BT.zoom abAddresses $ L.handleListEvent ev
-- Process new address book entry -- Process new address book entry
@ -1146,75 +1174,101 @@ appEvent (BT.VtyEvent e) = do
case e of case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook
V.EvKey V.KEnter [] -> do V.EvKey V.KEnter [] -> do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
fs <- BT.zoom abForm $ BT.gets formState fs <- BT.zoom abForm $ BT.gets formState
let idescr = T.unpack $ T.strip (fs ^. descrip) let idescr = T.unpack $ T.strip (fs ^. descrip)
let iabadr = fs ^. address let iabadr = fs ^. address
if not (null idescr) && isRecipientValid iabadr if not (null idescr) && isRecipientValid iabadr
then do then do
res <- liftIO $ saveAdrsInAdrBook pool $ AddressBook (ZcashNetDB (s ^. network)) (fs ^. descrip) (fs ^.address) res <-
case res of liftIO $
Nothing -> do saveAdrsInAdrBook pool $
BT.modify $ set msg ("AddressBook Entry already exists: " ++ T.unpack (fs ^.address)) AddressBook
BT.modify $ set displayBox MsgDisplay (ZcashNetDB (s ^. network))
Just _ -> do (fs ^. descrip)
BT.modify $ set msg ("New AddressBook entry created!!\n" ++ T.unpack (fs ^.address)) (fs ^. address)
BT.modify $ set displayBox MsgDisplay case res of
Nothing -> do
BT.modify $
set
msg
("AddressBook Entry already exists: " ++
T.unpack (fs ^. address))
BT.modify $ set displayBox MsgDisplay
Just _ -> do
BT.modify $
set
msg
("New AddressBook entry created!!\n" ++
T.unpack (fs ^. address))
BT.modify $ set displayBox MsgDisplay
-- case end -- case end
s' <- liftIO $ refreshAddressBook s s' <- liftIO $ refreshAddressBook s
BT.put s' BT.put s'
BT.modify $ set dialogBox AdrBook BT.modify $ set dialogBox AdrBook
else do else do
BT.modify $ set msg "Invalid or missing data!!: " BT.modify $ set msg "Invalid or missing data!!: "
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
BT.modify $ set dialogBox AdrBookForm BT.modify $ set dialogBox AdrBookForm
ev -> BT.zoom abForm $ do ev ->
handleFormEvent (BT.VtyEvent ev) BT.zoom abForm $ do
fs <- BT.gets formState handleFormEvent (BT.VtyEvent ev)
BT.modify $ fs <- BT.gets formState
setFieldValid BT.modify $
(isRecipientValid (fs ^. address)) setFieldValid
AddressField (isRecipientValid (fs ^. address))
AdrBookUpdForm -> do AddressField
AdrBookUpdForm -> do
case e of case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook
V.EvKey V.KEnter [] -> do V.EvKey V.KEnter [] -> do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
fs <- BT.zoom abForm $ BT.gets formState fs <- BT.zoom abForm $ BT.gets formState
let idescr = T.unpack $ T.strip (fs ^. descrip) let idescr = T.unpack $ T.strip (fs ^. descrip)
let iabadr = fs ^. address let iabadr = fs ^. address
if not (null idescr) && isRecipientValid iabadr if not (null idescr) && isRecipientValid iabadr
then do then do
res <- liftIO $ updateAdrsInAdrBook pool (fs ^. descrip) (fs ^.address) (s ^. abCurAdrs) res <-
BT.modify $ set msg ("AddressBook entry modified!!\n" ++ T.unpack (fs ^.address)) liftIO $
BT.modify $ set displayBox MsgDisplay updateAdrsInAdrBook
pool
(fs ^. descrip)
(fs ^. address)
(s ^. abCurAdrs)
BT.modify $
set
msg
("AddressBook entry modified!!\n" ++
T.unpack (fs ^. address))
BT.modify $ set displayBox MsgDisplay
-- case end -- case end
s' <- liftIO $ refreshAddressBook s s' <- liftIO $ refreshAddressBook s
BT.put s' BT.put s'
BT.modify $ set dialogBox AdrBook BT.modify $ set dialogBox AdrBook
else do else do
BT.modify $ set msg "Invalid or missing data!!: " BT.modify $ set msg "Invalid or missing data!!: "
BT.modify $ set displayBox MsgDisplay BT.modify $ set displayBox MsgDisplay
BT.modify $ set dialogBox AdrBookForm BT.modify $ set dialogBox AdrBookForm
ev -> BT.zoom abForm $ do ev ->
handleFormEvent (BT.VtyEvent ev) BT.zoom abForm $ do
fs <- BT.gets formState handleFormEvent (BT.VtyEvent ev)
BT.modify $ fs <- BT.gets formState
setFieldValid BT.modify $
(isRecipientValid (fs ^. address)) setFieldValid
AddressField (isRecipientValid (fs ^. address))
AddressField
-- Process delete AddresBook entry -- Process delete AddresBook entry
AdrBookDelForm -> do AdrBookDelForm -> do
case e of case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook
V.EvKey (V.KChar 'c') [] -> do V.EvKey (V.KChar 'c') [] -> do
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
fs <- BT.zoom abForm $ BT.gets formState fs <- BT.zoom abForm $ BT.gets formState
res <- liftIO $ deleteAdrsFromAB pool (fs ^.address) res <- liftIO $ deleteAdrsFromAB pool (fs ^. address)
s' <- liftIO $ refreshAddressBook s s' <- liftIO $ refreshAddressBook s
BT.put s' BT.put s'
BT.modify $ set dialogBox AdrBook BT.modify $ set dialogBox AdrBook
ev -> BT.modify $ set dialogBox AdrBookDelForm ev -> BT.modify $ set dialogBox AdrBookDelForm
-- Process any other event -- Process any other event
Blank -> do Blank -> do
case e of case e of
@ -1321,9 +1375,7 @@ runZenithTUI config = do
if not (null walList) if not (null walList)
then zcashWalletLastSync $ entityVal $ head walList then zcashWalletLastSync $ entityVal $ head walList
else 0 else 0
abookList <- getAdrBook pool $ zgb_net chainInfo abookList <- getAdrBook pool $ zgb_net chainInfo
bal <- bal <-
if not (null accList) if not (null accList)
then getBalance pool $ entityKey $ head accList then getBalance pool $ entityKey $ head accList
@ -1451,8 +1503,7 @@ addNewAccount n s = do
Right zA' -> do Right zA' -> do
r <- saveAccount pool zA' r <- saveAccount pool zA'
case r of case r of
Nothing -> Nothing -> return $ s & msg .~ "Account already exists: " ++ T.unpack n
return $ s & msg .~ "Account already exists: " ++ T.unpack n
Just x -> do Just x -> do
aL <- runNoLoggingT $ getAccounts pool (entityKey selWallet) aL <- runNoLoggingT $ getAccounts pool (entityKey selWallet)
let nL = let nL =
@ -1519,10 +1570,11 @@ refreshAddressBook s = do
do case L.listSelectedElement $ s ^. abAddresses of do case L.listSelectedElement $ s ^. abAddresses of
Nothing -> do Nothing -> do
let fAdd = let fAdd =
L.listSelectedElement $ L.listMoveToBeginning $ s ^. abAddresses L.listSelectedElement $
L.listMoveToBeginning $ s ^. abAddresses
return fAdd return fAdd
Just a2 -> return $ Just a2 Just a2 -> return $ Just a2
abookList <- getAdrBook pool (s ^. network) abookList <- getAdrBook pool (s ^. network)
let tL' = L.listReplace (Vec.fromList abookList) (Just 0) (s ^. abAddresses) let tL' = L.listReplace (Vec.fromList abookList) (Just 0) (s ^. abAddresses)
return $ s & abAddresses .~ tL' return $ s & abAddresses .~ tL'
@ -1547,8 +1599,7 @@ addNewAddress n scope s = do
Right uA' -> do Right uA' -> do
nAddr <- saveAddress pool uA' nAddr <- saveAddress pool uA'
case nAddr of case nAddr of
Nothing -> Nothing -> return $ s & msg .~ "Address already exists: " ++ T.unpack n
return $ s & msg .~ "Address already exists: " ++ T.unpack n
Just x -> do Just x -> do
addrL <- runNoLoggingT $ getAddresses pool (entityKey selAccount) addrL <- runNoLoggingT $ getAddresses pool (entityKey selAccount)
let nL = let nL =

View File

@ -1,6 +1,6 @@
cabal-version: 3.0 cabal-version: 3.0
name: zenith name: zenith
version: 0.5.3.0-beta version: 0.5.3.1-beta
license: MIT license: MIT
license-file: LICENSE license-file: LICENSE
author: Rene Vergara author: Rene Vergara