Merge pull request 'Enhancements to blockchain scanner' (#74) from rav001 into dev041

Reviewed-on: #74
This commit is contained in:
pitmutt 2024-04-04 19:39:06 +00:00 committed by Vergara Technologies LLC
commit a36de0a307
Signed by: Vergara Technologies LLC
GPG Key ID: 99DB473BB4715618
6 changed files with 96 additions and 38 deletions

View File

@ -8,8 +8,7 @@ import Zenith.Scanner (scanZebra)
main :: IO () main :: IO ()
main = do main = do
config <- load ["zenith.cfg"] config <- load ["zenith.cfg"]
--dbFilePath <- require config "dbFilePath" dbFilePath <- require config "dbFilePath"
dataStorePath <- require config "dataStorePath"
zebraPort <- require config "zebraPort" zebraPort <- require config "zebraPort"
zebraHost <- require config "zebraHost" zebraHost <- require config "zebraHost"
scanZebra 2781518 zebraHost zebraPort dataStorePath scanZebra 2762066 zebraHost zebraPort dbFilePath

View File

@ -157,3 +157,11 @@ createWalletAddress n i zNet scope za = do
(UnifiedAddressDB $ (UnifiedAddressDB $
encodeUnifiedAddress $ UnifiedAddress zNet oRec sRec (Just tRec)) encodeUnifiedAddress $ UnifiedAddress zNet oRec sRec (Just tRec))
(ScopeDB scope) (ScopeDB scope)
-- * Wallet
-- | Sync the wallet with the data store
syncWallet ::
T.Text -- ^ The database path
-> Entity ZcashWallet
-> IO ()
syncWallet walletDb w = undefined

View File

@ -78,23 +78,49 @@ share
UniqueAddress index scope accId UniqueAddress index scope accId
UniqueAddName accId name UniqueAddName accId name
deriving Show Eq deriving Show Eq
|]
share
[mkPersist sqlSettings, mkMigrate "rawStorage"]
[persistLowerCase|
WalletTransaction WalletTransaction
txId HexStringDB
block Int
conf Int
time Int
deriving Show Eq
WalletTrNote
tx WalletTransactionId
addrId WalletAddressId
value Int
rawId TransparentNoteId
spent Bool
deriving Show Eq
WalletSapNote
tx WalletTransactionId
addrId WalletAddressId
value Int
recipient BS.ByteString
memo T.Text
rawId ShieldOutputId
spent Bool
deriving Show Eq
WalletOrchNote
tx WalletTransactionId
addrId WalletAddressId
value Int
recipient BS.ByteString
memo T.Text
rawId OrchActionId
spent Bool
deriving Show Eq
ZcashTransaction
block Int block Int
txId HexStringDB txId HexStringDB
conf Int conf Int
time Int time Int
deriving Show Eq deriving Show Eq
TransparentNote TransparentNote
tx WalletTransactionId tx ZcashTransactionId
value Int value Int
script BS.ByteString script BS.ByteString
OrchAction OrchAction
tx WalletTransactionId tx ZcashTransactionId
nf HexStringDB nf HexStringDB
rk HexStringDB rk HexStringDB
cmx HexStringDB cmx HexStringDB
@ -105,7 +131,7 @@ share
auth HexStringDB auth HexStringDB
deriving Show Eq deriving Show Eq
ShieldOutput ShieldOutput
tx WalletTransactionId tx ZcashTransactionId
cv HexStringDB cv HexStringDB
cmu HexStringDB cmu HexStringDB
ephKey HexStringDB ephKey HexStringDB
@ -114,7 +140,7 @@ share
proof HexStringDB proof HexStringDB
deriving Show Eq deriving Show Eq
ShieldSpend ShieldSpend
tx WalletTransactionId tx ZcashTransactionId
cv HexStringDB cv HexStringDB
anchor HexStringDB anchor HexStringDB
nullifier HexStringDB nullifier HexStringDB
@ -132,12 +158,6 @@ initDb ::
initDb dbName = do initDb dbName = do
runSqlite dbName $ do runMigration migrateAll runSqlite dbName $ do runMigration migrateAll
-- | Initializes the raw data storage
initRawStore ::
T.Text -- ^ the database path
-> IO ()
initRawStore dbFilePath = runSqlite dbFilePath $ runMigration rawStorage
-- | Get existing wallets from database -- | Get existing wallets from database
getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet] getWallets :: T.Text -> ZcashNet -> IO [Entity ZcashWallet]
getWallets dbFp n = getWallets dbFp n =
@ -177,6 +197,30 @@ saveAccount ::
-> IO (Maybe (Entity ZcashAccount)) -> IO (Maybe (Entity ZcashAccount))
saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a saveAccount dbFp a = runSqlite dbFp $ insertUniqueEntity a
-- | Returns the largest block in storage
getMaxBlock ::
T.Text -- ^ The database path
-> IO Int
getMaxBlock dbPath = do
b <-
runSqlite dbPath $
selectFirst [ZcashTransactionBlock >. 0] [Desc ZcashTransactionBlock]
case b of
Nothing -> return $ -1
Just x -> return $ zcashTransactionBlock $ entityVal x
-- | Returns the largest block in the wallet
getMaxWalletBlock ::
T.Text -- ^ The database path
-> IO Int
getMaxWalletBlock dbPath = do
b <-
runSqlite dbPath $
selectFirst [WalletTransactionBlock >. 0] [Desc WalletTransactionBlock]
case b of
Nothing -> return $ -1
Just x -> return $ walletTransactionBlock $ entityVal x
-- | Returns a list of addresses associated with the given account -- | Returns a list of addresses associated with the given account
getAddresses :: getAddresses ::
T.Text -- ^ The database path T.Text -- ^ The database path
@ -216,12 +260,12 @@ saveTransaction ::
T.Text -- ^ the database path T.Text -- ^ the database path
-> Int -- ^ block time -> Int -- ^ block time
-> Transaction -- ^ The transaction to save -> Transaction -- ^ The transaction to save
-> IO (Key WalletTransaction) -> IO (Key ZcashTransaction)
saveTransaction dbFp t wt = saveTransaction dbFp t wt =
runSqlite dbFp $ do runSqlite dbFp $ do
w <- w <-
insert $ insert $
WalletTransaction (tx_height wt) (HexStringDB $ tx_id wt) (tx_conf wt) t ZcashTransaction (tx_height wt) (HexStringDB $ tx_id wt) (tx_conf wt) t
when (isJust $ tx_transpBundle wt) $ when (isJust $ tx_transpBundle wt) $
insertMany_ $ insertMany_ $
map (storeTxOut w) $ (tb_vout . fromJust . tx_transpBundle) wt map (storeTxOut w) $ (tb_vout . fromJust . tx_transpBundle) wt
@ -238,9 +282,9 @@ saveTransaction dbFp t wt =
map (storeOrchAction w) $ (obActions . fromJust . tx_orchardBundle) wt map (storeOrchAction w) $ (obActions . fromJust . tx_orchardBundle) wt
return w return w
where where
storeTxOut :: WalletTransactionId -> TxOut -> TransparentNote storeTxOut :: ZcashTransactionId -> TxOut -> TransparentNote
storeTxOut wid (TxOut v s) = TransparentNote wid (fromIntegral v) s storeTxOut wid (TxOut v s) = TransparentNote wid (fromIntegral v) s
storeSapSpend :: WalletTransactionId -> ShieldedSpend -> ShieldSpend storeSapSpend :: ZcashTransactionId -> ShieldedSpend -> ShieldSpend
storeSapSpend wid sp = storeSapSpend wid sp =
ShieldSpend ShieldSpend
wid wid
@ -250,7 +294,7 @@ saveTransaction dbFp t wt =
(HexStringDB $ sp_rk sp) (HexStringDB $ sp_rk sp)
(HexStringDB $ sp_proof sp) (HexStringDB $ sp_proof sp)
(HexStringDB $ sp_auth sp) (HexStringDB $ sp_auth sp)
storeSapOutput :: WalletTransactionId -> ShieldedOutput -> ShieldOutput storeSapOutput :: ZcashTransactionId -> ShieldedOutput -> ShieldOutput
storeSapOutput wid so = storeSapOutput wid so =
ShieldOutput ShieldOutput
wid wid
@ -260,7 +304,7 @@ saveTransaction dbFp t wt =
(HexStringDB $ s_encCipherText so) (HexStringDB $ s_encCipherText so)
(HexStringDB $ s_outCipherText so) (HexStringDB $ s_outCipherText so)
(HexStringDB $ s_proof so) (HexStringDB $ s_proof so)
storeOrchAction :: WalletTransactionId -> OrchardAction -> OrchAction storeOrchAction :: ZcashTransactionId -> OrchardAction -> OrchAction
storeOrchAction wid oa = storeOrchAction wid oa =
OrchAction OrchAction
wid wid

