Compare commits

..

No commits in common. "856ade051e5e62c609a707874c7897231dd96c10" and "cb63b786e824bdcbecbd87be12a06a5ba878b2d9" have entirely different histories.

5 changed files with 154 additions and 463 deletions

View file

@ -3,10 +3,9 @@
module Zenith.CLI where module Zenith.CLI where
import Control.Exception (throw, try) import Control.Exception (throw)
import Control.Monad (void) import Control.Monad (void)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Data.Maybe
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)
@ -44,9 +43,7 @@ import Brick.Widgets.Core
, padBottom , padBottom
, padRight , padRight
, str , str
, strWrap
, txt , txt
, txtWrap
, vBox , vBox
, vLimit , vLimit
, withAttr , withAttr
@ -56,12 +53,10 @@ import qualified Brick.Widgets.Dialog as D
import qualified Brick.Widgets.List as L import qualified Brick.Widgets.List as L
import qualified Data.Vector as Vec import qualified Data.Vector as Vec
import Database.Persist import Database.Persist
import ZcashHaskell.Keys (generateWalletSeedPhrase, getWalletSeed) import ZcashHaskell.Keys (generateWalletSeedPhrase)
import ZcashHaskell.Orchard (encodeUnifiedAddress, genOrchardSpendingKey)
import ZcashHaskell.Types import ZcashHaskell.Types
import Zenith.Core import Zenith.Core
import Zenith.DB import Zenith.DB
import Zenith.Utils (showAddress)
data Name data Name
= WList = WList
@ -81,21 +76,13 @@ makeLenses ''DialogInput
data DialogType data DialogType
= WName = WName
| AName | AName
| AdName
| WSelect
| ASelect
| Blank | Blank
data DisplayType
= AddrDisplay
| MsgDisplay
| BlankDisplay
data State = State data State = State
{ _network :: !ZcashNet { _network :: !String
, _wallets :: !(L.List Name (Entity ZcashWallet)) , _wallets :: !(L.List Name (Entity ZcashWallet))
, _accounts :: !(L.List Name (Entity ZcashAccount)) , _accounts :: !(L.List Name (Entity ZcashAccount))
, _addresses :: !(L.List Name (Entity WalletAddress)) , _addresses :: !(L.List Name String)
, _transactions :: !(L.List Name String) , _transactions :: !(L.List Name String)
, _msg :: !String , _msg :: !String
, _helpBox :: !Bool , _helpBox :: !Bool
@ -105,13 +92,12 @@ data State = State
, _focusRing :: !(F.FocusRing Name) , _focusRing :: !(F.FocusRing Name)
, _startBlock :: !Int , _startBlock :: !Int
, _dbPath :: !T.Text , _dbPath :: !T.Text
, _displayBox :: !DisplayType
} }
makeLenses ''State makeLenses ''State
drawUI :: State -> [Widget Name] drawUI :: State -> [Widget Name]
drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s] drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
where where
ui :: State -> Widget Name ui :: State -> Widget Name
ui st = ui st =
@ -120,24 +106,25 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
B.borderWithLabel B.borderWithLabel
(str (str
("Zenith - " <> ("Zenith - " <>
show (st ^. network) <> 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: " ++
T.unpack T.unpack
(maybe (maybe
"(None)" "(None)"
(\(_, a) -> zcashAccountName $ entityVal a) (\(_, a) -> zcashAccountName $ entityVal a)
(L.listSelectedElement (st ^. accounts))))) <=> (L.listSelectedElement (st ^. accounts))))) <=>
listAddressBox "Addresses" (st ^. addresses) <+> listBox "Addresses" (st ^. addresses) <+>
B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) <=>
listBox :: Show e => String -> L.List Name e -> Widget Name msgBox (st ^. msg)
listBox :: String -> L.List Name String -> Widget Name
listBox titleLabel l = listBox titleLabel l =
C.vCenter $ C.vCenter $
vBox vBox
@ -147,31 +134,10 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
, str " " , str " "
, C.hCenter $ str "Select " , C.hCenter $ str "Select "
] ]
selectListBox :: msgBox :: String -> Widget Name
Show e msgBox m =
=> String
-> L.List Name e
-> (Bool -> e -> Widget Name)
-> Widget Name
selectListBox titleLabel l drawF =
vBox vBox
[ C.hCenter [B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m]
(B.borderWithLabel (str titleLabel) $
hLimit 25 $ vLimit 15 $ L.renderList drawF True l)
, str " "
, C.hCenter $ str "Select "
]
listAddressBox ::
String -> L.List Name (Entity WalletAddress) -> Widget Name
listAddressBox titleLabel a =
C.vCenter $
vBox
[ C.hCenter
(B.borderWithLabel (str titleLabel) $
hLimit 40 $ vLimit 15 $ L.renderList listDrawAddress True a)
, str " "
, C.hCenter $ str "Use arrows to select"
]
helpDialog :: State -> Widget Name helpDialog :: State -> Widget Name
helpDialog st = helpDialog st =
if st ^. helpBox if st ^. helpBox
@ -181,17 +147,11 @@ 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", "q"] keyList = map (C.hCenter . str) ["?", "Esc", "c", "q"]
actionList = actionList =
map map
(hLimit 40 . str) (hLimit 40 . str)
[ "Open help" ["Open help", "Close dialog", "Create Wallet", "Quit"]
, "Close dialog"
, "Switch wallets"
, "Switch accounts"
, "View address"
, "Quit"
]
inputDialog :: State -> Widget Name inputDialog :: State -> Widget Name
inputDialog st = inputDialog st =
case st ^. dialogBox of case st ^. dialogBox of
@ -203,18 +163,6 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
D.renderDialog D.renderDialog
(D.dialog (Just (str "Create Account")) Nothing 50) (D.dialog (Just (str "Create Account")) Nothing 50)
(renderForm $ st ^. inputForm) (renderForm $ st ^. inputForm)
AdName ->
D.renderDialog
(D.dialog (Just (str "Create Address")) Nothing 50)
(renderForm $ st ^. inputForm)
WSelect ->
D.renderDialog
(D.dialog (Just (str "Select Wallet")) Nothing 50)
(selectListBox "Wallets" (st ^. wallets) listDrawWallet)
ASelect ->
D.renderDialog
(D.dialog (Just (str "Select Account")) Nothing 50)
(selectListBox "Accounts" (st ^. accounts) listDrawAccount)
Blank -> emptyWidget Blank -> emptyWidget
splashDialog :: State -> Widget Name splashDialog :: State -> Widget Name
splashDialog st = splashDialog st =
@ -229,28 +177,6 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.3.0")) <=> C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.3.0")) <=>
C.hCenter (withAttr blinkAttr $ str "Press any key...")) C.hCenter (withAttr blinkAttr $ str "Press any key..."))
else emptyWidget else emptyWidget
displayDialog :: State -> Widget Name
displayDialog st =
case st ^. displayBox of
AddrDisplay ->
case L.listSelectedElement $ st ^. addresses of
Just (_, a) ->
withBorderStyle unicodeBold $
D.renderDialog
(D.dialog
(Just $ txt ("Address: " <> walletAddressName (entityVal a)))
Nothing
60)
(padAll 1 $
txtWrap $
encodeUnifiedAddress $ walletAddressUAddress $ entityVal a)
Nothing -> emptyWidget
MsgDisplay ->
withBorderStyle unicodeBold $
D.renderDialog
(D.dialog (Just $ txt "Message") Nothing 50)
(padAll 1 $ strWrap $ st ^. msg)
BlankDisplay -> emptyWidget
mkInputForm :: DialogInput -> Form DialogInput e Name mkInputForm :: DialogInput -> Form DialogInput e Name
mkInputForm = mkInputForm =
@ -268,33 +194,6 @@ listDrawElement sel a =
else str s else str s
in C.hCenter $ selStr $ show a in C.hCenter $ selStr $ show a
listDrawWallet :: Bool -> Entity ZcashWallet -> Widget Name
listDrawWallet sel w =
let selStr s =
if sel
then withAttr customAttr (txt $ "<" <> s <> ">")
else txt s
in C.hCenter $ selStr $ zcashWalletName (entityVal w)
listDrawAccount :: Bool -> Entity ZcashAccount -> Widget Name
listDrawAccount sel w =
let selStr s =
if sel
then withAttr customAttr (txt $ "<" <> s <> ">")
else txt s
in C.hCenter $ selStr $ zcashAccountName (entityVal w)
listDrawAddress :: Bool -> Entity WalletAddress -> Widget Name
listDrawAddress sel w =
let selStr s =
if sel
then withAttr customAttr (txt $ "<" <> s <> ">")
else txt s
in C.hCenter $
selStr $
walletAddressName (entityVal w) <>
": " <> showAddress (walletAddressUAddress (entityVal w))
customAttr :: A.AttrName customAttr :: A.AttrName
customAttr = L.listSelectedAttr <> A.attrName "custom" customAttr = L.listSelectedAttr <> A.attrName "custom"
@ -317,104 +216,52 @@ appEvent (BT.VtyEvent e) = do
BT.modify $ set helpBox False BT.modify $ set helpBox False
_ev -> return () _ev -> return ()
else do else do
case s ^. displayBox of case s ^. dialogBox of
AddrDisplay -> BT.modify $ set displayBox BlankDisplay WName -> do
MsgDisplay -> BT.modify $ set displayBox BlankDisplay case e of
BlankDisplay -> do V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
case s ^. dialogBox of V.EvKey V.KEnter [] -> do
WName -> do fs <- BT.zoom inputForm $ BT.gets formState
case e of nw <- liftIO $ addNewWallet (fs ^. dialogInput) s
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank BT.put nw
V.EvKey V.KEnter [] -> do aL <- use accounts
fs <- BT.zoom inputForm $ BT.gets formState BT.modify $
nw <- liftIO $ addNewWallet (fs ^. dialogInput) s set dialogBox $
ns <- liftIO $ refreshWallet nw if not (null $ L.listElements aL)
BT.put ns then Blank
aL <- use accounts else AName
BT.modify $ set displayBox MsgDisplay ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
BT.modify $ AName -> do
set dialogBox $ case e of
if not (null $ L.listElements aL) V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
then Blank V.EvKey V.KEnter [] -> do
else AName fs <- BT.zoom inputForm $ BT.gets formState
ev -> na <- liftIO $ addNewAccount (fs ^. dialogInput) s
BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev) BT.put na
AName -> do BT.modify $ set dialogBox Blank
case e of ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank Blank -> do
V.EvKey V.KEnter [] -> do case e of
fs <- BT.zoom inputForm $ BT.gets formState V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
na <- liftIO $ addNewAccount (fs ^. dialogInput) s V.EvKey (V.KChar 'q') [] -> M.halt
ns <- liftIO $ refreshAccount na V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True
BT.put ns V.EvKey (V.KChar 'w') [] -> do
addrL <- use addresses BT.modify $
BT.modify $ set displayBox MsgDisplay set inputForm $
BT.modify $ updateFormState (DialogInput "New Wallet") $
set dialogBox $ s ^. inputForm
if not (null $ L.listElements addrL) BT.modify $ set dialogBox WName
then Blank V.EvKey (V.KChar 'a') [] -> do
else AdName BT.modify $
ev -> set inputForm $
BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev) updateFormState (DialogInput "New Account") $
AdName -> do s ^. inputForm
case e of BT.modify $ set dialogBox AName
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank ev ->
V.EvKey V.KEnter [] -> do case r of
fs <- BT.zoom inputForm $ BT.gets formState Just AList -> BT.zoom addresses $ L.handleListEvent ev
nAddr <- liftIO $ addNewAddress (fs ^. dialogInput) s Just TList -> BT.zoom transactions $ L.handleListEvent ev
BT.put nAddr _anyName -> return ()
BT.modify $ set displayBox MsgDisplay
BT.modify $ set dialogBox Blank
ev ->
BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
WSelect -> do
case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
V.EvKey V.KEnter [] -> do
ns <- liftIO $ refreshWallet s
BT.put ns
BT.modify $ set dialogBox Blank
V.EvKey (V.KChar 'c') [] -> do
BT.modify $
set inputForm $
updateFormState (DialogInput "New Wallet") $
s ^. inputForm
BT.modify $ set dialogBox WName
ev -> BT.zoom wallets $ L.handleListEvent ev
ASelect -> do
case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
V.EvKey V.KEnter [] -> do
ns <- liftIO $ refreshAccount s
BT.put ns
BT.modify $ set dialogBox Blank
V.EvKey (V.KChar 'c') [] -> do
BT.modify $
set inputForm $
updateFormState (DialogInput "New Account") $
s ^. inputForm
BT.modify $ set dialogBox AName
ev -> BT.zoom accounts $ L.handleListEvent ev
Blank -> do
case e of
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
V.EvKey (V.KChar 'q') [] -> M.halt
V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True
V.EvKey (V.KChar 'n') [] ->
BT.modify $ set dialogBox AdName
V.EvKey (V.KChar 'v') [] ->
BT.modify $ set displayBox AddrDisplay
V.EvKey (V.KChar 'w') [] ->
BT.modify $ set dialogBox WSelect
V.EvKey (V.KChar 'a') [] ->
BT.modify $ set dialogBox ASelect
ev ->
case r of
Just AList ->
BT.zoom addresses $ L.handleListEvent ev
Just TList ->
BT.zoom transactions $ L.handleListEvent ev
_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
@ -459,17 +306,13 @@ runZenithCLI host port dbFilePath = do
if not (null walList) if not (null walList)
then getAccounts dbFilePath $ entityKey $ head walList then getAccounts dbFilePath $ entityKey $ head walList
else return [] else return []
addrList <-
if not (null accList)
then getAddresses dbFilePath $ entityKey $ head accList
else return []
void $ void $
M.defaultMain theApp $ M.defaultMain theApp $
State State
(zgb_net chainInfo) ((show . zgb_net) chainInfo)
(L.list WList (Vec.fromList walList) 1) (L.list WList (Vec.fromList walList) 1)
(L.list AcList (Vec.fromList accList) 0) (L.list AcList (Vec.fromList accList) 0)
(L.list AList (Vec.fromList addrList) 1) (L.list AList (Vec.fromList ["utest...hn8zg", "utest...qfex8"]) 1)
(L.list TList (Vec.fromList ["tx1", "tx2", "tx3"]) 1) (L.list TList (Vec.fromList ["tx1", "tx2", "tx3"]) 1)
("Start up Ok! Connected to Zebra " ++ ("Start up Ok! Connected to Zebra " ++
(T.unpack . zgi_build) zebra ++ " on port " ++ show port ++ ".") (T.unpack . zgi_build) zebra ++ " on port " ++ show port ++ ".")
@ -482,39 +325,16 @@ runZenithCLI host port dbFilePath = do
(F.focusRing [AList, TList]) (F.focusRing [AList, TList])
(zgb_blocks chainInfo) (zgb_blocks chainInfo)
dbFilePath dbFilePath
MsgDisplay
Nothing -> do Nothing -> do
print $ print $
"No Zebra node available on port " <> "No Zebra node available on port " <>
show port <> ". Check your configuration" show port <> ". Check your configuration"
refreshWallet :: State -> IO State
refreshWallet s = do
selWallet <-
do case L.listSelectedElement $ s ^. wallets of
Nothing -> do
let fWall =
L.listSelectedElement $ L.listMoveToBeginning $ s ^. wallets
case fWall of
Nothing -> throw $ userError "Failed to select wallet"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
aL <- getAccounts (s ^. dbPath) $ entityKey selWallet
addrL <-
if not (null aL)
then getAddresses (s ^. dbPath) $ entityKey $ head aL
else return []
let aL' = L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
let addrL' = L.listReplace (Vec.fromList addrL) (Just 0) (s ^. addresses)
return $
(s & accounts .~ aL') & addresses .~ addrL' & msg .~ "Switched to wallet: " ++
T.unpack (zcashWalletName $ entityVal selWallet)
addNewWallet :: T.Text -> State -> IO State addNewWallet :: T.Text -> State -> IO State
addNewWallet n s = do addNewWallet n s = do
sP <- generateWalletSeedPhrase sP <- generateWalletSeedPhrase
let bH = s ^. startBlock let bH = s ^. startBlock
let netName = s ^. network let netName = read $ s ^. network
r <- saveWallet (s ^. dbPath) $ ZcashWallet n netName sP bH r <- saveWallet (s ^. dbPath) $ ZcashWallet n netName sP bH
case r of case r of
Nothing -> do Nothing -> do
@ -538,70 +358,21 @@ addNewAccount n s = do
Just (_j, w1) -> return w1 Just (_j, w1) -> return w1
Just (_k, w) -> return w Just (_k, w) -> return w
aL' <- getMaxAccount (s ^. dbPath) (entityKey selWallet) aL' <- getMaxAccount (s ^. dbPath) (entityKey selWallet)
zA <- r <-
try $ createZcashAccount n (aL' + 1) selWallet :: IO saveAccount (s ^. dbPath) $
(Either IOError ZcashAccount) ZcashAccount
case zA of (aL' + 1)
Left e -> return $ s & msg .~ ("Error: " ++ show e) (entityKey selWallet)
Right zA' -> do n
r <- saveAccount (s ^. dbPath) zA' "fakeOrchKey"
case r of "fakeSapKey"
Nothing -> "fakeTKey"
return $ s & msg .~ ("Account already exists: " ++ T.unpack n) case r of
Just x -> do Nothing -> return $ s & msg .~ ("Account already exists: " ++ T.unpack n)
aL <- getAccounts (s ^. dbPath) (entityKey selWallet) Just x -> do
let nL = aL <- getAccounts (s ^. dbPath) (entityKey selWallet)
L.listMoveToElement x $ let nL =
L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts) L.listMoveToElement x $
return $ L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
(s & accounts .~ nL) & msg .~ "Created new account: " ++ T.unpack n return $
(s & accounts .~ nL) & msg .~ "Created new account: " ++ T.unpack n
refreshAccount :: State -> IO State
refreshAccount s = do
selAccount <-
do case L.listSelectedElement $ s ^. accounts of
Nothing -> do
let fAcc =
L.listSelectedElement $ L.listMoveToBeginning $ s ^. accounts
case fAcc of
Nothing -> throw $ userError "Failed to select account"
Just (_j, w1) -> return w1
Just (_k, w) -> return w
aL <- getAddresses (s ^. dbPath) $ entityKey selAccount
let aL' = L.listReplace (Vec.fromList aL) (Just 0) (s ^. addresses)
return $
s & addresses .~ aL' & msg .~ "Switched to account: " ++
T.unpack (zcashAccountName $ entityVal selAccount)
addNewAddress :: T.Text -> State -> IO State
addNewAddress n s = do
selAccount <-
do case L.listSelectedElement $ s ^. accounts of
Nothing -> do
let fAcc =
L.listSelectedElement $ L.listMoveToBeginning $ s ^. accounts
case fAcc of
Nothing -> throw $ userError "Failed to select account"
Just (_j, a1) -> return a1
Just (_k, a) -> return a
maxAddr <- getMaxAddress (s ^. dbPath) (entityKey selAccount)
uA <-
try $ createWalletAddress n (maxAddr + 1) (s ^. network) selAccount :: IO
(Either IOError WalletAddress)
case uA of
Left e -> return $ s & msg .~ ("Error: " ++ show e)
Right uA' -> do
nAddr <- saveAddress (s ^. dbPath) uA'
case nAddr of
Nothing ->
return $ s & msg .~ ("Address already exists: " ++ T.unpack n)
Just x -> do
addrL <- getAddresses (s ^. dbPath) (entityKey selAccount)
let nL =
L.listMoveToElement x $
L.listReplace (Vec.fromList addrL) (Just 0) (s ^. addresses)
return $
(s & addresses .~ nL) & msg .~ "Created new address: " ++
T.unpack n ++
"(" ++
T.unpack (showAddress $ walletAddressUAddress $ entityVal x) ++ ")"

View file

@ -3,18 +3,64 @@
-- Core wallet functionality for Zenith -- Core wallet functionality for Zenith
module Zenith.Core where module Zenith.Core where
import Control.Exception (throwIO)
import Data.Aeson import Data.Aeson
import qualified Data.ByteString as BS
import qualified Data.Text as T import qualified Data.Text as T
import Database.Persist import Database.Persist
import Database.Persist.Sqlite
import Network.HTTP.Client import Network.HTTP.Client
import ZcashHaskell.Keys
import ZcashHaskell.Orchard
import ZcashHaskell.Types import ZcashHaskell.Types
import ZcashHaskell.Utils import ZcashHaskell.Utils
import Zenith.DB import Zenith.DB
-- * Database functions
-- | Initializes the database
initDb ::
T.Text -- ^ The database path to check
-> IO ()
initDb dbName = do
runSqlite dbName $ do runMigration migrateAll
-- | Save a new wallet to the database
saveWallet ::
T.Text -- ^ The database path to use
-> ZcashWallet -- ^ The wallet to add to the database
-> IO (Maybe (Entity ZcashWallet))
saveWallet dbFp w = runSqlite dbFp $ insertUniqueEntity w
-- | Returns a list of accounts associated with the given wallet
getAccounts ::
T.Text -- ^ The database path
-> ZcashWalletId -- ^ The wallet ID to check
-> IO [Entity ZcashAccount]
getAccounts dbFp w = runSqlite dbFp $ selectList [ZcashAccountWalletId ==. w] []
-- | Returns the largest account index for the given wallet
getMaxAccount ::
T.Text -- ^ The database path
-> ZcashWalletId -- ^ The wallet ID to check
-> IO Int
getMaxAccount dbFp w = do
a <-
runSqlite dbFp $
selectFirst [ZcashAccountWalletId ==. w] [Desc ZcashAccountIndex]
case a of
Nothing -> return $ -1
Just x -> return $ zcashAccountIndex $ entityVal x
-- | Save a new account to the database
saveAccount ::
T.Text -- ^ The database path
-> ZcashAccount -- ^ The account to add to the database
-> IO (Maybe (Entity ZcashAccount))
saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a
-- | Returns a list of addresses associated with the given account
getAddresses ::
T.Text -- ^ The database path
-> ZcashAccountId -- ^ The account ID to check
-> IO [Entity WalletAddress]
getAddresses dbFp a = runSqlite dbFp $ selectList [WalletAddressAccId ==. a] []
-- * Zebra Node interaction -- * Zebra Node interaction
-- | Checks the status of the `zebrad` node -- | Checks the status of the `zebrad` node
checkZebra :: checkZebra ::
@ -33,7 +79,7 @@ checkBlockChain ::
-> IO (Maybe ZebraGetBlockChainInfo) -> IO (Maybe ZebraGetBlockChainInfo)
checkBlockChain nodeHost nodePort = do checkBlockChain nodeHost nodePort = do
let f = makeZebraCall nodeHost nodePort let f = makeZebraCall nodeHost nodePort
result . responseBody <$> f "getblockchaininfo" [] result <$> (responseBody <$> f "getblockchaininfo" [])
-- | Generic RPC call function -- | Generic RPC call function
connectZebra :: connectZebra ::
@ -42,52 +88,3 @@ connectZebra nodeHost nodePort m params = do
res <- makeZebraCall nodeHost nodePort m params res <- makeZebraCall nodeHost nodePort m params
let body = responseBody res let body = responseBody res
return $ result body return $ result body
-- * Spending Keys
-- | Create an Orchard Spending Key for the given wallet and account index
createOrchardSpendingKey :: ZcashWallet -> Int -> IO BS.ByteString
createOrchardSpendingKey zw i = do
let s = getWalletSeed $ zcashWalletSeedPhrase zw
case s of
Nothing -> throwIO $ userError "Unable to generate seed"
Just s' -> do
let coinType =
case zcashWalletNetwork zw of
MainNet -> MainNetCoin
TestNet -> TestNetCoin
RegTestNet -> RegTestNetCoin
let r = genOrchardSpendingKey s' coinType i
case r of
Nothing -> throwIO $ userError "Unable to generate Orchard spending key"
Just sk -> return sk
-- * Accounts
-- | Create an account for the given wallet and account index
createZcashAccount ::
T.Text -- ^ The account's name
-> Int -- ^ The account's index
-> Entity ZcashWallet -- ^ The Zcash wallet that this account will be attached to
-> IO ZcashAccount
createZcashAccount n i zw = do
orSk <- createOrchardSpendingKey (entityVal zw) i
return $ ZcashAccount i (entityKey zw) n orSk "fakeSapKey" "fakeTkey"
-- * Addresses
-- | Create a unified address for the given account and index
createWalletAddress ::
T.Text -- ^ The address nickname
-> Int -- ^ The address' index
-> ZcashNet -- ^ The network for this address
-> Entity ZcashAccount -- ^ The Zcash account that the address will be attached to
-> IO WalletAddress
createWalletAddress n i zNet za = do
return $
WalletAddress
i
(entityKey za)
n
(UnifiedAddress
zNet
"fakeBString"
"fakeBString"
(Just $ TransparentAddress P2PKH zNet "fakeBString"))

View file

@ -23,12 +23,10 @@ import qualified Data.Text as T
import Database.Persist import Database.Persist
import Database.Persist.Sqlite import Database.Persist.Sqlite
import Database.Persist.TH import Database.Persist.TH
import ZcashHaskell.Types (Phrase, UnifiedAddress(..), ZcashNet) import ZcashHaskell.Types (Phrase, ZcashNet)
derivePersistField "ZcashNet" derivePersistField "ZcashNet"
derivePersistField "UnifiedAddress"
share share
[mkPersist sqlSettings, mkMigrate "migrateAll"] [mkPersist sqlSettings, mkMigrate "migrateAll"]
[persistLowerCase| [persistLowerCase|
@ -47,87 +45,19 @@ share
sapSpendKey BS.ByteString sapSpendKey BS.ByteString
tPrivateKey BS.ByteString tPrivateKey BS.ByteString
UniqueAccount index walletId UniqueAccount index walletId
UniqueAccName walletId name
deriving Show Eq deriving Show Eq
WalletAddress WalletAddress
index Int
accId ZcashAccountId accId ZcashAccountId
name T.Text index Int
uAddress UnifiedAddress orchRec BS.ByteString Maybe
UniqueAddress index accId sapRec BS.ByteString Maybe
UniqueAddName accId name tRec BS.ByteString Maybe
encoded T.Text
deriving Show Eq deriving Show Eq
|] |]
-- * Database functions
-- | Initializes the database
initDb ::
T.Text -- ^ The database path to check
-> IO ()
initDb dbName = do
runSqlite dbName $ do runMigration migrateAll
-- | Get existing wallets from database
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet] getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
getWallets dbFp n = runSqlite dbFp $ selectList [ZcashWalletNetwork ==. n] [] getWallets dbFp n =
runSqlite dbFp $ do
-- | Save a new wallet to the database s <- selectList [ZcashWalletNetwork ==. n] []
saveWallet :: liftIO $ return s
T.Text -- ^ The database path to use
-> ZcashWallet -- ^ The wallet to add to the database
-> IO (Maybe (Entity ZcashWallet))
saveWallet dbFp w = runSqlite dbFp $ insertUniqueEntity w
-- | Returns a list of accounts associated with the given wallet
getAccounts ::
T.Text -- ^ The database path
-> ZcashWalletId -- ^ The wallet ID to check
-> IO [Entity ZcashAccount]
getAccounts dbFp w = runSqlite dbFp $ selectList [ZcashAccountWalletId ==. w] []
-- | Returns the largest account index for the given wallet
getMaxAccount ::
T.Text -- ^ The database path
-> ZcashWalletId -- ^ The wallet ID to check
-> IO Int
getMaxAccount dbFp w = do
a <-
runSqlite dbFp $
selectFirst [ZcashAccountWalletId ==. w] [Desc ZcashAccountIndex]
case a of
Nothing -> return $ -1
Just x -> return $ zcashAccountIndex $ entityVal x
-- | Save a new account to the database
saveAccount ::
T.Text -- ^ The database path
-> ZcashAccount -- ^ The account to add to the database
-> IO (Maybe (Entity ZcashAccount))
saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a
-- | Returns a list of addresses associated with the given account
getAddresses ::
T.Text -- ^ The database path
-> ZcashAccountId -- ^ The account ID to check
-> IO [Entity WalletAddress]
getAddresses dbFp a = runSqlite dbFp $ selectList [WalletAddressAccId ==. a] []
-- | Returns the largest address index for the given account
getMaxAddress ::
T.Text -- ^ The database path
-> ZcashAccountId -- ^ The wallet ID to check
-> IO Int
getMaxAddress dbFp w = do
a <-
runSqlite dbFp $
selectFirst [WalletAddressAccId ==. w] [Desc WalletAddressIndex]
case a of
Nothing -> return $ -1
Just x -> return $ walletAddressIndex $ entityVal x
-- | Save a new address to the database
saveAddress ::
T.Text -- ^ the database path
-> WalletAddress -- ^ The wallet to add to the database
-> IO (Maybe (Entity WalletAddress))
saveAddress dbFp w = runSqlite dbFp $ insertUniqueEntity w

View file

@ -13,9 +13,8 @@ import qualified Data.Text.IO as TIO
import System.Process (createProcess_, shell) import System.Process (createProcess_, shell)
import Text.Read (readMaybe) import Text.Read (readMaybe)
import Text.Regex.Posix import Text.Regex.Posix
import ZcashHaskell.Orchard (encodeUnifiedAddress, isValidUnifiedAddress) import ZcashHaskell.Orchard (isValidUnifiedAddress)
import ZcashHaskell.Sapling (isValidShieldedAddress) import ZcashHaskell.Sapling (isValidShieldedAddress)
import ZcashHaskell.Types (UnifiedAddress(..))
import Zenith.Types import Zenith.Types
( AddressGroup(..) ( AddressGroup(..)
, AddressSource(..) , AddressSource(..)
@ -31,12 +30,6 @@ displayZec s
| s < 100000000 = show (fromIntegral s / 100000) ++ " mZEC " | s < 100000000 = show (fromIntegral s / 100000) ++ " mZEC "
| otherwise = show (fromIntegral s / 100000000) ++ " ZEC " | otherwise = show (fromIntegral s / 100000000) ++ " ZEC "
-- | Helper function to display abbreviated Unified Address
showAddress :: UnifiedAddress -> T.Text
showAddress u = T.take 20 t <> "..."
where
t = encodeUnifiedAddress u
-- | Helper function to extract addresses from AddressGroups -- | Helper function to extract addresses from AddressGroups
getAddresses :: AddressGroup -> [ZcashAddress] getAddresses :: AddressGroup -> [ZcashAddress]
getAddresses ag = agtransparent ag <> agsapling ag <> agunified ag getAddresses ag = agtransparent ag <> agsapling ag <> agunified ag

@ -1 +1 @@
Subproject commit e371fcdb724686bfb51157911c5d4c0fda433c53 Subproject commit a52d2231f1a4f85a6504bfb9228a1475a0773088