Compare commits
No commits in common. "bb05d269acfaae50b978f638af216479921a18e2" and "488a01c46d6cfa9fcd7e81208fe8f22d86dccba4" have entirely different histories.
bb05d269ac
...
488a01c46d
6 changed files with 27 additions and 76 deletions
|
@ -36,13 +36,13 @@ Zenith is a command-line interface for the Zcash Full Node (`zcashd`). It has th
|
||||||
git clone https://git.vergara.tech/Vergara_Tech/zenith.git
|
git clone https://git.vergara.tech/Vergara_Tech/zenith.git
|
||||||
cd zenith
|
cd zenith
|
||||||
git submodule init
|
git submodule init
|
||||||
git submodule update --remote
|
git submodule update
|
||||||
```
|
```
|
||||||
|
|
||||||
- Install using `cabal`:
|
- Install using `stack`:
|
||||||
|
|
||||||
```
|
```
|
||||||
cabal install
|
stack install
|
||||||
```
|
```
|
||||||
|
|
||||||
## Configuration
|
## Configuration
|
||||||
|
|
|
@ -4,7 +4,6 @@
|
||||||
module Zenith.CLI where
|
module Zenith.CLI where
|
||||||
|
|
||||||
import Control.Monad (void)
|
import Control.Monad (void)
|
||||||
import Control.Monad.IO.Class (liftIO)
|
|
||||||
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)
|
||||||
|
@ -42,7 +41,6 @@ import Brick.Widgets.Core
|
||||||
, padBottom
|
, padBottom
|
||||||
, padRight
|
, padRight
|
||||||
, str
|
, str
|
||||||
, txt
|
|
||||||
, vBox
|
, vBox
|
||||||
, vLimit
|
, vLimit
|
||||||
, withAttr
|
, withAttr
|
||||||
|
@ -52,7 +50,7 @@ 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)
|
import Network.HTTP.Simple
|
||||||
import ZcashHaskell.Types
|
import ZcashHaskell.Types
|
||||||
import Zenith.Core
|
import Zenith.Core
|
||||||
import Zenith.DB
|
import Zenith.DB
|
||||||
|
@ -87,8 +85,6 @@ data State = State
|
||||||
, _splashBox :: !Bool
|
, _splashBox :: !Bool
|
||||||
, _inputForm :: !(Form DialogInput () Name)
|
, _inputForm :: !(Form DialogInput () Name)
|
||||||
, _focusRing :: !(F.FocusRing Name)
|
, _focusRing :: !(F.FocusRing Name)
|
||||||
, _startBlock :: !Int
|
|
||||||
, _dbPath :: !T.Text
|
|
||||||
}
|
}
|
||||||
|
|
||||||
makeLenses ''State
|
makeLenses ''State
|
||||||
|
@ -100,16 +96,7 @@ drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
|
||||||
ui st =
|
ui st =
|
||||||
joinBorders $
|
joinBorders $
|
||||||
withBorderStyle unicode $
|
withBorderStyle unicode $
|
||||||
B.borderWithLabel
|
B.borderWithLabel (str $ "Zenith - " <> st ^. network) $
|
||||||
(str
|
|
||||||
("Zenith - " <>
|
|
||||||
st ^. network <>
|
|
||||||
" - " <>
|
|
||||||
T.unpack
|
|
||||||
(maybe
|
|
||||||
"(None)"
|
|
||||||
(\(_, w) -> zcashWalletName $ entityVal w)
|
|
||||||
(L.listSelectedElement (st ^. wallets))))) $
|
|
||||||
(C.center (listBox "Addresses" (st ^. addresses)) <+>
|
(C.center (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)
|
||||||
|
@ -163,7 +150,7 @@ drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
|
||||||
titleAttr
|
titleAttr
|
||||||
(str
|
(str
|
||||||
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=>
|
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=>
|
||||||
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.3.0")) <=>
|
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.1")) <=>
|
||||||
C.hCenter (withAttr blinkAttr $ str "Press any key..."))
|
C.hCenter (withAttr blinkAttr $ str "Press any key..."))
|
||||||
else emptyWidget
|
else emptyWidget
|
||||||
|
|
||||||
|
@ -210,12 +197,10 @@ appEvent (BT.VtyEvent e) = 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
|
||||||
|
BT.modify $ set dialogBox Blank
|
||||||
fs <- BT.zoom inputForm $ BT.gets formState
|
fs <- BT.zoom inputForm $ BT.gets formState
|
||||||
nw <- liftIO $ addNewWallet (fs ^. dialogInput) s
|
|
||||||
BT.modify $ set wallets nw
|
|
||||||
printMsg $
|
printMsg $
|
||||||
"Creating new wallet " <> T.unpack (fs ^. dialogInput)
|
"Creating new wallet " <> T.unpack (fs ^. dialogInput)
|
||||||
BT.modify $ set dialogBox Blank
|
|
||||||
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
|
||||||
|
@ -286,7 +271,6 @@ runZenithCLI host port dbFilePath = do
|
||||||
case (bc :: Maybe ZebraGetBlockChainInfo) of
|
case (bc :: Maybe ZebraGetBlockChainInfo) of
|
||||||
Nothing -> print "Unable to determine blockchain status"
|
Nothing -> print "Unable to determine blockchain status"
|
||||||
Just chainInfo -> do
|
Just chainInfo -> do
|
||||||
initDb dbFilePath
|
|
||||||
walList <- getWallets dbFilePath $ zgb_net chainInfo
|
walList <- getWallets dbFilePath $ zgb_net chainInfo
|
||||||
void $
|
void $
|
||||||
M.defaultMain theApp $
|
M.defaultMain theApp $
|
||||||
|
@ -304,19 +288,7 @@ runZenithCLI host port dbFilePath = do
|
||||||
True
|
True
|
||||||
(mkInputForm $ DialogInput "Main")
|
(mkInputForm $ DialogInput "Main")
|
||||||
(F.focusRing [AList, TList])
|
(F.focusRing [AList, TList])
|
||||||
(zgb_blocks chainInfo)
|
|
||||||
dbFilePath
|
|
||||||
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"
|
||||||
|
|
||||||
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,40 +13,14 @@ import ZcashHaskell.Utils
|
||||||
import Zenith.DB
|
import Zenith.DB
|
||||||
|
|
||||||
-- * Database functions
|
-- * Database functions
|
||||||
-- | Initializes the database
|
-- | Returns the list of wallets available in the given database
|
||||||
initDb ::
|
checkWallets ::
|
||||||
T.Text -- ^ The database path to check
|
T.Text -- ^ The database name to check
|
||||||
-> IO ()
|
-> ZcashNet -- ^ The network the wallet is running
|
||||||
initDb dbName = do
|
-> IO [Entity ZcashWallet]
|
||||||
|
checkWallets dbName znet = do
|
||||||
runSqlite dbName $ do runMigration migrateAll
|
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
|
-- * Zebra Node interaction
|
||||||
-- | Checks the status of the `zebrad` node
|
-- | Checks the status of the `zebrad` node
|
||||||
|
@ -54,8 +28,8 @@ checkZebra ::
|
||||||
T.Text -- ^ Host where `zebrad` is available
|
T.Text -- ^ Host where `zebrad` is available
|
||||||
-> Int -- ^ Port where `zebrad` is available
|
-> Int -- ^ Port where `zebrad` is available
|
||||||
-> IO (Maybe ZebraGetInfo)
|
-> IO (Maybe ZebraGetInfo)
|
||||||
checkZebra nodeHost nodePort = do
|
checkZebra host port = do
|
||||||
res <- makeZebraCall nodeHost nodePort "getinfo" []
|
res <- makeZebraCall host port "getinfo" []
|
||||||
let body = responseBody (res :: Response (RpcResponse ZebraGetInfo))
|
let body = responseBody (res :: Response (RpcResponse ZebraGetInfo))
|
||||||
return $ result body
|
return $ result body
|
||||||
|
|
||||||
|
@ -64,14 +38,14 @@ checkBlockChain ::
|
||||||
T.Text -- ^ Host where `zebrad` is available
|
T.Text -- ^ Host where `zebrad` is available
|
||||||
-> Int -- ^ Port where `zebrad` is available
|
-> Int -- ^ Port where `zebrad` is available
|
||||||
-> IO (Maybe ZebraGetBlockChainInfo)
|
-> IO (Maybe ZebraGetBlockChainInfo)
|
||||||
checkBlockChain nodeHost nodePort = do
|
checkBlockChain host port = do
|
||||||
let f = makeZebraCall nodeHost nodePort
|
let f = makeZebraCall host port
|
||||||
result <$> (responseBody <$> f "getblockchaininfo" [])
|
result <$> (responseBody <$> f "getblockchaininfo" [])
|
||||||
|
|
||||||
-- | Generic RPC call function
|
-- | Generic RPC call function
|
||||||
connectZebra ::
|
connectZebra ::
|
||||||
FromJSON a => T.Text -> Int -> T.Text -> [Data.Aeson.Value] -> IO (Maybe a)
|
FromJSON a => T.Text -> Int -> T.Text -> [Data.Aeson.Value] -> IO (Maybe a)
|
||||||
connectZebra nodeHost nodePort m params = do
|
connectZebra host port m params = do
|
||||||
res <- makeZebraCall nodeHost nodePort m params
|
res <- makeZebraCall host port m params
|
||||||
let body = responseBody res
|
let body = responseBody res
|
||||||
return $ result body
|
return $ result body
|
||||||
|
|
|
@ -57,3 +57,9 @@ getWallets dbFp n =
|
||||||
runSqlite dbFp $ do
|
runSqlite dbFp $ do
|
||||||
s <- selectList [ZcashWalletNetwork ==. n] []
|
s <- selectList [ZcashWalletNetwork ==. n] []
|
||||||
liftIO $ return s
|
liftIO $ return s
|
||||||
|
|
||||||
|
getAccounts :: T.Text -> ZcashWalletId -> IO [Entity ZcashAccount]
|
||||||
|
getAccounts dbFp w =
|
||||||
|
runSqlite dbFp $ do
|
||||||
|
s <- selectList [ZcashAccountWalletId ==. w] []
|
||||||
|
liftIO $ return s
|
||||||
|
|
|
@ -6,7 +6,6 @@ import Database.Persist.Sqlite
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import ZcashHaskell.Types (ZcashNet(..))
|
import ZcashHaskell.Types (ZcashNet(..))
|
||||||
import Zenith.Core (getAccounts)
|
|
||||||
import Zenith.DB
|
import Zenith.DB
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
|
|
|
@ -1 +1 @@
|
||||||
Subproject commit a52d2231f1a4f85a6504bfb9228a1475a0773088
|
Subproject commit 419f041ca9d1dd921673721c56a673fe1dc058e8
|
Loading…
Reference in a new issue