Add wallet creation logic
This commit is contained in:
parent
c5a23d827c
commit
bb05d269ac
3 changed files with 71 additions and 23 deletions
|
@ -4,6 +4,7 @@
|
|||
module Zenith.CLI where
|
||||
|
||||
import Control.Monad (void)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import qualified Data.Text as T
|
||||
import qualified Graphics.Vty as V
|
||||
import Lens.Micro ((&), (.~), (^.), set)
|
||||
|
@ -41,6 +42,7 @@ import Brick.Widgets.Core
|
|||
, padBottom
|
||||
, padRight
|
||||
, str
|
||||
, txt
|
||||
, vBox
|
||||
, vLimit
|
||||
, withAttr
|
||||
|
@ -50,7 +52,7 @@ import qualified Brick.Widgets.Dialog as D
|
|||
import qualified Brick.Widgets.List as L
|
||||
import qualified Data.Vector as Vec
|
||||
import Database.Persist
|
||||
import Network.HTTP.Simple
|
||||
import ZcashHaskell.Keys (generateWalletSeedPhrase)
|
||||
import ZcashHaskell.Types
|
||||
import Zenith.Core
|
||||
import Zenith.DB
|
||||
|
@ -85,6 +87,8 @@ data State = State
|
|||
, _splashBox :: !Bool
|
||||
, _inputForm :: !(Form DialogInput () Name)
|
||||
, _focusRing :: !(F.FocusRing Name)
|
||||
, _startBlock :: !Int
|
||||
, _dbPath :: !T.Text
|
||||
}
|
||||
|
||||
makeLenses ''State
|
||||
|
@ -96,7 +100,16 @@ drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
|
|||
ui st =
|
||||
joinBorders $
|
||||
withBorderStyle unicode $
|
||||
B.borderWithLabel (str $ "Zenith - " <> st ^. network) $
|
||||
B.borderWithLabel
|
||||
(str
|
||||
("Zenith - " <>
|
||||
st ^. network <>
|
||||
" - " <>
|
||||
T.unpack
|
||||
(maybe
|
||||
"(None)"
|
||||
(\(_, w) -> zcashWalletName $ entityVal w)
|
||||
(L.listSelectedElement (st ^. wallets))))) $
|
||||
(C.center (listBox "Addresses" (st ^. addresses)) <+>
|
||||
B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) <=>
|
||||
msgBox (st ^. msg)
|
||||
|
@ -150,7 +163,7 @@ drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
|
|||
titleAttr
|
||||
(str
|
||||
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=>
|
||||
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.1")) <=>
|
||||
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.3.0")) <=>
|
||||
C.hCenter (withAttr blinkAttr $ str "Press any key..."))
|
||||
else emptyWidget
|
||||
|
||||
|
@ -197,10 +210,12 @@ appEvent (BT.VtyEvent e) = do
|
|||
case e of
|
||||
V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
|
||||
V.EvKey V.KEnter [] -> do
|
||||
BT.modify $ set dialogBox Blank
|
||||
fs <- BT.zoom inputForm $ BT.gets formState
|
||||
nw <- liftIO $ addNewWallet (fs ^. dialogInput) s
|
||||
BT.modify $ set wallets nw
|
||||
printMsg $
|
||||
"Creating new wallet " <> T.unpack (fs ^. dialogInput)
|
||||
BT.modify $ set dialogBox Blank
|
||||
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
|
||||
AName -> do
|
||||
case e of
|
||||
|
@ -271,6 +286,7 @@ runZenithCLI host port dbFilePath = do
|
|||
case (bc :: Maybe ZebraGetBlockChainInfo) of
|
||||
Nothing -> print "Unable to determine blockchain status"
|
||||
Just chainInfo -> do
|
||||
initDb dbFilePath
|
||||
walList <- getWallets dbFilePath $ zgb_net chainInfo
|
||||
void $
|
||||
M.defaultMain theApp $
|
||||
|
@ -288,7 +304,19 @@ runZenithCLI host port dbFilePath = do
|
|||
True
|
||||
(mkInputForm $ DialogInput "Main")
|
||||
(F.focusRing [AList, TList])
|
||||
(zgb_blocks chainInfo)
|
||||
dbFilePath
|
||||
Nothing -> do
|
||||
print $
|
||||
"No Zebra node available on port " <>
|
||||
show port <> ". Check your configuration"
|
||||
|
||||
addNewWallet ::
|
||||
T.Text -> State -> IO (L.GenericList Name Vec.Vector (Entity ZcashWallet))
|
||||
addNewWallet n s = do
|
||||
sP <- generateWalletSeedPhrase
|
||||
let bH = s ^. startBlock
|
||||
let netName = read $ s ^. network
|
||||
_ <- saveWallet (s ^. dbPath) $ ZcashWallet sP bH n netName
|
||||
wL <- getWallets (s ^. dbPath) netName
|
||||
return $ L.listReplace (Vec.fromList wL) (Just 0) $ s ^. wallets
|
||||
|
|
|
@ -13,14 +13,40 @@ import ZcashHaskell.Utils
|
|||
import Zenith.DB
|
||||
|
||||
-- * Database functions
|
||||
-- | Returns the list of wallets available in the given database
|
||||
checkWallets ::
|
||||
T.Text -- ^ The database name to check
|
||||
-> ZcashNet -- ^ The network the wallet is running
|
||||
-> IO [Entity ZcashWallet]
|
||||
checkWallets dbName znet = do
|
||||
-- | Initializes the database
|
||||
initDb ::
|
||||
T.Text -- ^ The database path to check
|
||||
-> IO ()
|
||||
initDb dbName = do
|
||||
runSqlite dbName $ do runMigration migrateAll
|
||||
runSqlite dbName $ selectList [ZcashWalletNetwork ==. znet] []
|
||||
|
||||
-- | Save a new wallet to the database
|
||||
saveWallet ::
|
||||
T.Text -- ^ The database path to use
|
||||
-> ZcashWallet -- ^ The wallet to add to the database
|
||||
-> IO ZcashWalletId
|
||||
saveWallet dbFp w = runSqlite dbFp $ insert 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] []
|
||||
|
||||
-- | Save a new account to the database
|
||||
saveAccount ::
|
||||
T.Text -- ^ The database path
|
||||
-> ZcashAccount -- ^ The account to add to the database
|
||||
-> IO ZcashAccountId
|
||||
saveAccount dbFp a = runSqlite dbFp $ insert 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
|
||||
-- | Checks the status of the `zebrad` node
|
||||
|
@ -28,8 +54,8 @@ checkZebra ::
|
|||
T.Text -- ^ Host where `zebrad` is available
|
||||
-> Int -- ^ Port where `zebrad` is available
|
||||
-> IO (Maybe ZebraGetInfo)
|
||||
checkZebra host port = do
|
||||
res <- makeZebraCall host port "getinfo" []
|
||||
checkZebra nodeHost nodePort = do
|
||||
res <- makeZebraCall nodeHost nodePort "getinfo" []
|
||||
let body = responseBody (res :: Response (RpcResponse ZebraGetInfo))
|
||||
return $ result body
|
||||
|
||||
|
@ -38,14 +64,14 @@ checkBlockChain ::
|
|||
T.Text -- ^ Host where `zebrad` is available
|
||||
-> Int -- ^ Port where `zebrad` is available
|
||||
-> IO (Maybe ZebraGetBlockChainInfo)
|
||||
checkBlockChain host port = do
|
||||
let f = makeZebraCall host port
|
||||
checkBlockChain nodeHost nodePort = do
|
||||
let f = makeZebraCall nodeHost nodePort
|
||||
result <$> (responseBody <$> f "getblockchaininfo" [])
|
||||
|
||||
-- | Generic RPC call function
|
||||
connectZebra ::
|
||||
FromJSON a => T.Text -> Int -> T.Text -> [Data.Aeson.Value] -> IO (Maybe a)
|
||||
connectZebra host port m params = do
|
||||
res <- makeZebraCall host port m params
|
||||
connectZebra nodeHost nodePort m params = do
|
||||
res <- makeZebraCall nodeHost nodePort m params
|
||||
let body = responseBody res
|
||||
return $ result body
|
||||
|
|
|
@ -57,9 +57,3 @@ getWallets dbFp n =
|
|||
runSqlite dbFp $ do
|
||||
s <- selectList [ZcashWalletNetwork ==. n] []
|
||||
liftIO $ return s
|
||||
|
||||
getAccounts :: T.Text -> ZcashWalletId -> IO [Entity ZcashAccount]
|
||||
getAccounts dbFp w =
|
||||
runSqlite dbFp $ do
|
||||
s <- selectList [ZcashAccountWalletId ==. w] []
|
||||
liftIO $ return s
|
||||
|
|
Loading…
Reference in a new issue