Compare commits

...

4 commits

6 changed files with 98 additions and 63 deletions

View file

@ -199,7 +199,7 @@ main :: IO ()
main = do
config <- load ["zenith.cfg"]
args <- getArgs
dbName <- require config "dbName"
dbFilePath <- require config "dbFilePath"
nodeUser <- require config "nodeUser"
nodePwd <- require config "nodePwd"
zebraPort <- require config "zebraPort"
@ -217,7 +217,7 @@ main = do
" ______ _ _ _ \n |___ / (_) | | | \n / / ___ _ __ _| |_| |__ \n / / / _ \\ '_ \\| | __| '_ \\ \n / /_| __/ | | | | |_| | | |\n /_____\\___|_| |_|_|\\__|_| |_|\n Zcash Full Node CLI v0.4.0"
}
(root nodeUser nodePwd)
"cli" -> runZenithCLI zebraHost zebraPort dbName
"cli" -> runZenithCLI zebraHost zebraPort dbFilePath
_ -> printUsage
else printUsage

View file

@ -4,8 +4,6 @@
module Zenith.CLI where
import Control.Monad (void)
import Control.Monad.IO.Class (liftIO)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import qualified Graphics.Vty as V
import Lens.Micro ((&), (.~), (^.), set)
@ -89,13 +87,13 @@ drawUI :: State -> [Widget Name]
drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
where
ui :: State -> Widget Name
ui s =
ui st =
joinBorders $
withBorderStyle unicode $
B.borderWithLabel (str $ "Zenith - " <> s ^. network) $
(C.center (listBox "Addresses" (s ^. addresses)) <+>
B.vBorder <+> C.center (listBox "Transactions" (s ^. transactions))) <=>
msgBox (s ^. msg)
B.borderWithLabel (str $ "Zenith - " <> st ^. network) $
(C.center (listBox "Addresses" (st ^. addresses)) <+>
B.vBorder <+> C.center (listBox "Transactions" (st ^. transactions))) <=>
msgBox (st ^. msg)
listBox :: String -> L.List Name String -> Widget Name
listBox titleLabel l =
C.vCenter $
@ -111,8 +109,8 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
vBox
[B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m]
helpDialog :: State -> Widget Name
helpDialog s =
if s ^. helpBox
helpDialog st =
if st ^. helpBox
then D.renderDialog
(D.dialog (Just (str "Commands")) Nothing 55)
(vBox ([C.hCenter $ str "Key", B.hBorder] <> keyList) <+>
@ -125,15 +123,15 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
(hLimit 40 . str)
["Open help", "Close dialog", "Create Wallet", "Quit"]
walletDialog :: State -> Widget Name
walletDialog s =
if s ^. walletBox
walletDialog st =
if st ^. walletBox
then D.renderDialog
(D.dialog (Just (str "Create Wallet")) Nothing 50)
(renderForm $ s ^. walletForm)
(renderForm $ st ^. walletForm)
else emptyWidget
splashDialog :: State -> Widget Name
splashDialog s =
if s ^. splashBox
splashDialog st =
if st ^. splashBox
then withBorderStyle unicodeBold $
D.renderDialog
(D.dialog Nothing Nothing 30)
@ -180,7 +178,7 @@ appEvent (BT.VtyEvent e) = do
case e of
V.EvKey V.KEsc [] -> do
BT.modify $ set helpBox False
ev -> return ()
_ev -> return ()
else do
if s ^. walletBox
then do
@ -190,7 +188,7 @@ appEvent (BT.VtyEvent e) = do
BT.modify $ set walletBox False
fs <- BT.zoom walletForm $ BT.gets formState
printMsg $
"Creating new wallet " <> (T.unpack $ fs ^. walName)
"Creating new wallet " <> T.unpack (fs ^. walName)
ev -> BT.zoom walletForm $ handleFormEvent (BT.VtyEvent ev)
else do
case e of
@ -203,12 +201,13 @@ appEvent (BT.VtyEvent e) = do
case r of
Just AList -> BT.zoom addresses $ L.handleListEvent ev
Just TList -> BT.zoom transactions $ L.handleListEvent ev
Nothing -> return ()
_anyName -> return ()
where
printMsg :: String -> BT.EventM Name State ()
printMsg s = BT.modify $ updateMsg s
updateMsg :: String -> State -> State
updateMsg = set msg
appEvent _ = return ()
theMap :: A.AttrMap
theMap =
@ -233,7 +232,7 @@ theApp =
}
runZenithCLI :: T.Text -> Int -> T.Text -> IO ()
runZenithCLI host port dbName = do
runZenithCLI host port dbFilePath = do
w <- checkZebra host port
case (w :: Maybe ZebraGetInfo) of
Just zebra -> do
@ -241,7 +240,7 @@ runZenithCLI host port dbName = do
case (bc :: Maybe ZebraGetBlockChainInfo) of
Nothing -> print "Unable to determine blockchain status"
Just chainInfo -> do
walList <- getWallets $ zgb_net chainInfo
walList <- getWallets dbFilePath $ zgb_net chainInfo
void $
M.defaultMain theApp $
State

