Compare commits

..

No commits in common. "6f22f7c781eb0a7a64b3257672e7bfe172c4a5c9" and "3057db9aef945b40d37efb889daadf5fbf2f9957" have entirely different histories.

3 changed files with 25 additions and 98 deletions

View file

@ -3,7 +3,6 @@
module Zenith.CLI where module Zenith.CLI where
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 qualified Data.Text as T import qualified Data.Text as T
@ -61,7 +60,6 @@ import Zenith.DB
data Name data Name
= WList = WList
| AList | AList
| AcList
| TList | TList
| HelpDialog | HelpDialog
| DialogInputField | DialogInputField
@ -81,7 +79,6 @@ data DialogType
data State = State data State = State
{ _network :: !String { _network :: !String
, _wallets :: !(L.List Name (Entity ZcashWallet)) , _wallets :: !(L.List Name (Entity ZcashWallet))
, _accounts :: !(L.List Name (Entity ZcashAccount))
, _addresses :: !(L.List Name String) , _addresses :: !(L.List Name String)
, _transactions :: !(L.List Name String) , _transactions :: !(L.List Name String)
, _msg :: !String , _msg :: !String
@ -113,15 +110,7 @@ drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
"(None)" "(None)"
(\(_, w) -> zcashWalletName $ entityVal w) (\(_, w) -> zcashWalletName $ entityVal w)
(L.listSelectedElement (st ^. wallets))))) $ (L.listSelectedElement (st ^. wallets))))) $
(C.hCenter (C.center (listBox "Addresses" (st ^. addresses)) <+>
(str
("Account: " ++
T.unpack
(maybe
"(None)"
(\(_, a) -> zcashAccountName $ entityVal a)
(L.listSelectedElement (st ^. accounts))))) <=>
listBox "Addresses" (st ^. addresses) <+>
B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) <=> B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) <=>
msgBox (st ^. msg) msgBox (st ^. msg)
listBox :: String -> L.List Name String -> Widget Name listBox :: String -> L.List Name String -> Widget Name
@ -223,22 +212,19 @@ appEvent (BT.VtyEvent e) = do
V.EvKey V.KEnter [] -> do V.EvKey V.KEnter [] -> do
fs <- BT.zoom inputForm $ BT.gets formState fs <- BT.zoom inputForm $ BT.gets formState
nw <- liftIO $ addNewWallet (fs ^. dialogInput) s nw <- liftIO $ addNewWallet (fs ^. dialogInput) s
BT.put nw BT.modify $ set wallets nw
aL <- use accounts printMsg $
BT.modify $ "Creating new wallet " <> T.unpack (fs ^. dialogInput)
set dialogBox $ BT.modify $ set dialogBox Blank
if not (null $ L.listElements aL)
then Blank
else AName
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev) ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
AName -> do AName -> do
case e of case e of
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
V.EvKey V.KEnter [] -> do V.EvKey V.KEnter [] -> do
fs <- BT.zoom inputForm $ BT.gets formState
na <- liftIO $ addNewAccount (fs ^. dialogInput) s
BT.put na
BT.modify $ set dialogBox Blank BT.modify $ set dialogBox Blank
fs <- BT.zoom inputForm $ BT.gets formState
printMsg $
"Creating new address " <> T.unpack (fs ^. dialogInput)
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev) ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
Blank -> do Blank -> do
case e of case e of
@ -302,17 +288,12 @@ runZenithCLI host port dbFilePath = do
Just chainInfo -> do Just chainInfo -> do
initDb dbFilePath initDb dbFilePath
walList <- getWallets dbFilePath $ zgb_net chainInfo walList <- getWallets dbFilePath $ zgb_net chainInfo
accList <-
if not (null walList)
then getAccounts dbFilePath $ entityKey $ head walList
else return []
void $ void $
M.defaultMain theApp $ M.defaultMain theApp $
State State
((show . 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 AList (Vec.fromList ["addr1", "addr2"]) 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 ++ ".")
@ -330,49 +311,12 @@ runZenithCLI host port dbFilePath = do
"No Zebra node available on port " <> "No Zebra node available on port " <>
show port <> ". Check your configuration" show port <> ". Check your configuration"
addNewWallet :: T.Text -> State -> IO State addNewWallet ::
T.Text -> State -> IO (L.GenericList Name Vec.Vector (Entity ZcashWallet))
addNewWallet n s = do addNewWallet n s = do
sP <- generateWalletSeedPhrase sP <- generateWalletSeedPhrase
let bH = s ^. startBlock let bH = s ^. startBlock
let netName = read $ s ^. network let netName = read $ s ^. network
r <- saveWallet (s ^. dbPath) $ ZcashWallet n netName sP bH _ <- saveWallet (s ^. dbPath) $ ZcashWallet sP bH n netName
case r of
Nothing -> do
return $ s & msg .~ ("Wallet already exists: " ++ T.unpack n)
Just _ -> do
wL <- getWallets (s ^. dbPath) netName wL <- getWallets (s ^. dbPath) netName
let aL = return $ L.listReplace (Vec.fromList wL) (Just 0) $ s ^. wallets
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
addNewAccount :: T.Text -> State -> IO State
addNewAccount n 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' <- getMaxAccount (s ^. dbPath) (entityKey selWallet)
r <-
saveAccount (s ^. dbPath) $
ZcashAccount
(aL' + 1)
(entityKey selWallet)
n
"fakeOrchKey"
"fakeSapKey"
"fakeTKey"
case r of
Nothing -> return $ s & msg .~ ("Account already exists: " ++ T.unpack n)
Just x -> do
aL <- getAccounts (s ^. dbPath) (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

View file

@ -24,8 +24,8 @@ initDb dbName = do
saveWallet :: saveWallet ::
T.Text -- ^ The database path to use T.Text -- ^ The database path to use
-> ZcashWallet -- ^ The wallet to add to the database -> ZcashWallet -- ^ The wallet to add to the database
-> IO (Maybe (Entity ZcashWallet)) -> IO ZcashWalletId
saveWallet dbFp w = runSqlite dbFp $ insertUniqueEntity w saveWallet dbFp w = runSqlite dbFp $ insert w
-- | Returns a list of accounts associated with the given wallet -- | Returns a list of accounts associated with the given wallet
getAccounts :: getAccounts ::
@ -34,25 +34,12 @@ getAccounts ::
-> IO [Entity ZcashAccount] -> IO [Entity ZcashAccount]
getAccounts dbFp w = runSqlite dbFp $ selectList [ZcashAccountWalletId ==. w] [] 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 -- | Save a new account to the database
saveAccount :: saveAccount ::
T.Text -- ^ The database path T.Text -- ^ The database path
-> ZcashAccount -- ^ The account to add to the database -> ZcashAccount -- ^ The account to add to the database
-> IO (Maybe (Entity ZcashAccount)) -> IO ZcashAccountId
saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a saveAccount dbFp a = runSqlite dbFp $ insert a
-- | Returns a list of addresses associated with the given account -- | Returns a list of addresses associated with the given account
getAddresses :: getAddresses ::

View file

@ -8,7 +8,6 @@
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
@ -31,21 +30,18 @@ share
[mkPersist sqlSettings, mkMigrate "migrateAll"] [mkPersist sqlSettings, mkMigrate "migrateAll"]
[persistLowerCase| [persistLowerCase|
ZcashWallet ZcashWallet
name T.Text
network ZcashNet
seedPhrase Phrase seedPhrase Phrase
birthdayHeight Int birthdayHeight Int
UniqueWallet name network
deriving Show Eq
ZcashAccount
index Int
walletId ZcashWalletId
name T.Text name T.Text
network ZcashNet
deriving Show
ZcashAccount
walletId ZcashWalletId
index Int
orchSpendKey BS.ByteString orchSpendKey BS.ByteString
sapSpendKey BS.ByteString sapSpendKey BS.ByteString
tPrivateKey BS.ByteString tPrivateKey BS.ByteString
UniqueAccount index walletId deriving Show
deriving Show Eq
WalletAddress WalletAddress
accId ZcashAccountId accId ZcashAccountId
index Int index Int
@ -53,7 +49,7 @@ share
sapRec BS.ByteString Maybe sapRec BS.ByteString Maybe
tRec BS.ByteString Maybe tRec BS.ByteString Maybe
encoded T.Text encoded T.Text
deriving Show Eq deriving Show
|] |]
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet] getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]