Implement display of seed phrase #69
5 changed files with 191 additions and 68 deletions
|
@ -57,6 +57,7 @@ import ZcashHaskell.Keys (generateWalletSeedPhrase)
|
||||||
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
|
||||||
|
@ -76,13 +77,14 @@ makeLenses ''DialogInput
|
||||||
data DialogType
|
data DialogType
|
||||||
= WName
|
= WName
|
||||||
| AName
|
| AName
|
||||||
|
| AdName
|
||||||
| Blank
|
| Blank
|
||||||
|
|
||||||
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))
|
, _accounts :: !(L.List Name (Entity ZcashAccount))
|
||||||
, _addresses :: !(L.List Name String)
|
, _addresses :: !(L.List Name (Entity WalletAddress))
|
||||||
, _transactions :: !(L.List Name String)
|
, _transactions :: !(L.List Name String)
|
||||||
, _msg :: !String
|
, _msg :: !String
|
||||||
, _helpBox :: !Bool
|
, _helpBox :: !Bool
|
||||||
|
@ -121,10 +123,10 @@ drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
|
||||||
"(None)"
|
"(None)"
|
||||||
(\(_, a) -> zcashAccountName $ entityVal a)
|
(\(_, a) -> zcashAccountName $ entityVal a)
|
||||||
(L.listSelectedElement (st ^. accounts))))) <=>
|
(L.listSelectedElement (st ^. accounts))))) <=>
|
||||||
listBox "Addresses" (st ^. addresses) <+>
|
listAddressBox "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 :: Show e => String -> L.List Name e -> Widget Name
|
||||||
listBox titleLabel l =
|
listBox titleLabel l =
|
||||||
C.vCenter $
|
C.vCenter $
|
||||||
vBox
|
vBox
|
||||||
|
@ -134,6 +136,17 @@ drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
|
||||||
, str " "
|
, str " "
|
||||||
, C.hCenter $ str "Select "
|
, 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"
|
||||||
|
]
|
||||||
msgBox :: String -> Widget Name
|
msgBox :: String -> Widget Name
|
||||||
msgBox m =
|
msgBox m =
|
||||||
vBox
|
vBox
|
||||||
|
@ -163,6 +176,10 @@ drawUI s = [splashDialog s, helpDialog 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)
|
||||||
Blank -> emptyWidget
|
Blank -> emptyWidget
|
||||||
splashDialog :: State -> Widget Name
|
splashDialog :: State -> Widget Name
|
||||||
splashDialog st =
|
splashDialog st =
|
||||||
|
@ -194,6 +211,33 @@ 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"
|
||||||
|
|
||||||
|
@ -238,6 +282,20 @@ appEvent (BT.VtyEvent e) = do
|
||||||
fs <- BT.zoom inputForm $ BT.gets formState
|
fs <- BT.zoom inputForm $ BT.gets formState
|
||||||
na <- liftIO $ addNewAccount (fs ^. dialogInput) s
|
na <- liftIO $ addNewAccount (fs ^. dialogInput) s
|
||||||
BT.put na
|
BT.put na
|
||||||
|
addrL <- use addresses
|
||||||
|
BT.modify $
|
||||||
|
set dialogBox $
|
||||||
|
if not (null $ L.listElements addrL)
|
||||||
|
then Blank
|
||||||
|
else AdName
|
||||||
|
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||||
|
AdName -> do
|
||||||
|
case e of
|
||||||
|
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||||
|
V.EvKey V.KEnter [] -> do
|
||||||
|
fs <- BT.zoom inputForm $ BT.gets formState
|
||||||
|
nAddr <- liftIO $ addNewAddress (fs ^. dialogInput) s
|
||||||
|
BT.put nAddr
|
||||||
BT.modify $ set dialogBox Blank
|
BT.modify $ set dialogBox Blank
|
||||||
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||||
Blank -> do
|
Blank -> do
|
||||||
|
@ -306,13 +364,17 @@ 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
|
||||||
((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 AcList (Vec.fromList accList) 0)
|
||||||
(L.list AList (Vec.fromList ["utest...hn8zg", "utest...qfex8"]) 1)
|
(L.list AList (Vec.fromList addrList) 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 ++ ".")
|
||||||
|
@ -376,3 +438,39 @@ addNewAccount n s = do
|
||||||
L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
|
L.listReplace (Vec.fromList aL) (Just 0) (s ^. accounts)
|
||||||
return $
|
return $
|
||||||
(s & accounts .~ nL) & msg .~ "Created new account: " ++ T.unpack n
|
(s & accounts .~ nL) & msg .~ "Created new account: " ++ T.unpack n
|
||||||
|
|
||||||
|
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)
|
||||||
|
nAddr <-
|
||||||
|
saveAddress (s ^. dbPath) $
|
||||||
|
WalletAddress
|
||||||
|
(maxAddr + 1)
|
||||||
|
(entityKey selAccount)
|
||||||
|
n
|
||||||
|
(UnifiedAddress
|
||||||
|
MainNet
|
||||||
|
"fakeBstring"
|
||||||
|
"fakeBString"
|
||||||
|
(Just $ TransparentAddress P2PKH MainNet "fakeBString"))
|
||||||
|
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) ++ ")"
|
||||||
|
|
|
@ -5,61 +5,9 @@ module Zenith.Core where
|
||||||
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Database.Persist
|
|
||||||
import Database.Persist.Sqlite
|
|
||||||
import Network.HTTP.Client
|
import Network.HTTP.Client
|
||||||
import ZcashHaskell.Types
|
import ZcashHaskell.Types
|
||||||
import ZcashHaskell.Utils
|
import ZcashHaskell.Utils
|
||||||
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
|
||||||
|
|
|
@ -23,10 +23,12 @@ 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, ZcashNet)
|
import ZcashHaskell.Types (Phrase, UnifiedAddress(..), ZcashNet)
|
||||||
|
|
||||||
derivePersistField "ZcashNet"
|
derivePersistField "ZcashNet"
|
||||||
|
|
||||||
|
derivePersistField "UnifiedAddress"
|
||||||
|
|
||||||
share
|
share
|
||||||
[mkPersist sqlSettings, mkMigrate "migrateAll"]
|
[mkPersist sqlSettings, mkMigrate "migrateAll"]
|
||||||
[persistLowerCase|
|
[persistLowerCase|
|
||||||
|
@ -45,19 +47,87 @@ 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
|
||||||
accId ZcashAccountId
|
|
||||||
index Int
|
index Int
|
||||||
orchRec BS.ByteString Maybe
|
accId ZcashAccountId
|
||||||
sapRec BS.ByteString Maybe
|
name T.Text
|
||||||
tRec BS.ByteString Maybe
|
uAddress UnifiedAddress
|
||||||
encoded T.Text
|
UniqueAddress index accId
|
||||||
|
UniqueAddName accId name
|
||||||
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 =
|
getWallets dbFp n = runSqlite dbFp $ selectList [ZcashWalletNetwork ==. n] []
|
||||||
runSqlite dbFp $ do
|
|
||||||
s <- selectList [ZcashWalletNetwork ==. n] []
|
-- | Save a new wallet to the database
|
||||||
liftIO $ return s
|
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] []
|
||||||
|
|
||||||
|
-- | 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
|
||||||
|
|
|
@ -13,8 +13,9 @@ 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 (isValidUnifiedAddress)
|
import ZcashHaskell.Orchard (encodeUnifiedAddress, isValidUnifiedAddress)
|
||||||
import ZcashHaskell.Sapling (isValidShieldedAddress)
|
import ZcashHaskell.Sapling (isValidShieldedAddress)
|
||||||
|
import ZcashHaskell.Types (UnifiedAddress(..))
|
||||||
import Zenith.Types
|
import Zenith.Types
|
||||||
( AddressGroup(..)
|
( AddressGroup(..)
|
||||||
, AddressSource(..)
|
, AddressSource(..)
|
||||||
|
@ -30,6 +31,12 @@ 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 8 t <> "..." <> T.takeEnd 8 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 a52d2231f1a4f85a6504bfb9228a1475a0773088
|
Subproject commit c1507f36e0146f0be76ee2a71cb2b3b4ebd9f3cf
|
Loading…
Reference in a new issue