View File

@ -8,6 +8,7 @@ import Data.HexString
import Data.Maybe import Data.Maybe
import qualified Data.Text as T import qualified Data.Text as T
import GHC.Utils.Monad (concatMapM) import GHC.Utils.Monad (concatMapM)
import System.Console.AsciiProgress
import ZcashHaskell.Types import ZcashHaskell.Types
( BlockResponse(..) ( BlockResponse(..)
, RawZebraTx(..) , RawZebraTx(..)
@ -20,7 +21,7 @@ import ZcashHaskell.Types
) )
import ZcashHaskell.Utils (getBlockTime, makeZebraCall, readZebraTransaction) import ZcashHaskell.Utils (getBlockTime, makeZebraCall, readZebraTransaction)
import Zenith.Core (checkBlockChain) import Zenith.Core (checkBlockChain)
import Zenith.DB (initRawStore, saveTransaction) import Zenith.DB (getMaxBlock, initDb, saveTransaction)
import Zenith.Utils (jsonNumber) import Zenith.Utils (jsonNumber)
-- | Function to scan the Zcash blockchain through the Zebra node and populate the Zenith database -- | Function to scan the Zcash blockchain through the Zebra node and populate the Zenith database
@ -31,32 +32,37 @@ scanZebra ::
-> T.Text -- ^ Path to database file -> T.Text -- ^ Path to database file
-> IO () -> IO ()
scanZebra b host port dbFilePath = do scanZebra b host port dbFilePath = do
_ <- initRawStore dbFilePath _ <- initDb dbFilePath
bc <- bc <-
try $ checkBlockChain host port :: IO try $ checkBlockChain host port :: IO
(Either IOError ZebraGetBlockChainInfo) (Either IOError ZebraGetBlockChainInfo)
case bc of case bc of
Left e -> print e Left e -> print e
Right bStatus -> do Right bStatus -> do
if b > zgb_blocks bStatus || b < 1 dbBlock <- getMaxBlock dbFilePath
let sb = max dbBlock b
if sb > zgb_blocks bStatus || sb < 1
then throwIO $ userError "Invalid starting block for scan" then throwIO $ userError "Invalid starting block for scan"
else do else do
let bList = [b .. (zgb_blocks bStatus)] let bList = [sb .. (zgb_blocks bStatus)]
txList <- displayConsoleRegions $ do
try $ mapM_ (processBlock host port dbFilePath) bList :: IO pg <- newProgressBar def {pgTotal = fromIntegral $ length bList}
(Either IOError ()) txList <-
case txList of try $ mapM_ (processBlock host port dbFilePath pg) bList :: IO
Left e1 -> print e1 (Either IOError ())
Right txList' -> print txList' case txList of
Left e1 -> print e1
Right txList' -> print txList'
-- | Function to process a raw block and extract the transaction information -- | Function to process a raw block and extract the transaction information
processBlock :: processBlock ::
T.Text -- ^ Host name for `zebrad` T.Text -- ^ Host name for `zebrad`
-> Int -- ^ Port for `zebrad` -> Int -- ^ Port for `zebrad`
-> T.Text -- ^ DB file path -> T.Text -- ^ DB file path
-> ProgressBar -- ^ Progress bar
-> Int -- ^ The block number to process -> Int -- ^ The block number to process
-> IO () -> IO ()
processBlock host port dbFp b = do processBlock host port dbFp pg b = do
r <- r <-
makeZebraCall makeZebraCall
host host
@ -78,6 +84,7 @@ processBlock host port dbFp b = do
let blockTime = getBlockTime hb let blockTime = getBlockTime hb
mapM_ (processTx host port blockTime dbFp) $ mapM_ (processTx host port blockTime dbFp) $
bl_txs $ addTime blk blockTime bl_txs $ addTime blk blockTime
tick pg
where where
addTime :: BlockResponse -> Int -> BlockResponse addTime :: BlockResponse -> Int -> BlockResponse
addTime bl t = addTime bl t =
@ -108,7 +115,7 @@ processTx host port bt dbFp t = do
case readZebraTransaction (ztr_hex rawTx) of case readZebraTransaction (ztr_hex rawTx) of
Nothing -> return () Nothing -> return ()
Just rzt -> do Just rzt -> do
k <- _ <-
saveTransaction dbFp bt $ saveTransaction dbFp bt $
Transaction Transaction
t t
@ -118,4 +125,4 @@ processTx host port bt dbFp t = do
(fromRawTBundle $ zt_tBundle rzt) (fromRawTBundle $ zt_tBundle rzt)
(fromRawSBundle $ zt_sBundle rzt) (fromRawSBundle $ zt_sBundle rzt)
(fromRawOBundle $ zt_oBundle rzt) (fromRawOBundle $ zt_oBundle rzt)
print k return ()

View File

@ -65,6 +65,7 @@ library
, vector , vector
, vty , vty
, word-wrap , word-wrap
, ascii-progress
, zcash-haskell , zcash-haskell
--pkgconfig-depends: rustzcash_wrapper --pkgconfig-depends: rustzcash_wrapper
default-language: Haskell2010 default-language: Haskell2010

View File

@ -3,4 +3,3 @@ nodePwd = "superSecret"
dbFilePath = "zenith.db" dbFilePath = "zenith.db"
zebraHost = "127.0.0.1" zebraHost = "127.0.0.1"
zebraPort = 18232 zebraPort = 18232
dataStorePath = "datastore.db"