View file

@ -31,16 +31,35 @@ share
[persistLowerCase|
ZcashWallet
seedPhrase Phrase
spendingKey BS.ByteString
tPrivateKey BS.ByteString
birthdayHeight Int
name T.Text
network ZcashNet
deriving Show
ZcashAccount
walletId ZcashWalletId
index Int
orchSpendKey BS.ByteString
sapSpendKey BS.ByteString
tPrivateKey BS.ByteString
deriving Show
WalletAddress
accId ZcashAccountId
index Int
orchRec BS.ByteString Maybe
sapRec BS.ByteString Maybe
tRec BS.ByteString Maybe
encoded T.Text
deriving Show
|]
getWallets :: ZcashNet -> IO [Entity ZcashWallet]
getWallets n =
runSqlite "zenith.db" $ do
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
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

View file

@ -1,51 +1,67 @@
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad.IO.Class (liftIO)
import Control.Monad (when)
import Database.Persist
import Database.Persist.Sqlite
import System.Directory
import Test.Hspec
import ZcashHaskell.Types (ZcashNet(..))
import Zenith.DB
import Zenith.DB
( EntityField(ZcashWalletId, ZcashWalletName)
, ZcashWallet(zcashWalletName)
)
main :: IO ()
main = do
checkDbFile <- doesFileExist "test.db"
when checkDbFile $ removeFile "test.db"
hspec $ do
describe "Database tests" $ do
it "Create table" $ do
s <- runSqlite "test.db" $ do runMigration migrateAll
s `shouldBe` ()
it "insert wallet record" $ do
s <-
runSqlite "test.db" $ do
insert $
ZcashWallet
"one two three four five six seven eight nine ten eleven twelve"
"123456789"
"987654321"
2000000
"Main Wallet"
MainNet
fromSqlKey s `shouldBe` 1
it "read wallet record" $ do
s <-
runSqlite "test.db" $ do
selectList [ZcashWalletBirthdayHeight >. 0] []
length s `shouldBe` 1
it "modify wallet record" $ do
s <-
runSqlite "test.db" $ do
let recId = toSqlKey 1 :: ZcashWalletId
update recId [ZcashWalletName =. "New Wallet"]
get recId
"New Wallet" `shouldBe` maybe "None" zcashWalletName s
it "delete wallet record" $ do
s <-
runSqlite "test.db" $ do
let recId = toSqlKey 1 :: ZcashWalletId
delete recId
get recId
"None" `shouldBe` maybe "None" zcashWalletName s
describe "Wallet Table" $ do
it "insert wallet record" $ do
s <-
runSqlite "test.db" $ do
insert $
ZcashWallet
"one two three four five six seven eight nine ten eleven twelve"
2000000
"Main Wallet"
MainNet
fromSqlKey s `shouldBe` 1
it "read wallet record" $ do
s <-
runSqlite "test.db" $ do
selectList [ZcashWalletBirthdayHeight >. 0] []
length s `shouldBe` 1
it "modify wallet record" $ do
s <-
runSqlite "test.db" $ do
let recId = toSqlKey 1 :: ZcashWalletId
update recId [ZcashWalletName =. "New Wallet"]
get recId
"New Wallet" `shouldBe` maybe "None" zcashWalletName s
it "delete wallet record" $ do
s <-
runSqlite "test.db" $ do
let recId = toSqlKey 1 :: ZcashWalletId
delete recId
get recId
"None" `shouldBe` maybe "None" zcashWalletName s
describe "Account table" $ do
it "insert account" $ do
s <-
runSqlite "test.db" $ do
insert $
ZcashWallet
"one two three four five six seven eight nine ten eleven twelve"
2000000
"Main Wallet"
MainNet
t <-
runSqlite "test.db" $ do
insert $ ZcashAccount s 0 "132465798" "987654321" "739182462"
fromSqlKey t `shouldBe` 1
it "read accounts for wallet" $ do
wList <- getWallets "test.db" MainNet
acc <- getAccounts "test.db" $ entityKey (head wList)
length acc `shouldBe` 1

View file

@ -104,6 +104,7 @@ test-suite zenith-tests
, persistent
, persistent-sqlite
, hspec
, directory
, zcash-haskell
, zenith
pkgconfig-depends: rustzcash_wrapper

View file

@ -1,5 +1,5 @@
nodeUser = "user"
nodePwd = "superSecret"
dbName = "zenith.db"
dbFilePath = "zenith.db"
zebraHost = "127.0.0.1"
zebraPort = 18232