diff --git a/.gitignore b/.gitignore index 1c231fa..00967d7 100644 --- a/.gitignore +++ b/.gitignore @@ -1,3 +1,7 @@ .stack-work/ *~ dist-newstyle/ +zenith.db +zenith.log +zenith.db-shm +zenith.db-wal diff --git a/CHANGELOG.md b/CHANGELOG.md index 8daee9c..aa0b028 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -17,6 +17,11 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0 ## [0.5.2.0-beta] +### Added + +- Address Book functionality. Allows users to store frequently used zcash addresses and + generate transactions using them. + ### Changed - Update to `zcash-haskell-0.6.2.0` to increase performance of transaction creation diff --git a/README.md b/README.md index efabca0..bce5523 100644 --- a/README.md +++ b/README.md @@ -21,6 +21,7 @@ Zenith is a wallet for the [Zebra](https://zfnd.org/zebra/) Zcash node . It has - Listing transactions for specific addresses, decoding memos for easy reading. - Copying addresses to the clipboard. - Sending transactions with shielded memo support. +- Address Book for storing frequently used zcash addresses ## Installation diff --git a/src/Zenith/CLI.hs b/src/Zenith/CLI.hs index cfef49d..a324b38 100644 --- a/src/Zenith/CLI.hs +++ b/src/Zenith/CLI.hs @@ -3,6 +3,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} + module Zenith.CLI where import qualified Brick.AttrMap as A @@ -21,6 +22,8 @@ import Brick.Forms , renderForm , setFieldValid , updateFormState + , FormFieldState + , editShowableField ) import qualified Brick.Main as M import qualified Brick.Types as BT @@ -40,6 +43,9 @@ import Brick.Widgets.Core , joinBorders , padAll , padBottom + , padTop + , padLeft + , setAvailableSize , str , strWrap , strWrapWith @@ -48,6 +54,7 @@ import Brick.Widgets.Core , txtWrapWith , updateAttrMap , vBox + , viewport , vLimit , withAttr , withBorderStyle @@ -109,6 +116,10 @@ data Name | RecField | AmtField | MemoField + | ABViewport + | ABList + | DescripField + | AddressField deriving (Eq, Show, Ord) data DialogInput = DialogInput @@ -125,6 +136,13 @@ data SendInput = SendInput makeLenses ''SendInput +data AdrBookEntry = AdrBookEntry + { _descrip :: !T.Text + , _address :: !T.Text + } deriving (Show) + +makeLenses ''AdrBookEntry + data DialogType = WName | AName @@ -133,6 +151,10 @@ data DialogType | ASelect | SendTx | Blank + | AdrBook + | AdrBookForm + | AdrBookUpdForm + | AdrBookDelForm data DisplayType = AddrDisplay @@ -142,6 +164,7 @@ data DisplayType | TxIdDisplay | SyncDisplay | SendDisplay + | AdrBookEntryDisplay | BlankDisplay data Tick @@ -172,6 +195,9 @@ data State = State , _eventDispatch :: !(BC.BChan Tick) , _timer :: !Int , _txForm :: !(Form SendInput () Name) + , _abAddresses :: !(L.List Name (Entity AddressBook)) + , _abForm :: !(Form AdrBookEntry () Name) + , _abCurAdrs :: !T.Text -- used for address book CRUD operations , _sentTx :: !(Maybe HexString) } @@ -186,14 +212,14 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] withBorderStyle unicode $ B.borderWithLabel (str - ("Zenith - " <> + (" Zenith - " <> show (st ^. network) <> " - " <> - T.unpack + (T.unpack (maybe "(None)" (\(_, w) -> zcashWalletName $ entityVal w) - (L.listSelectedElement (st ^. wallets))))) + (L.listSelectedElement (st ^. wallets)))) ++ " ")) (C.hCenter (str ("Account: " ++ @@ -208,17 +234,19 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] if st ^. network == MainNet then displayZec (st ^. balance) else displayTaz (st ^. balance))) <=> - listAddressBox "Addresses" (st ^. addresses) <+> + listAddressBox " Addresses " (st ^. addresses) <+> B.vBorder <+> - (C.hCenter (str ("Last block seen: " ++ show (st ^. syncBlock))) <=> - listTxBox "Transactions" (st ^. network) (st ^. transactions))) <=> + (C.hCenter (str ("Last block seen: " ++ show (st ^. syncBlock) ++ "\n")) <=> + listTxBox " Transactions " (st ^. network) (st ^. transactions))) <=> C.hCenter (hBox [ capCommand "W" "allets" , capCommand "A" "ccounts" , capCommand "V" "iew address" , capCommand "S" "end Tx" + , capCommand2 "Address " "B" "ook" , capCommand "Q" "uit" + , capCommand "?" " Help" , str $ show (st ^. timer) ]) listBox :: Show e => String -> L.List Name e -> Widget Name @@ -257,7 +285,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] (hBox [ capCommand "↑↓ " "move" , capCommand "↲ " "select" - , capCommand "Tab " "->" + , capCommand3 "" "Tab" " ->" ]) ] listTxBox :: @@ -273,7 +301,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] (hBox [ capCommand "↑↓ " "move" , capCommand "T" "x Display" - , capCommand "Tab " "<-" + , capCommand3 "" "Tab" " <-" ]) ] helpDialog :: State -> Widget Name @@ -285,7 +313,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] vBox ([str "Actions", B.hBorder] <> actionList)) else emptyWidget where - keyList = map (C.hCenter . str) ["?", "Esc", "w", "a", "v", "q"] + keyList = map (C.hCenter . str) ["?", "Esc", "w", "a", "v", "s", "b", "q"] actionList = map (hLimit 40 . str) @@ -294,6 +322,8 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] , "Switch wallets" , "Switch accounts" , "View address" + , "Send Tx" + , "Address Book" , "Quit" ] inputDialog :: State -> Widget Name @@ -341,6 +371,53 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] C.hCenter (hBox [capCommand "↲ " "Send", capCommand " " "Cancel"])) Blank -> emptyWidget + -- Address Book List + AdrBook -> + D.renderDialog + (D.dialog (Just $ str " Address Book ") Nothing 60) + (withAttr abDefAttr $ + setAvailableSize (50,20) $ + viewport ABViewport BT.Vertical $ + vLimit 20 $ + hLimit 50 $ + vBox [vLimit 16 $ + hLimit 50 $ + vBox $ [ L.renderList listDrawAB True (s ^. abAddresses) ], + padTop Max $ + vLimit 4 $ + hLimit 50 $ + withAttr abMBarAttr $ + vBox $ [C.hCenter $ + (capCommand "N" "ew Address" <+> + capCommand "E" "dit Address" <+> + capCommand3 "" "C" "opy Address"), + C.hCenter $ + (capCommand "D" "elete Address" <+> + capCommand "S" "end Zcash" <+> + capCommand3 "E" "x" "it")]]) + -- Address Book new entry form + AdrBookForm -> + D.renderDialog + (D.dialog (Just $ str " New Address Book Entry ") Nothing 50) + (renderForm (st ^. abForm) <=> + C.hCenter + (hBox [capCommand "↲" " Save", capCommand3 "" "" " Cancel"])) + -- Address Book edit/update entry form + AdrBookUpdForm -> + D.renderDialog + (D.dialog (Just $ str " Edit Address Book Entry ") Nothing 50) + (renderForm (st ^. abForm) <=> + C.hCenter + (hBox [capCommand "↲" " Save", capCommand3 "" "" " Cancel"])) + -- Address Book edit/update entry form + AdrBookDelForm -> + D.renderDialog + (D.dialog (Just $ str " Delete Address Book Entry ") Nothing 50) + (renderForm (st ^. abForm) <=> + C.hCenter + (hBox [capCommand "C" "onfirm delete", capCommand3 "" "" " Cancel"])) + -- + splashDialog :: State -> Widget Name splashDialog st = if st ^. splashBox @@ -355,6 +432,13 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] (withAttr titleAttr (str "Zcash Wallet v0.5.3.0-beta")) <=> C.hCenter (withAttr blinkAttr $ str "Press any key...")) else emptyWidget + + capCommand3 :: String -> String -> String -> Widget Name + capCommand3 l h e = hBox [str l, withAttr titleAttr (str h), str e] + + capCommand2 :: String -> String -> String -> Widget Name + capCommand2 l h e = hBox [str l, withAttr titleAttr (str h), str e, str " | "] + capCommand :: String -> String -> Widget Name capCommand k comm = hBox [withAttr titleAttr (str k), str comm, str " | "] xCommand :: Widget Name @@ -478,6 +562,21 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] (strWrapWith (WrapSettings False True NoFill FillAfterFirst) (st ^. msg))) + AdrBookEntryDisplay -> do + case L.listSelectedElement $ st ^. abAddresses of + Just (_, a) -> do + let abentry = T.pack $ + " Descr: " ++ + T.unpack (addressBookAbdescrip (entityVal a)) ++ + "\n Address: " ++ + T.unpack (addressBookAbaddress (entityVal a)) + withBorderStyle unicodeBold $ + D.renderDialog + (D.dialog (Just $ txt " Address Book Entry ") Nothing 60) + (padAll 1 $ + txtWrapWith (WrapSettings False True NoFill FillAfterFirst) $ + abentry) + _ -> emptyWidget BlankDisplay -> emptyWidget mkInputForm :: DialogInput -> Form DialogInput e Name @@ -498,10 +597,20 @@ mkSendForm bal = ] where isAmountValid :: Integer -> Float -> Bool - isAmountValid b i = (fromIntegral b * 100000000.0) >= i + isAmountValid b i = (fromIntegral b * 100000000.0) >= i && i > 0 label s w = padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w +mkNewABForm :: AdrBookEntry -> Form AdrBookEntry e Name +mkNewABForm = + newForm + [ label "Descrip: " @@= editTextField descrip DescripField (Just 1) + , label "Address: " @@= editTextField address AddressField (Just 1) + ] + where + label s w = + padBottom (Pad 1) $ vLimit 1 (hLimit 10 $ str s <+> fill ' ') <+> w + isRecipientValid :: T.Text -> Bool isRecipientValid a = case isValidUnifiedAddress (E.encodeUtf8 a) of @@ -571,6 +680,14 @@ listDrawTx znet sel tx = then withAttr customAttr (txt $ "> " <> s) else txt $ " " <> s +listDrawAB :: Bool -> Entity AddressBook -> Widget Name +listDrawAB sel ab = + let selStr s = + if sel + then withAttr abSelAttr (txt $ " " <> s ) + else txt $ " " <> s + in selStr $ addressBookAbdescrip (entityVal ab) + customAttr :: A.AttrName customAttr = L.listSelectedAttr <> A.attrName "custom" @@ -589,6 +706,15 @@ barDoneAttr = A.attrName "done" barToDoAttr :: A.AttrName barToDoAttr = A.attrName "remaining" +abDefAttr :: A.AttrName +abDefAttr = A.attrName "abdefault" + +abSelAttr :: A.AttrName +abSelAttr = A.attrName "abselected" + +abMBarAttr :: A.AttrName +abMBarAttr = A.attrName "menubar" + validBarValue :: Float -> Float validBarValue = clamp 0 1 @@ -600,8 +726,7 @@ scanZebra dbP zHost zPort b eChan = do dbBlock <- runNoLoggingT $ getMaxBlock pool let sb = max dbBlock b if sb > zgb_blocks bStatus || sb < 1 - then do - liftIO $ BC.writeBChan eChan $ TickMsg "Invalid starting block for scan" + then liftIO $ BC.writeBChan eChan $ TickMsg "Invalid starting block for scan" else do let bList = [(sb + 1) .. (zgb_blocks bStatus)] if not (null bList) @@ -621,8 +746,7 @@ scanZebra dbP zHost zPort b eChan = do "getblock" [Data.Aeson.String $ T.pack $ show bl, jsonNumber 1] case r of - Left e1 -> do - liftIO $ BC.writeBChan eChan $ TickMsg e1 + Left e1 -> liftIO $ BC.writeBChan eChan $ TickMsg e1 Right blk -> do r2 <- liftIO $ @@ -632,8 +756,7 @@ scanZebra dbP zHost zPort b eChan = do "getblock" [Data.Aeson.String $ T.pack $ show bl, jsonNumber 0] case r2 of - Left e2 -> do - liftIO $ BC.writeBChan eChan $ TickMsg e2 + Left e2 -> liftIO $ BC.writeBChan eChan $ TickMsg e2 Right hb -> do let blockTime = getBlockTime hb mapM_ (runNoLoggingT . processTx zHost zPort blockTime pool) $ @@ -660,8 +783,8 @@ appEvent (BT.AppEvent t) = do TxDisplay -> return () TxIdDisplay -> return () SyncDisplay -> return () - SendDisplay -> do - BT.modify $ set msg m + SendDisplay -> BT.modify $ set msg m + AdrBookEntryDisplay -> return () BlankDisplay -> return () TickTx txid -> do BT.modify $ set sentTx (Just txid) @@ -674,6 +797,7 @@ appEvent (BT.AppEvent t) = do TxDisplay -> return () TxIdDisplay -> return () SendDisplay -> return () + AdrBookEntryDisplay -> return () SyncDisplay -> do if s ^. barValue == 1.0 then do @@ -706,6 +830,10 @@ appEvent (BT.AppEvent t) = do WSelect -> return () ASelect -> return () SendTx -> return () + AdrBook -> return () + AdrBookForm -> return () + AdrBookUpdForm -> return () + AdrBookDelForm -> return () Blank -> do if s ^. timer == 90 then do @@ -723,8 +851,7 @@ appEvent (BT.AppEvent t) = do (s ^. eventDispatch) BT.modify $ set timer 0 return () - else do - BT.modify $ set timer $ 1 + s ^. timer + else BT.modify $ set timer $ 1 + s ^. timer appEvent (BT.VtyEvent e) = do r <- F.focusGetCurrent <$> use focusRing s <- BT.get @@ -733,8 +860,7 @@ appEvent (BT.VtyEvent e) = do else if s ^. helpBox then do case e of - V.EvKey V.KEsc [] -> do - BT.modify $ set helpBox False + V.EvKey V.KEsc [] -> BT.modify $ set helpBox False _ev -> return () else do case s ^. displayBox of @@ -805,6 +931,7 @@ appEvent (BT.VtyEvent e) = do _ev -> return () SendDisplay -> BT.modify $ set displayBox BlankDisplay SyncDisplay -> BT.modify $ set displayBox BlankDisplay + AdrBookEntryDisplay -> BT.modify $ set displayBox BlankDisplay BlankDisplay -> do case s ^. dialogBox of WName -> do @@ -945,14 +1072,150 @@ appEvent (BT.VtyEvent e) = do BT.modify $ set msg "Invalid inputs" BT.modify $ set displayBox MsgDisplay BT.modify $ set dialogBox Blank - ev -> do - BT.zoom txForm $ do - handleFormEvent (BT.VtyEvent ev) - fs <- BT.gets formState - BT.modify $ - setFieldValid - (isRecipientValid (fs ^. sendTo)) - RecField + ev -> BT.zoom txForm $ do + handleFormEvent (BT.VtyEvent ev) + fs <- BT.gets formState + BT.modify $ + setFieldValid + (isRecipientValid (fs ^. sendTo)) + RecField + AdrBook -> do + case e of + V.EvKey (V.KChar 'x') [] -> + BT.modify $ set dialogBox Blank + V.EvKey (V.KChar 'c') [] -> do + -- Copy Address to Clipboard + case L.listSelectedElement $ s ^. abAddresses of + Just (_, a) -> do + liftIO $ + setClipboard $ + T.unpack $ addressBookAbaddress (entityVal a) + BT.modify $ + set msg $ + "Address copied to Clipboard from >>\n" ++ + T.unpack (addressBookAbdescrip (entityVal a)) + BT.modify $ set displayBox MsgDisplay + _ -> do + BT.modify $ set msg "Error while copying the address!!" + BT.modify $ set displayBox MsgDisplay + -- Send Zcash transaction + V.EvKey (V.KChar 's') [] -> do + case L.listSelectedElement $ s ^. abAddresses of + Just (_, a) -> do + BT.modify $ + set txForm $ + mkSendForm (s ^. balance) (SendInput (addressBookAbaddress (entityVal a)) 0.0 "") + BT.modify $ set dialogBox SendTx + _ -> do + BT.modify $ set msg "No receiver address available!!" + BT.modify $ set displayBox MsgDisplay + -- Edit an entry in Address Book + V.EvKey (V.KChar 'e') [] -> do + case L.listSelectedElement $ s ^. abAddresses of + Just (_, a) -> do + BT.modify $ set abCurAdrs (addressBookAbaddress (entityVal a)) + BT.modify $ + set abForm $ + mkNewABForm (AdrBookEntry (addressBookAbdescrip (entityVal a)) (addressBookAbaddress (entityVal a))) + BT.modify $ set dialogBox AdrBookUpdForm + _ -> do + BT.modify $ set dialogBox Blank + -- Delete an entry from Address Book + V.EvKey (V.KChar 'd') [] -> do + case L.listSelectedElement $ s ^. abAddresses of + Just (_, a) -> do + BT.modify $ set abCurAdrs (addressBookAbaddress (entityVal a)) + BT.modify $ + set abForm $ + mkNewABForm (AdrBookEntry (addressBookAbdescrip (entityVal a)) (addressBookAbaddress (entityVal a))) + BT.modify $ set dialogBox AdrBookDelForm + _ -> do + BT.modify $ set dialogBox Blank + -- Create a new entry in Address Book + V.EvKey (V.KChar 'n') [] -> do + BT.modify $ set abForm $ mkNewABForm (AdrBookEntry "" "") + BT.modify $ set dialogBox AdrBookForm + -- Show AddressBook entry data + V.EvKey V.KEnter [] -> do + BT.modify $ set displayBox AdrBookEntryDisplay + + -- Process any other event + ev -> BT.zoom abAddresses $ L.handleListEvent ev + -- Process new address book entry + AdrBookForm -> 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 $ saveAdrsInAdrBook pool $ AddressBook (ZcashNetDB (s ^. network)) (fs ^. descrip) (fs ^.address) + 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 + s' <- liftIO $ refreshAddressBook s + BT.put s' + 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 + s' <- liftIO $ refreshAddressBook s + BT.put s' + 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 + -- Process delete AddresBook entry + AdrBookDelForm -> do + case e of + V.EvKey V.KEsc [] -> BT.modify $ set dialogBox AdrBook + V.EvKey (V.KChar 'c') [] -> do + pool <- liftIO $ runNoLoggingT $ initPool $ s ^. dbPath + fs <- BT.zoom abForm $ BT.gets formState + res <- liftIO $ deleteAdrsFromAB pool (fs ^.address) + s' <- liftIO $ refreshAddressBook s + BT.put s' + BT.modify $ set dialogBox AdrBook + ev -> BT.modify $ set dialogBox AdrBookDelForm + -- Process any other event Blank -> do case e of V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext @@ -976,12 +1239,16 @@ appEvent (BT.VtyEvent e) = do set txForm $ mkSendForm (s ^. balance) (SendInput "" 0.0 "") BT.modify $ set dialogBox SendTx + V.EvKey (V.KChar 'b') [] -> + BT.modify $ set dialogBox AdrBook ev -> case r of Just AList -> BT.zoom addresses $ L.handleListEvent ev Just TList -> BT.zoom transactions $ L.handleListEvent ev + Just ABList -> + BT.zoom abAddresses $ L.handleListEvent ev _anyName -> return () where printMsg :: String -> BT.EventM Name State () @@ -1001,11 +1268,14 @@ theMap = , (blinkAttr, style V.blink) , (focusedFormInputAttr, V.white `on` V.blue) , (invalidFormInputAttr, V.red `on` V.black) - , (E.editAttr, V.white `on` V.blue) - , (E.editFocusedAttr, V.blue `on` V.white) + , (E.editAttr, V.white `on` V.black) + , (E.editFocusedAttr, V.black `on` V.white) , (baseAttr, bg V.brightBlack) , (barDoneAttr, V.white `on` V.blue) , (barToDoAttr, V.white `on` V.black) + , (abDefAttr, V.white `on` V.blue) + , (abSelAttr, V.black `on` V.white) + , (abMBarAttr, V.white `on` V.black) ] theApp :: M.App State Tick Name @@ -1051,6 +1321,9 @@ runZenithCLI config = do if not (null walList) then zcashWalletLastSync $ entityVal $ head walList else 0 + + abookList <- getAdrBook pool $ zgb_net chainInfo + bal <- if not (null accList) then getBalance pool $ entityKey $ head accList @@ -1091,6 +1364,9 @@ runZenithCLI config = do eventChan 0 (mkSendForm 0 $ SendInput "" 0.0 "") + (L.list ABList (Vec.fromList abookList) 1) + (mkNewABForm (AdrBookEntry "" "")) + "" Nothing Left e -> do print $ @@ -1146,14 +1422,13 @@ addNewWallet n s = do let netName = s ^. network r <- saveWallet pool $ ZcashWallet n (ZcashNetDB netName) (PhraseDB sP) bH 0 case r of - Nothing -> do - return $ s & msg .~ ("Wallet already exists: " ++ T.unpack n) + Nothing -> return $ s & msg .~ ("Wallet already exists: " ++ T.unpack n) Just _ -> do wL <- getWallets pool netName let aL = L.listFindBy (\x -> zcashWalletName (entityVal x) == n) $ L.listReplace (Vec.fromList wL) (Just 0) (s ^. wallets) - return $ (s & wallets .~ aL) & msg .~ "Created new wallet: " ++ T.unpack n + return $ s & wallets .~ aL & msg .~ "Created new wallet: " ++ T.unpack n addNewAccount :: T.Text -> State -> IO State addNewAccount n s = do @@ -1172,19 +1447,19 @@ addNewAccount n s = do try $ createZcashAccount n (aL' + 1) selWallet :: IO (Either IOError ZcashAccount) case zA of - Left e -> return $ s & msg .~ ("Error: " ++ show e) + Left e -> return $ s & msg .~ "Error: " ++ show e Right zA' -> do r <- saveAccount pool zA' case r of Nothing -> - return $ s & msg .~ ("Account already exists: " ++ T.unpack n) + return $ s & msg .~ "Account already exists: " ++ T.unpack n Just x -> do aL <- runNoLoggingT $ getAccounts pool (entityKey selWallet) let nL = L.listMoveToElement x $ L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts) return $ - (s & accounts .~ nL) & msg .~ "Created new account: " ++ T.unpack n + s & accounts .~ nL & msg .~ "Created new account: " ++ T.unpack n refreshAccount :: State -> IO State refreshAccount s = do @@ -1237,6 +1512,20 @@ refreshTxs s = do let tL' = L.listReplace (Vec.fromList tList) (Just 0) (s ^. transactions) 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 + 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 n scope s = do pool <- runNoLoggingT $ initPool $ s ^. dbPath @@ -1254,19 +1543,19 @@ addNewAddress n scope s = do try $ createWalletAddress n (maxAddr + 1) (s ^. network) scope selAccount :: IO (Either IOError WalletAddress) case uA of - Left e -> return $ s & msg .~ ("Error: " ++ show e) + Left e -> return $ s & msg .~ "Error: " ++ show e Right uA' -> do nAddr <- saveAddress pool uA' case nAddr of Nothing -> - return $ s & msg .~ ("Address already exists: " ++ T.unpack n) + return $ s & msg .~ "Address already exists: " ++ T.unpack n Just x -> do addrL <- runNoLoggingT $ getAddresses pool (entityKey selAccount) let nL = L.listMoveToElement x $ L.listReplace (Vec.fromList addrL) (Just 0) (s ^. addresses) return $ - (s & addresses .~ nL) & msg .~ "Created new address: " ++ + s & addresses .~ nL & msg .~ "Created new address: " ++ T.unpack n ++ "(" ++ T.unpack (showAddress $ walletAddressUAddress $ entityVal x) ++ ")" diff --git a/src/Zenith/Core.hs b/src/Zenith/Core.hs index a8dc6f2..abfb476 100644 --- a/src/Zenith/Core.hs +++ b/src/Zenith/Core.hs @@ -24,7 +24,7 @@ import Data.Binary.Get hiding (getBytes) import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as LBS import Data.Digest.Pure.MD5 -import Data.HexString (HexString, hexString, toBytes) +import Data.HexString (HexString, hexString, toBytes, toText) import Data.List import Data.Maybe (fromJust) import Data.Pool (Pool) @@ -574,6 +574,7 @@ prepareTx pool zebraHost zebraPort zn za bh amt ua memo = do zn (bh + 3) True + logDebugN $ T.pack $ show tx return tx where makeOutgoing :: diff --git a/src/Zenith/DB.hs b/src/Zenith/DB.hs index a48151d..8f9eef1 100644 --- a/src/Zenith/DB.hs +++ b/src/Zenith/DB.hs @@ -246,6 +246,12 @@ share position Int UniqueSSPos tx position deriving Show Eq + AddressBook + network ZcashNetDB + abdescrip T.Text + abaddress T.Text + UniqueABA abaddress + deriving Show Eq |] -- * Database functions @@ -1467,5 +1473,56 @@ readUnifiedAddressDB :: WalletAddress -> Maybe UnifiedAddress readUnifiedAddressDB = isValidUnifiedAddress . TE.encodeUtf8 . getUA . walletAddressUAddress +-- | Get list of external zcash addresses from database +getAdrBook :: ConnectionPool -> ZcashNet -> IO [Entity AddressBook] +getAdrBook pool n = + runNoLoggingT $ + PS.retryOnBusy $ + flip PS.runSqlPool pool $ do + select $ do + adrbook <- from $ table @AddressBook + where_ (adrbook ^. AddressBookNetwork ==. val (ZcashNetDB n)) + pure adrbook + +-- | Save a new address into AddressBook +saveAdrsInAdrBook :: + ConnectionPool -- ^ The database path to use + -> AddressBook -- ^ The address to add to the database + -> IO (Maybe (Entity AddressBook)) +saveAdrsInAdrBook pool a = + runNoLoggingT $ + PS.retryOnBusy $ flip PS.runSqlPool pool $ insertUniqueEntity a + +-- | Update an existing address into AddressBook +updateAdrsInAdrBook :: ConnectionPool -> T.Text -> T.Text -> T.Text -> IO () +updateAdrsInAdrBook pool d a ia = do + runNoLoggingT $ + PS.retryOnBusy $ + flip PS.runSqlPool pool $ do + update $ \ab -> do + set ab [AddressBookAbdescrip =. val d, AddressBookAbaddress =. val a] + where_ $ ab ^. AddressBookAbaddress ==. val ia + +-- | Get one AddrssBook record using the Address as a key +-- getABookRec :: ConnectionPool -> T.Tex t -> IO (Maybe (Entity AddressBook)) +-- getABookRec pool a = do +-- runNoLoggingT $ +-- PS.retryOnBusy $ +-- flip PS.runSqlPool pool $ +-- select $ do +-- adrbook <- from $ table @AddressBook +-- where_ ((adrbook ^. AddressBookAbaddress) ==. val a) +-- return adrbook + +-- | delete an existing address from AddressBook +deleteAdrsFromAB :: ConnectionPool -> T.Text -> IO () +deleteAdrsFromAB pool ia = do + runNoLoggingT $ + PS.retryOnBusy $ + flip PS.runSqlPool pool $ do + delete $ do + ab <- from $ table @AddressBook + where_ (ab ^. AddressBookAbaddress ==. val ia) + rmdups :: Ord a => [a] -> [a] rmdups = map head . group . sort diff --git a/src/Zenith/Utils.hs b/src/Zenith/Utils.hs index 96ca8dd..0f73fc9 100644 --- a/src/Zenith/Utils.hs +++ b/src/Zenith/Utils.hs @@ -26,18 +26,18 @@ jsonNumber i = Number $ scientific (fromIntegral i) 0 -- | Helper function to display small amounts of ZEC displayZec :: Integer -> String displayZec s - | abs s < 100 = show s ++ " zats " - | abs s < 100000 = show (fromIntegral s / 100) ++ " μZEC " - | abs s < 100000000 = show (fromIntegral s / 100000) ++ " mZEC " + | abs s < 100 = show s ++ " zats" + | abs s < 100000 = show (fromIntegral s / 100) ++ " μZEC" + | abs s < 100000000 = show (fromIntegral s / 100000) ++ " mZEC" | otherwise = show (fromIntegral s / 100000000) ++ " ZEC " -- | Helper function to display small amounts of ZEC displayTaz :: Integer -> String displayTaz s - | abs s < 100 = show s ++ " tazs " - | abs s < 100000 = show (fromIntegral s / 100) ++ " μTAZ " - | abs s < 100000000 = show (fromIntegral s / 100000) ++ " mTAZ " - | otherwise = show (fromIntegral s / 100000000) ++ " TAZ " + | abs s < 100 = show s ++ " tazs" + | abs s < 100000 = show (fromIntegral s / 100) ++ " μTAZ" + | abs s < 100000000 = show (fromIntegral s / 100000) ++ " mTAZ" + | otherwise = show (fromIntegral s / 100000000) ++ " TAZ" -- | Helper function to display abbreviated Unified Address showAddress :: UnifiedAddressDB -> T.Text diff --git a/zenith_er.bmp b/zenith_er.bmp new file mode 100644 index 0000000..d248b8f Binary files /dev/null and b/zenith_er.bmp differ diff --git a/zenith_er.png b/zenith_er.png new file mode 100644 index 0000000..5d6d21c Binary files /dev/null and b/zenith_er.png differ