Implement wallet check from DB

This commit is contained in:
Rene Vergara 2024-02-19 14:05:32 -06:00
parent e9fd87ef58
commit b8ff1eb561
Signed by: pitmutt
GPG Key ID: 65122AD495A7F5B2
5 changed files with 36 additions and 7 deletions

View File

@ -87,3 +87,4 @@ tests:
- persistent
- persistent-sqlite
- persistent-template
- zcash-haskell

View File

@ -4,6 +4,7 @@
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
@ -13,7 +14,15 @@ import Lens.Micro.TH
import qualified Brick.AttrMap as A
import qualified Brick.Focus as F
import Brick.Forms (Form(..), (@@=), editTextField, newForm, renderForm)
import Brick.Forms
( Form(..)
, (@@=)
, editTextField
, focusedFormInputAttr
, handleFormEvent
, newForm
, renderForm
)
import qualified Brick.Main as M
import qualified Brick.Types as BT
import Brick.Types (Widget)
@ -41,9 +50,11 @@ import Brick.Widgets.Core
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.Types
import Zenith.Core
import Zenith.DB
data Name
= WList
@ -61,7 +72,7 @@ makeLenses ''WalletName
data State = State
{ _network :: !String
, _wallets :: !(L.List Name String)
, _wallets :: !(L.List Name (Entity ZcashWallet))
, _addresses :: !(L.List Name String)
, _transactions :: !(L.List Name String)
, _msg :: !String
@ -136,7 +147,7 @@ drawUI s = [splashDialog s, helpDialog s, walletDialog s, ui s]
mkWalletForm :: WalletName -> Form WalletName e Name
mkWalletForm =
newForm [label "Name" @@= editTextField walName WalNameField (Just 1)]
newForm [label "Name: " @@= editTextField walName WalNameField (Just 1)]
where
label s w =
padBottom (Pad 1) $ vLimit 1 (hLimit 15 $ str s <+> fill ' ') <+> w
@ -159,7 +170,6 @@ blinkAttr :: A.AttrName
blinkAttr = A.attrName "blink"
appEvent :: BT.BrickEvent Name e -> BT.EventM Name State ()
appEvent (BT.VtyEvent (V.EvKey (V.KChar '\t') [])) = focusRing %= F.focusNext
appEvent (BT.VtyEvent e) = do
r <- F.focusGetCurrent <$> use focusRing
s <- BT.get
@ -176,9 +186,15 @@ appEvent (BT.VtyEvent e) = do
then do
case e of
V.EvKey V.KEsc [] -> BT.modify $ set walletBox False
ev -> return ()
V.EvKey V.KEnter [] -> do
BT.modify $ set walletBox False
fs <- BT.zoom walletForm $ BT.gets formState
printMsg $
"Creating new wallet " <> (T.unpack $ fs ^. walName)
ev -> BT.zoom walletForm $ handleFormEvent (BT.VtyEvent ev)
else do
case e of
V.EvKey (V.KChar '\t') [] -> focusRing %= F.focusNext
V.EvKey (V.KChar 'q') [] -> M.halt
V.EvKey (V.KChar '?') [] -> BT.modify $ set helpBox True
V.EvKey (V.KChar 'c') [] -> BT.modify $ set walletBox True
@ -203,6 +219,7 @@ theMap =
, (customAttr, fg V.black)
, (titleAttr, V.withStyle (fg V.brightGreen) V.bold)
, (blinkAttr, style V.blink)
, (focusedFormInputAttr, V.white `on` V.blue)
]
theApp :: M.App State e Name
@ -224,17 +241,18 @@ 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
void $
M.defaultMain theApp $
State
((show . zgb_net) chainInfo)
(L.list WList (Vec.fromList ["wall1"]) 1)
(L.list WList (Vec.fromList walList) 1)
(L.list AList (Vec.fromList ["addr1", "addr2"]) 1)
(L.list TList (Vec.fromList ["tx1", "tx2", "tx3"]) 1)
("Start up Ok! Connected to Zebra " ++
(T.unpack . zgi_build) zebra ++ " on port " ++ show port ++ ".")
False
False
(null walList)
True
(mkWalletForm $ WalletName "Main")
(F.focusRing [AList, TList])

View File

@ -16,6 +16,7 @@
module Zenith.DB where
import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString as BS
import qualified Data.Text as T
import Database.Persist
@ -37,3 +38,9 @@ share
network ZcashNet
deriving Show
|]
getWallets :: ZcashNet -> IO [Entity ZcashWallet]
getWallets n =
runSqlite "zenith.db" $ do
s <- selectList [ZcashWalletNetwork ==. n] []
liftIO $ return s

View File

@ -4,6 +4,7 @@ import Control.Monad.IO.Class (liftIO)
import Database.Persist
import Database.Persist.Sqlite
import Test.Hspec
import ZcashHaskell.Types (ZcashNet(..))
import Zenith.DB
import Zenith.DB
( EntityField(ZcashWalletId, ZcashWalletName)
@ -27,6 +28,7 @@ main = do
"987654321"
2000000
"Main Wallet"
MainNet
fromSqlKey s `shouldBe` 1
it "read wallet record" $ do
s <-

View File

@ -98,5 +98,6 @@ test-suite zenith-test
, persistent
, persistent-sqlite
, persistent-template
, zcash-haskell
, zenith
default-language: Haskell2010