Merge pull request 'New Wallet creation flow' (#67) from rav001 into dev041

Reviewed-on: #67
This commit is contained in:
pitmutt 2024-02-28 21:23:36 +00:00 committed by Vergara Technologies LLC
commit 43970a8393
Signed by: Vergara Technologies LLC
GPG Key ID: 99DB473BB4715618
9 changed files with 223 additions and 106 deletions

View File

@ -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 git submodule update --remote
``` ```
- Install using `stack`: - Install using `cabal`:
``` ```
stack install cabal install
``` ```
## Configuration ## Configuration

View File

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

View File

@ -5,7 +5,6 @@ module Zenith.CLI where
import Control.Monad (void) import Control.Monad (void)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Data.Maybe (fromMaybe)
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)
@ -22,6 +21,7 @@ import Brick.Forms
, handleFormEvent , handleFormEvent
, newForm , newForm
, renderForm , renderForm
, updateFormState
) )
import qualified Brick.Main as M import qualified Brick.Main as M
import qualified Brick.Types as BT import qualified Brick.Types as BT
@ -42,6 +42,7 @@ import Brick.Widgets.Core
, padBottom , padBottom
, padRight , padRight
, str , str
, txt
, vBox , vBox
, vLimit , vLimit
, withAttr , withAttr
@ -51,7 +52,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 Network.HTTP.Simple import ZcashHaskell.Keys (generateWalletSeedPhrase)
import ZcashHaskell.Types import ZcashHaskell.Types
import Zenith.Core import Zenith.Core
import Zenith.DB import Zenith.DB
@ -61,14 +62,19 @@ data Name
| AList | AList
| TList | TList
| HelpDialog | HelpDialog
| WalNameField | DialogInputField
deriving (Eq, Show, Ord) deriving (Eq, Show, Ord)
data WalletName = WalletName data DialogInput = DialogInput
{ _walName :: !T.Text { _dialogInput :: !T.Text
} deriving (Show) } deriving (Show)
makeLenses ''WalletName makeLenses ''DialogInput
data DialogType
= WName
| AName
| Blank
data State = State data State = State
{ _network :: !String { _network :: !String
@ -77,25 +83,36 @@ data State = State
, _transactions :: !(L.List Name String) , _transactions :: !(L.List Name String)
, _msg :: !String , _msg :: !String
, _helpBox :: !Bool , _helpBox :: !Bool
, _walletBox :: !Bool , _dialogBox :: !DialogType
, _splashBox :: !Bool , _splashBox :: !Bool
, _walletForm :: !(Form WalletName () Name) , _inputForm :: !(Form DialogInput () Name)
, _focusRing :: !(F.FocusRing Name) , _focusRing :: !(F.FocusRing Name)
, _startBlock :: !Int
, _dbPath :: !T.Text
} }
makeLenses ''State makeLenses ''State
drawUI :: State -> [Widget Name] drawUI :: State -> [Widget Name]
drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s] drawUI s = [splashDialog s, helpDialog s, inputDialog s, ui s]
where where
ui :: State -> Widget Name ui :: State -> Widget Name
ui s = ui st =
joinBorders $ joinBorders $
withBorderStyle unicode $ withBorderStyle unicode $
B.borderWithLabel (str $ "Zenith - " <> s ^. network) $ B.borderWithLabel
(C.center (listBox "Addresses" (s ^. addresses)) <+> (str
B.vBorder <+> C.center (listBox "Transactions" (s ^. transactions))) <=> ("Zenith - " <>
msgBox (s ^. msg) 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)
listBox :: String -> L.List Name String -> Widget Name listBox :: String -> L.List Name String -> Widget Name
listBox titleLabel l = listBox titleLabel l =
C.vCenter $ C.vCenter $
@ -111,8 +128,8 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
vBox vBox
[B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m] [B.hBorderWithLabel (str "Messages"), hLimit 70 $ padRight Max $ str m]
helpDialog :: State -> Widget Name helpDialog :: State -> Widget Name
helpDialog s = helpDialog st =
if s ^. helpBox if st ^. helpBox
then D.renderDialog then D.renderDialog
(D.dialog (Just (str "Commands")) Nothing 55) (D.dialog (Just (str "Commands")) Nothing 55)
(vBox ([C.hCenter $ str "Key", B.hBorder] <> keyList) <+> (vBox ([C.hCenter $ str "Key", B.hBorder] <> keyList) <+>
@ -124,16 +141,21 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
map map
(hLimit 40 . str) (hLimit 40 . str)
["Open help", "Close dialog", "Create Wallet", "Quit"] ["Open help", "Close dialog", "Create Wallet", "Quit"]
walletDialog :: State -> Widget Name inputDialog :: State -> Widget Name
walletDialog s = inputDialog st =
if s ^. walletBox case st ^. dialogBox of
then D.renderDialog WName ->
(D.dialog (Just (str "Create Wallet")) Nothing 50) D.renderDialog
(renderForm $ s ^. walletForm) (D.dialog (Just (str "Create Wallet")) Nothing 50)
else emptyWidget (renderForm $ st ^. inputForm)
AName ->
D.renderDialog
(D.dialog (Just (str "Create Account")) Nothing 50)
(renderForm $ st ^. inputForm)
Blank -> emptyWidget
splashDialog :: State -> Widget Name splashDialog :: State -> Widget Name
splashDialog s = splashDialog st =
if s ^. splashBox if st ^. splashBox
then withBorderStyle unicodeBold $ then withBorderStyle unicodeBold $
D.renderDialog D.renderDialog
(D.dialog Nothing Nothing 30) (D.dialog Nothing Nothing 30)
@ -141,13 +163,14 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
titleAttr titleAttr
(str (str
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=> " _____ _ _ _ \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...")) C.hCenter (withAttr blinkAttr $ str "Press any key..."))
else emptyWidget else emptyWidget
mkWalletForm :: WalletName -> Form WalletName e Name mkInputForm :: DialogInput -> Form DialogInput e Name
mkWalletForm = mkInputForm =
newForm [label "Name: " @@= editTextField walName WalNameField (Just 1)] newForm
[label "Name: " @@= editTextField dialogInput DialogInputField (Just 1)]
where where
label s w = label s w =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
@ -180,35 +203,57 @@ appEvent (BT.VtyEvent e) = do
case e of case e of
V.EvKey V.KEsc [] -> do V.EvKey V.KEsc [] -> do
BT.modify $ set helpBox False BT.modify $ set helpBox False
ev -> return () _ev -> return ()
else do else do
if s ^. walletBox case s ^. dialogBox of
then do WName -> do
case e of case e of
V.EvKey V.KEsc [] -> BT.modify $ set walletBox False V.EvKey V.KEsc [] -> BT.modify $ set dialogBox Blank
V.EvKey V.KEnter [] -> do V.EvKey V.KEnter [] -> do
BT.modify $ set walletBox False fs <- BT.zoom inputForm $ BT.gets formState
fs <- BT.zoom walletForm $ BT.gets formState nw <- liftIO $ addNewWallet (fs ^. dialogInput) s
BT.modify $ set wallets nw
printMsg $ printMsg $
"Creating new wallet " <> (T.unpack $ fs ^. walName) "Creating new wallet " <> T.unpack (fs ^. dialogInput)
ev -> BT.zoom walletForm $ handleFormEvent (BT.VtyEvent ev) BT.modify $ set dialogBox Blank
else do ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
AName -> 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
printMsg $
"Creating new address " <> T.unpack (fs ^. dialogInput)
ev -> BT.zoom inputForm $ handleFormEvent (BT.VtyEvent ev)
Blank -> do
case e of case e of
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
V.EvKey (V.KChar 'q') [] -> M.halt V.EvKey (V.KChar 'q') [] -> M.halt
V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True
V.EvKey (V.KChar 'c') [] -> BT.modify $ set walletBox True V.EvKey (V.KChar 'w') [] -> do
V.EvKey (V.KChar 's') [] -> printMsg "You pressed S!" BT.modify $
set inputForm $
updateFormState (DialogInput "New Wallet") $
s ^. inputForm
BT.modify $ set dialogBox WName
V.EvKey (V.KChar 'a') [] -> do
BT.modify $
set inputForm $
updateFormState (DialogInput "New Account") $
s ^. inputForm
BT.modify $ set dialogBox AName
ev -> ev ->
case r of case r of
Just AList -> BT.zoom addresses $ L.handleListEvent ev Just AList -> BT.zoom addresses $ L.handleListEvent ev
Just TList -> BT.zoom transactions $ L.handleListEvent ev Just TList -> BT.zoom transactions $ L.handleListEvent ev
Nothing -> return () _anyName -> return ()
where where
printMsg :: String -> BT.EventM Name State () printMsg :: String -> BT.EventM Name State ()
printMsg s = BT.modify $ updateMsg s printMsg s = BT.modify $ updateMsg s
updateMsg :: String -> State -> State updateMsg :: String -> State -> State
updateMsg = set msg updateMsg = set msg
appEvent _ = return ()
theMap :: A.AttrMap theMap :: A.AttrMap
theMap = theMap =
@ -233,7 +278,7 @@ theApp =
} }
runZenithCLI :: T.Text -> Int -> T.Text -> IO () runZenithCLI :: T.Text -> Int -> T.Text -> IO ()
runZenithCLI host port dbName = do runZenithCLI host port dbFilePath = do
w <- checkZebra host port w <- checkZebra host port
case (w :: Maybe ZebraGetInfo) of case (w :: Maybe ZebraGetInfo) of
Just zebra -> do Just zebra -> do
@ -241,7 +286,8 @@ runZenithCLI host port dbName = 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
walList <- getWallets $ zgb_net chainInfo initDb dbFilePath
walList <- getWallets dbFilePath $ zgb_net chainInfo
void $ void $
M.defaultMain theApp $ M.defaultMain theApp $
State State
@ -252,11 +298,25 @@ runZenithCLI host port dbName = do
("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 ++ ".")
False False
(null walList) (if null walList
then WName
else Blank)
True True
(mkWalletForm $ WalletName "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

View File

@ -13,14 +13,40 @@ import ZcashHaskell.Utils
import Zenith.DB import Zenith.DB
-- * Database functions -- * Database functions
-- | Returns the list of wallets available in the given database -- | Initializes the database
checkWallets :: initDb ::
T.Text -- ^ The database name to check T.Text -- ^ The database path to check
-> ZcashNet -- ^ The network the wallet is running -> IO ()
-> IO [Entity ZcashWallet] initDb dbName = do
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
@ -28,8 +54,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 host port = do checkZebra nodeHost nodePort = do
res <- makeZebraCall host port "getinfo" [] res <- makeZebraCall nodeHost nodePort "getinfo" []
let body = responseBody (res :: Response (RpcResponse ZebraGetInfo)) let body = responseBody (res :: Response (RpcResponse ZebraGetInfo))
return $ result body return $ result body
@ -38,14 +64,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 host port = do checkBlockChain nodeHost nodePort = do
let f = makeZebraCall host port let f = makeZebraCall nodeHost nodePort
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 host port m params = do connectZebra nodeHost nodePort m params = do
res <- makeZebraCall host port m params res <- makeZebraCall nodeHost nodePort m params
let body = responseBody res let body = responseBody res
return $ result body return $ result body

View File

@ -31,16 +31,29 @@ share
[persistLowerCase| [persistLowerCase|
ZcashWallet ZcashWallet
seedPhrase Phrase seedPhrase Phrase
spendingKey BS.ByteString
tPrivateKey BS.ByteString
birthdayHeight Int birthdayHeight Int
name T.Text name T.Text
network ZcashNet network ZcashNet
deriving Show 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 :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
getWallets n = getWallets dbFp n =
runSqlite "zenith.db" $ do runSqlite dbFp $ do
s <- selectList [ZcashWalletNetwork ==. n] [] s <- selectList [ZcashWalletNetwork ==. n] []
liftIO $ return s liftIO $ return s

View File

@ -1,51 +1,68 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
import Control.Monad.IO.Class (liftIO) import Control.Monad (when)
import Database.Persist import Database.Persist
import Database.Persist.Sqlite import Database.Persist.Sqlite
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
import Zenith.DB
( EntityField(ZcashWalletId, ZcashWalletName)
, ZcashWallet(zcashWalletName)
)
main :: IO () main :: IO ()
main = do main = do
checkDbFile <- doesFileExist "test.db"
when checkDbFile $ removeFile "test.db"
hspec $ do hspec $ do
describe "Database tests" $ do describe "Database tests" $ do
it "Create table" $ do it "Create table" $ do
s <- runSqlite "test.db" $ do runMigration migrateAll s <- runSqlite "test.db" $ do runMigration migrateAll
s `shouldBe` () s `shouldBe` ()
it "insert wallet record" $ do describe "Wallet Table" $ do
s <- it "insert wallet record" $ do
runSqlite "test.db" $ do s <-
insert $ runSqlite "test.db" $ do
ZcashWallet insert $
"one two three four five six seven eight nine ten eleven twelve" ZcashWallet
"123456789" "one two three four five six seven eight nine ten eleven twelve"
"987654321" 2000000
2000000 "Main Wallet"
"Main Wallet" MainNet
MainNet fromSqlKey s `shouldBe` 1
fromSqlKey s `shouldBe` 1 it "read wallet record" $ do
it "read wallet record" $ do s <-
s <- runSqlite "test.db" $ do
runSqlite "test.db" $ do selectList [ZcashWalletBirthdayHeight >. 0] []
selectList [ZcashWalletBirthdayHeight >. 0] [] length s `shouldBe` 1
length s `shouldBe` 1 it "modify wallet record" $ do
it "modify wallet record" $ do s <-
s <- runSqlite "test.db" $ do
runSqlite "test.db" $ do let recId = toSqlKey 1 :: ZcashWalletId
let recId = toSqlKey 1 :: ZcashWalletId update recId [ZcashWalletName =. "New Wallet"]
update recId [ZcashWalletName =. "New Wallet"] get recId
get recId "New Wallet" `shouldBe` maybe "None" zcashWalletName s
"New Wallet" `shouldBe` maybe "None" zcashWalletName s it "delete wallet record" $ do
it "delete wallet record" $ do s <-
s <- runSqlite "test.db" $ do
runSqlite "test.db" $ do let recId = toSqlKey 1 :: ZcashWalletId
let recId = toSqlKey 1 :: ZcashWalletId delete recId
delete recId get recId
get recId "None" `shouldBe` maybe "None" zcashWalletName s
"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

@ -1 +1 @@
Subproject commit 419f041ca9d1dd921673721c56a673fe1dc058e8 Subproject commit a52d2231f1a4f85a6504bfb9228a1475a0773088

View File

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

View File

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