rvv041 #82
2 changed files with 90 additions and 19 deletions
|
@ -2,6 +2,7 @@
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE BlockArguments #-}
|
||||||
pitmutt marked this conversation as resolved
Outdated
|
|||||||
|
|
||||||
module Zenith.CLI where
|
module Zenith.CLI where
|
||||||
|
|
||||||
|
@ -151,6 +152,7 @@ data DialogType
|
||||||
| Blank
|
| Blank
|
||||||
| AdrBook
|
| AdrBook
|
||||||
| AdrBookForm
|
| AdrBookForm
|
||||||
|
| AdrBookUpdForm
|
||||||
|
|
||||||
data DisplayType
|
data DisplayType
|
||||||
= AddrDisplay
|
= AddrDisplay
|
||||||
|
@ -190,6 +192,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
|
||||||
pitmutt marked this conversation as resolved
Outdated
pitmutt
commented
The field should be named The field should be named `_abAddresses`
|
|||||||
}
|
}
|
||||||
|
|
||||||
pitmutt marked this conversation as resolved
Outdated
pitmutt
commented
What is this field for? What is this field for?
|
|||||||
makeLenses ''State
|
makeLenses ''State
|
||||||
pitmutt marked this conversation as resolved
Outdated
pitmutt
commented
What is this field for? What is this field for?
|
|||||||
|
@ -362,6 +365,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
||||||
C.hCenter
|
C.hCenter
|
||||||
(hBox [capCommand "↲ " "Send", capCommand "<esc> " "Cancel"]))
|
(hBox [capCommand "↲ " "Send", capCommand "<esc> " "Cancel"]))
|
||||||
Blank -> emptyWidget
|
Blank -> emptyWidget
|
||||||
|
-- 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)
|
||||||
|
@ -384,15 +388,21 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
||||||
C.hCenter $
|
C.hCenter $
|
||||||
(capCommand "D" "elete Address" <+>
|
(capCommand "D" "elete Address" <+>
|
||||||
capCommand "S" "end Zcash" <+>
|
capCommand "S" "end Zcash" <+>
|
||||||
capCommand3 "E" "x" "it")]])
|
capCommand3 "E" "x" "it")]])
|
||||||
|
-- Address Book new entry form
|
||||||
AdrBookForm ->
|
AdrBookForm ->
|
||||||
D.renderDialog
|
D.renderDialog
|
||||||
(D.dialog (Just (str " Address Book Entry ")) Nothing 50)
|
(D.dialog (Just $ str " New Address Book Entry ") Nothing 50)
|
||||||
|
(renderForm (st ^. abForm) <=>
|
||||||
|
C.hCenter
|
||||||
|
(hBox [capCommand "↲" " Save", capCommand3 "" "<Esc>" " Cancel"]))
|
||||||
|
-- Address Book edit/update entry form
|
||||||
|
AdrBookUpdForm ->
|
||||||
|
D.renderDialog
|
||||||
|
(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"]))
|
||||||
|
|
||||||
|
|
||||||
splashDialog :: State -> Widget Name
|
splashDialog :: State -> Widget Name
|
||||||
splashDialog st =
|
splashDialog st =
|
||||||
|
@ -772,6 +782,7 @@ appEvent (BT.AppEvent t) = do
|
||||||
SendTx -> return ()
|
SendTx -> return ()
|
||||||
AdrBook -> return ()
|
AdrBook -> return ()
|
||||||
AdrBookForm -> return ()
|
AdrBookForm -> return ()
|
||||||
|
AdrBookUpdForm -> return ()
|
||||||
Blank -> do
|
Blank -> do
|
||||||
if s ^. timer == 90
|
if s ^. timer == 90
|
||||||
then do
|
then do
|
||||||
|
@ -1041,10 +1052,15 @@ appEvent (BT.VtyEvent e) = do
|
||||||
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 $
|
BT.modify $ set abCurAdrs (addressBookAddress (entityVal a))
|
||||||
set abForm $
|
BT.modify $
|
||||||
mkNewABForm (AdrBookEntry (addressBookDescrip (entityVal a)) (addressBookAddress (entityVal a)))
|
set abForm $
|
||||||
BT.modify $ set dialogBox AdrBookForm
|
mkNewABForm (AdrBookEntry (addressBookDescrip (entityVal a)) (addressBookAddress (entityVal a)))
|
||||||
|
BT.modify $ set dialogBox AdrBookUpdForm
|
||||||
|
|
||||||
|
_ -> do
|
||||||
|
BT.modify $ set dialogBox Blank
|
||||||
|
|
||||||
-- Create a new entry in Address Book
|
-- Create a new entry in Address Book
|
||||||
pitmutt marked this conversation as resolved
Outdated
pitmutt
commented
It is not necessary to show the address, it is too long for the message window. We should only use the name in the message. It is not necessary to show the address, it is too long for the message window. We should only use the name in the message.
|
|||||||
V.EvKey (V.KChar 'n') [] -> do
|
V.EvKey (V.KChar 'n') [] -> do
|
||||||
BT.modify $ set abForm $ mkNewABForm (AdrBookEntry "" "")
|
BT.modify $ set abForm $ mkNewABForm (AdrBookEntry "" "")
|
||||||
|
@ -1061,7 +1077,7 @@ appEvent (BT.VtyEvent e) = do
|
||||||
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 <- liftIO $ saveAdrsInAdrBook pool $ AddressBook (ZcashNetDB (s ^. network)) (fs ^. descrip) (fs ^.address)
|
||||||
case res of
|
case res of
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
|
@ -1070,15 +1086,42 @@ appEvent (BT.VtyEvent e) = do
|
||||||
Just _ -> do
|
Just _ -> do
|
||||||
BT.modify $ set msg ("New AddressBook entry created!!\n" ++ T.unpack (fs ^.address))
|
BT.modify $ set msg ("New AddressBook entry created!!\n" ++ T.unpack (fs ^.address))
|
||||||
BT.modify $ set displayBox MsgDisplay
|
BT.modify $ set displayBox MsgDisplay
|
||||||
-- ns <- liftIO $ refreshWallet nw
|
-- case end
|
||||||
abookList <- liftIO $ getAdrBook pool (s ^. network)
|
ab <- liftIO $ refreshAddressBook s
|
||||||
let abL = L.listReplace (Vec.fromList abookList) (Just 0) (s ^. abaddresses)
|
BT.put ab
|
||||||
|
BT.modify $ set dialogBox AdrBook
|
||||||
|
else do
|
||||||
|
BT.modify $ set msg "Invalid or missing data!!: "
|
||||||
|
BT.modify $ set displayBox MsgDisplay
|
||||||
|
BT.modify $ set dialogBox AdrBookForm
|
||||||
|
ev -> BT.zoom abForm $ do
|
||||||
|
handleFormEvent (BT.VtyEvent ev)
|
||||||
|
fs <- BT.gets formState
|
||||||
|
BT.modify $
|
||||||
|
setFieldValid
|
||||||
|
(isRecipientValid (fs ^. address))
|
||||||
|
AddressField
|
||||||
|
AdrBookUpdForm -> do
|
||||||
|
case e of
|
||||||
|
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook
|
||||||
|
V.EvKey V.KEnter [] -> do
|
||||||
|
pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath
|
||||||
|
fs <- BT.zoom abForm $ BT.gets formState
|
||||||
|
let idescr = T.unpack $ T.strip (fs ^. descrip)
|
||||||
|
let iabadr = fs ^. address
|
||||||
|
if not (null idescr) && isRecipientValid iabadr
|
||||||
|
then do
|
||||||
|
res <- liftIO $ 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
|
||||||
|
abookList <- liftIO $ getAdrBook pool (s ^. network)
|
||||||
|
let abL = L.listReplace (Vec.fromList abookList) (Just 0) (s ^. abaddresses)
|
||||||
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 -> BT.zoom abForm $ do
|
||||||
handleFormEvent (BT.VtyEvent ev)
|
handleFormEvent (BT.VtyEvent ev)
|
||||||
fs <- BT.gets formState
|
fs <- BT.gets formState
|
||||||
|
@ -1086,7 +1129,6 @@ appEvent (BT.VtyEvent e) = do
|
||||||
setFieldValid
|
setFieldValid
|
||||||
(isRecipientValid (fs ^. address))
|
(isRecipientValid (fs ^. address))
|
||||||
AddressField
|
AddressField
|
||||||
|
|
||||||
Blank -> do
|
Blank -> do
|
||||||
case e of
|
case e of
|
||||||
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
|
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
|
||||||
|
@ -1237,6 +1279,7 @@ runZenithCLI config = do
|
||||||
(mkSendForm 0 $ SendInput "" 0.0 "")
|
(mkSendForm 0 $ SendInput "" 0.0 "")
|
||||||
(L.list ABList (Vec.fromList abookList) 1)
|
(L.list ABList (Vec.fromList abookList) 1)
|
||||||
(mkNewABForm (AdrBookEntry "" ""))
|
(mkNewABForm (AdrBookEntry "" ""))
|
||||||
|
" "
|
||||||
Left e -> print $
|
Left e -> print $
|
||||||
"No Zebra node available on port " <>
|
"No Zebra node available on port " <>
|
||||||
show port <> ". Check your configuration."
|
show port <> ". Check your configuration."
|
||||||
|
@ -1380,6 +1423,23 @@ refreshTxs s = do
|
||||||
let tL' = L.listReplace (Vec.fromList tList) (Just 0) (s ^. transactions)
|
let tL' = L.listReplace (Vec.fromList tList) (Just 0) (s ^. transactions)
|
||||||
return $ s & transactions .~ tL'
|
return $ s & transactions .~ tL'
|
||||||
|
|
||||||
|
refreshAddressBook :: State -> IO State
|
||||||
|
refreshAddressBook s = do
|
||||||
|
pool <- runNoLoggingT $ initPool $ s ^. dbPath
|
||||||
|
selAddress <-
|
||||||
|
do case L.listSelectedElement $ s ^. abaddresses of
|
||||||
|
Nothing -> do
|
||||||
|
let fAdd =
|
||||||
|
L.listSelectedElement $ L.listMoveToBeginning $ s ^. abaddresses
|
||||||
|
return fAdd
|
||||||
|
Just a2 -> return $ Just a2
|
||||||
|
case selAddress of
|
||||||
|
Nothing -> return s
|
||||||
|
Just (_i, a) -> do
|
||||||
|
abookList <- getAdrBook pool (s ^. network)
|
||||||
|
let tL' = L.listReplace (Vec.fromList abookList) (Just 0) (s ^. abaddresses)
|
||||||
|
return $ s & abaddresses .~ tL'
|
||||||
|
|
||||||
addNewAddress :: T.Text -> Scope -> State -> IO State
|
addNewAddress :: T.Text -> Scope -> State -> IO State
|
||||||
addNewAddress n scope s = do
|
addNewAddress n scope s = do
|
||||||
pool <- runNoLoggingT $ initPool $ s ^. dbPath
|
pool <- runNoLoggingT $ initPool $ s ^. dbPath
|
||||||
|
|
|
@ -15,6 +15,7 @@
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
|
{-# LANGUAGE BlockArguments #-}
|
||||||
pitmutt marked this conversation as resolved
Outdated
pitmutt
commented
This option is not required This option is not required
|
|||||||
|
|
||||||
module Zenith.DB where
|
module Zenith.DB where
|
||||||
|
|
||||||
|
@ -1494,14 +1495,24 @@ saveAdrsInAdrBook pool a =
|
||||||
PS.retryOnBusy $ flip PS.runSqlPool pool $ insertUniqueEntity a
|
PS.retryOnBusy $ flip PS.runSqlPool pool $ insertUniqueEntity a
|
||||||
|
|
||||||
-- | Update an existing address into AddressBook
|
-- | Update an existing address into AddressBook
|
||||||
updateAdrsInAdrBook :: ConnectionPool -> T.Text -> AddressBookId -> IO ()
|
updateAdrsInAdrBook :: ConnectionPool -> T.Text -> T.Text -> T.Text -> IO ()
|
||||||
updateAdrsInAdrBook pool a i = do
|
updateAdrsInAdrBook pool d a ia = do
|
||||||
runNoLoggingT $
|
runNoLoggingT $
|
||||||
PS.retryOnBusy $
|
PS.retryOnBusy $
|
||||||
flip PS.runSqlPool pool $ do
|
flip PS.runSqlPool pool $ do
|
||||||
update $ \ab -> do
|
update $ \ab -> do
|
||||||
set ab [AddressBookAddress =. val a]
|
set ab [AddressBookDescrip =. val d, AddressBookAddress =. val a]
|
||||||
where_ $ ab ^. AddressBookId ==. val i
|
where_ $ ab ^. AddressBookAddress ==. val ia
|
||||||
|
|
||||||
|
getABookRec :: ConnectionPool -> T.Text -> IO [Entity AddressBook]
|
||||||
|
getABookRec pool a = do
|
||||||
pitmutt marked this conversation as resolved
Outdated
pitmutt
commented
If this function is intended to provide only one record, it should return a If this function is intended to provide only one record, it should return a `IO (Maybe (Entity AddressBook))`
|
|||||||
|
runNoLoggingT $
|
||||||
|
PS.retryOnBusy $
|
||||||
|
flip PS.runSqlPool pool $
|
||||||
|
select $ do
|
||||||
|
adrbook <- from $ table @AddressBook
|
||||||
|
where_ ((adrbook ^. AddressBookAddress) ==. val a)
|
||||||
|
return adrbook
|
||||||
|
|
||||||
-- | delete an existing address from AddressBook
|
-- | delete an existing address from AddressBook
|
||||||
deleteAdrsFromAB :: ConnectionPool -> AddressBookId -> IO ()
|
deleteAdrsFromAB :: ConnectionPool -> AddressBookId -> IO ()
|
||||||
|
@ -1509,7 +1520,7 @@ deleteAdrsFromAB pool i = do
|
||||||
runNoLoggingT $
|
runNoLoggingT $
|
||||||
PS.retryOnBusy $
|
PS.retryOnBusy $
|
||||||
flip PS.runSqlPool pool $ do
|
flip PS.runSqlPool pool $ do
|
||||||
delete $ do
|
delete $ do
|
||||||
ab <- from $ table @AddressBook
|
ab <- from $ table @AddressBook
|
||||||
where_ (ab ^. AddressBookId ==. val i)
|
where_ (ab ^. AddressBookId ==. val i)
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue
This option is not required.