Merge pull request 'Implements scanning of transparent transactions' (#72) from rav001 into dev041

Reviewed-on: #72
This commit is contained in:
pitmutt 2024-03-27 18:40:58 +00:00 committed by Vergara Technologies LLC
commit 24fd6e2e95
Signed by: Vergara Technologies LLC
GPG Key ID: 99DB473BB4715618
4 changed files with 42 additions and 9 deletions

View File

@ -12,4 +12,4 @@ main = do
{-dataStorePath <- require config "dataStorePath"-}
zebraPort <- require config "zebraPort"
zebraHost <- require config "zebraHost"
scanZebra 2764500 zebraHost zebraPort dbFilePath
scanZebra 2772000 zebraHost zebraPort dbFilePath

View File

@ -5,15 +5,18 @@ module Zenith.Scanner where
import Control.Exception (throwIO, try)
import Data.Aeson
import Data.HexString
import Data.Maybe
import qualified Data.Text as T
import GHC.Utils.Monad (concatMapM)
import Network.HTTP.Simple (getResponseBody)
import ZcashHaskell.Types
( BlockResponse(..)
, RpcResponse(..)
, RawZebraTx(..)
, Transaction(..)
, ZebraGetBlockChainInfo(..)
, ZebraTxResponse(..)
, fromRawTBundle
)
import ZcashHaskell.Utils (makeZebraCall)
import ZcashHaskell.Utils (makeZebraCall, readZebraTransaction)
import Zenith.Core (checkBlockChain)
import Zenith.DB (initRawStore)
import Zenith.Utils (jsonNumber)
@ -39,7 +42,7 @@ scanZebra b host port dbFilePath = do
let bList = [b .. (zgb_blocks bStatus)]
txList <-
try $ concatMapM (processBlock host port) bList :: IO
(Either IOError [HexString])
(Either IOError [Transaction])
case txList of
Left e1 -> print e1
Right txList' -> print txList'
@ -49,7 +52,7 @@ processBlock ::
T.Text -- ^ Host name for `zebrad`
-> Int -- ^ Port for `zebrad`
-> Int -- ^ The block number to process
-> IO [HexString]
-> IO [Transaction]
processBlock host port b = do
r <-
makeZebraCall
@ -59,4 +62,34 @@ processBlock host port b = do
[Data.Aeson.String $ T.pack $ show b, jsonNumber 1]
case r of
Left e -> throwIO $ userError e
Right blk -> return $ bl_txs blk
Right blk -> do
x <- mapM (processTx host port) $ bl_txs blk
return $ catMaybes x
-- | Function to process a raw transaction
processTx ::
T.Text -- ^ Host name for `zebrad`
-> Int -- ^ Port for `zebrad`
-> HexString -- ^ transaction id
-> IO (Maybe Transaction)
processTx host port t = do
r <-
makeZebraCall
host
port
"getrawtransaction"
[Data.Aeson.String $ toText t, jsonNumber 1]
case r of
Left e -> throwIO $ userError e
Right rawTx -> do
case readZebraTransaction (ztr_hex rawTx) of
Nothing -> return Nothing
Just rzt ->
return $
Just $
Transaction
t
(ztr_blockheight rawTx)
(ztr_conf rawTx)
(fromIntegral $ zt_expiry rzt)
(fromRawTBundle $ zt_tBundle rzt)

@ -1 +1 @@
Subproject commit f0995441628381fee14ae1c655c3c4f8d96162e5
Subproject commit 4b064af4dece54fe51e3704aa95db18324167d36

View File

@ -1,6 +1,6 @@
cabal-version: 3.0
name: zenith
version: 0.4.4.1
version: 0.4.4.2
license: MIT
license-file: LICENSE
author: Rene Vergara