Include display of balance and transactions #76

Merged
pitmutt merged 9 commits from rav001 into dev041 2024-04-25 19:25:00 +00:00
9 changed files with 363 additions and 84 deletions
Showing only changes of commit c6da52f594 - Show all commits

View file

@ -11,6 +11,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
- Functions to scan relevant transparent notes - Functions to scan relevant transparent notes
- Functions to scan relevant Sapling notes - Functions to scan relevant Sapling notes
- Functions to scan relevant Orchard notes
- Function to query `zebrad` for commitment trees - Function to query `zebrad` for commitment trees
### Changed ### Changed

View file

@ -16,8 +16,10 @@ import System.Environment (getArgs)
import System.Exit import System.Exit
import System.IO import System.IO
import Text.Read (readMaybe) import Text.Read (readMaybe)
import ZcashHaskell.Types
import Zenith.CLI import Zenith.CLI
import Zenith.Types (ZcashAddress(..), ZcashPool(..), ZcashTx(..)) import Zenith.Core (testSync)
import Zenith.Types (Config(..), ZcashAddress(..), ZcashPool(..), ZcashTx(..))
import Zenith.Utils import Zenith.Utils
import Zenith.Zcashd import Zenith.Zcashd
@ -204,6 +206,7 @@ main = do
nodePwd <- require config "nodePwd" nodePwd <- require config "nodePwd"
zebraPort <- require config "zebraPort" zebraPort <- require config "zebraPort"
zebraHost <- require config "zebraHost" zebraHost <- require config "zebraHost"
let myConfig = Config dbFilePath zebraHost zebraPort
if not (null args) if not (null args)
then do then do
case head args of case head args of
@ -217,7 +220,8 @@ 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 dbFilePath "cli" -> runZenithCLI myConfig
"sync" -> testSync myConfig
_ -> printUsage _ -> printUsage
else printUsage else printUsage

View file

@ -61,12 +61,17 @@ import Lens.Micro.Mtl
import Lens.Micro.TH import Lens.Micro.TH
import Text.Wrap (FillScope(..), FillStrategy(..), WrapSettings(..), wrapText) import Text.Wrap (FillScope(..), FillStrategy(..), WrapSettings(..), wrapText)
import ZcashHaskell.Keys (generateWalletSeedPhrase, getWalletSeed) import ZcashHaskell.Keys (generateWalletSeedPhrase, getWalletSeed)
import ZcashHaskell.Orchard (isValidUnifiedAddress) import ZcashHaskell.Orchard (getSaplingFromUA, isValidUnifiedAddress)
import ZcashHaskell.Transparent (encodeTransparent) import ZcashHaskell.Transparent (encodeTransparentReceiver)
import ZcashHaskell.Types import ZcashHaskell.Types
import Zenith.Core import Zenith.Core
import Zenith.DB import Zenith.DB
import Zenith.Types (PhraseDB(..), UnifiedAddressDB(..), ZcashNetDB(..)) import Zenith.Types
( Config(..)
, PhraseDB(..)
, UnifiedAddressDB(..)
, ZcashNetDB(..)
)
import Zenith.Utils (showAddress) import Zenith.Utils (showAddress)
data Name data Name
@ -254,7 +259,7 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
titleAttr titleAttr
(str (str
" _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=> " _____ _ _ _ \n|__ /___ _ __ (_) |_| |__\n / // _ \\ '_ \\| | __| '_ \\\n / /| __/ | | | | |_| | | |\n/____\\___|_| |_|_|\\__|_| |_|") <=>
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.4.0")) <=> C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.5.0")) <=>
C.hCenter (withAttr blinkAttr $ str "Press any key...")) C.hCenter (withAttr blinkAttr $ str "Press any key..."))
else emptyWidget else emptyWidget
capCommand :: String -> String -> Widget Name capCommand :: String -> String -> Widget Name
@ -280,13 +285,15 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
getUA $ walletAddressUAddress $ entityVal a) <=> getUA $ walletAddressUAddress $ entityVal a) <=>
B.borderWithLabel B.borderWithLabel
(str "Legacy Shielded") (str "Legacy Shielded")
(txtWrapWith (txtWrapWith (WrapSettings False True NoFill FillAfterFirst) $
(WrapSettings False True NoFill FillAfterFirst) fromMaybe "None" $
"Pending") <=> (getSaplingFromUA .
E.encodeUtf8 . getUA . walletAddressUAddress)
(entityVal a)) <=>
B.borderWithLabel B.borderWithLabel
(str "Transparent") (str "Transparent")
(txtWrapWith (WrapSettings False True NoFill FillAfterFirst) $ (txtWrapWith (WrapSettings False True NoFill FillAfterFirst) $
maybe "Pending" (encodeTransparent (st ^. network)) $ maybe "None" (encodeTransparentReceiver (st ^. network)) $
t_rec =<< t_rec =<<
(isValidUnifiedAddress . (isValidUnifiedAddress .
E.encodeUtf8 . getUA . walletAddressUAddress) E.encodeUtf8 . getUA . walletAddressUAddress)
@ -511,8 +518,11 @@ theApp =
, M.appAttrMap = const theMap , M.appAttrMap = const theMap
} }
runZenithCLI :: T.Text -> Int -> T.Text -> IO () runZenithCLI :: Config -> IO ()
runZenithCLI host port dbFilePath = do runZenithCLI config = do
let host = c_zebraHost config
let port = c_zebraPort config
let dbFilePath = c_dbPath config
w <- try $ checkZebra host port :: IO (Either IOError ZebraGetInfo) w <- try $ checkZebra host port :: IO (Either IOError ZebraGetInfo)
case w of case w of
Right zebra -> do Right zebra -> do

View file

@ -3,29 +3,42 @@
-- | Core wallet functionality for Zenith -- | Core wallet functionality for Zenith
module Zenith.Core where module Zenith.Core where
import Control.Exception (throwIO) import Control.Exception (throwIO, try)
import Data.Aeson import Data.Aeson
import Data.HexString (hexString) import Data.HexString (hexString)
import Data.Maybe (fromJust)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import Database.Persist import Database.Persist
import Database.Persist.Sqlite
import Network.HTTP.Client import Network.HTTP.Client
import ZcashHaskell.Keys import ZcashHaskell.Keys
import ZcashHaskell.Orchard import ZcashHaskell.Orchard
( encodeUnifiedAddress ( decryptOrchardActionSK
, encodeUnifiedAddress
, genOrchardReceiver , genOrchardReceiver
, genOrchardSpendingKey , genOrchardSpendingKey
, getOrchardNotePosition
, getOrchardWitness
, updateOrchardCommitmentTree
) )
import ZcashHaskell.Sapling import ZcashHaskell.Sapling
( genSaplingInternalAddress ( decodeSaplingOutputEsk
, genSaplingInternalAddress
, genSaplingPaymentAddress , genSaplingPaymentAddress
, genSaplingSpendingKey , genSaplingSpendingKey
, getSaplingNotePosition
, getSaplingWitness
, updateSaplingCommitmentTree
) )
import ZcashHaskell.Transparent (genTransparentPrvKey, genTransparentReceiver) import ZcashHaskell.Transparent (genTransparentPrvKey, genTransparentReceiver)
import ZcashHaskell.Types import ZcashHaskell.Types
import ZcashHaskell.Utils import ZcashHaskell.Utils
import Zenith.DB import Zenith.DB
import Zenith.Types import Zenith.Types
( OrchardSpendingKeyDB(..) ( Config(..)
, HexStringDB(..)
, OrchardSpendingKeyDB(..)
, PhraseDB(..) , PhraseDB(..)
, SaplingSpendingKeyDB(..) , SaplingSpendingKeyDB(..)
, ScopeDB(..) , ScopeDB(..)
@ -177,23 +190,195 @@ createWalletAddress n i zNet scope za = do
(ScopeDB scope) (ScopeDB scope)
-- * Wallet -- * Wallet
-- | Find the Sapling notes that match the given spending key
findSaplingOutputs ::
Config -- ^ the configuration parameters
-> Int -- ^ the starting block
-> ZcashNetDB -- ^ The network
-> SaplingSpendingKeyDB -- ^ The spending key to trial decrypt
-> IO ()
findSaplingOutputs config b znet sk = do
let dbPath = c_dbPath config
let zebraHost = c_zebraHost config
let zebraPort = c_zebraPort config
let zn = getNet znet
tList <- getShieldedOutputs dbPath b
trees <- getCommitmentTrees zebraHost zebraPort (b - 1)
let sT = SaplingCommitmentTree $ ztiSapling trees
decryptNotes sT zn tList
where
decryptNotes ::
SaplingCommitmentTree
-> ZcashNet
-> [(Entity ZcashTransaction, Entity ShieldOutput)]
-> IO ()
decryptNotes _ _ [] = return ()
decryptNotes st n ((zt, o):txs) = do
let updatedTree =
updateSaplingCommitmentTree
st
(getHex $ shieldOutputCmu $ entityVal o)
case updatedTree of
Nothing -> throwIO $ userError "Failed to update commitment tree"
Just uT -> do
let noteWitness = getSaplingWitness uT
let notePos = getSaplingNotePosition <$> noteWitness
case notePos of
Nothing -> throwIO $ userError "Failed to obtain note position"
Just nP -> do
case decodeShOut External n nP o of
Nothing -> do
case decodeShOut Internal n nP o of
Nothing -> do
decryptNotes uT n txs
Just dn1 -> do
print dn1
wId <- saveWalletTransaction (c_dbPath config) zt
saveWalletSapNote
(c_dbPath config)
wId
nP
(fromJust noteWitness)
dn1
decryptNotes uT n txs
Just dn0 -> do
print dn0
wId <- saveWalletTransaction (c_dbPath config) zt
saveWalletSapNote
(c_dbPath config)
wId
nP
(fromJust noteWitness)
dn0
decryptNotes uT n txs
decodeShOut ::
Scope
-> ZcashNet
-> Integer
-> Entity ShieldOutput
-> Maybe DecodedNote
decodeShOut scope n pos s = do
decodeSaplingOutputEsk
(getSapSK sk)
(ShieldedOutput
(getHex $ shieldOutputCv $ entityVal s)
(getHex $ shieldOutputCmu $ entityVal s)
(getHex $ shieldOutputEphKey $ entityVal s)
(getHex $ shieldOutputEncCipher $ entityVal s)
(getHex $ shieldOutputOutCipher $ entityVal s)
(getHex $ shieldOutputProof $ entityVal s))
n
scope
pos
-- | Get Orchard actions
findOrchardActions ::
Config -- ^ the configuration parameters
-> Int -- ^ the starting block
-> ZcashNetDB -- ^ The network
-> OrchardSpendingKeyDB -- ^ The spending key to trial decrypt
-> IO ()
findOrchardActions config b znet sk = do
let dbPath = c_dbPath config
let zebraHost = c_zebraHost config
let zebraPort = c_zebraPort config
let zn = getNet znet
tList <- getOrchardActions dbPath b
trees <- getCommitmentTrees zebraHost zebraPort (b - 1)
let sT = OrchardCommitmentTree $ ztiOrchard trees
decryptNotes sT zn tList
where
decryptNotes ::
OrchardCommitmentTree
-> ZcashNet
-> [(Entity ZcashTransaction, Entity OrchAction)]
-> IO ()
decryptNotes _ _ [] = return ()
decryptNotes ot n ((zt, o):txs) = do
let updatedTree =
updateOrchardCommitmentTree
ot
(getHex $ orchActionCmx $ entityVal o)
case updatedTree of
Nothing -> throwIO $ userError "Failed to update commitment tree"
Just uT -> do
let noteWitness = getOrchardWitness uT
let notePos = getOrchardNotePosition <$> noteWitness
case notePos of
Nothing -> throwIO $ userError "Failed to obtain note position"
Just nP ->
case decodeOrchAction External nP o of
Nothing ->
case decodeOrchAction Internal nP o of
Nothing -> decryptNotes uT n txs
Just dn1 -> do
print dn1
wId <- saveWalletTransaction (c_dbPath config) zt
saveWalletOrchNote
(c_dbPath config)
wId
nP
(fromJust noteWitness)
dn1
decryptNotes uT n txs
Just dn -> do
print dn
wId <- saveWalletTransaction (c_dbPath config) zt
saveWalletOrchNote
(c_dbPath config)
wId
nP
(fromJust noteWitness)
dn
decryptNotes uT n txs
decodeOrchAction ::
Scope -> Integer -> Entity OrchAction -> Maybe DecodedNote
decodeOrchAction scope pos o =
decryptOrchardActionSK (getOrchSK sk) scope $
OrchardAction
(getHex $ orchActionNf $ entityVal o)
(getHex $ orchActionRk $ entityVal o)
(getHex $ orchActionCmx $ entityVal o)
(getHex $ orchActionEphKey $ entityVal o)
(getHex $ orchActionEncCipher $ entityVal o)
(getHex $ orchActionOutCipher $ entityVal o)
(getHex $ orchActionCv $ entityVal o)
(getHex $ orchActionAuth $ entityVal o)
-- | Sync the wallet with the data store -- | Sync the wallet with the data store
syncWallet :: syncWallet ::
T.Text -- ^ The database path Config -- ^ configuration parameters
-> Entity ZcashWallet -> Entity ZcashWallet
-> IO String -> IO String
syncWallet walletDb w = do syncWallet config w = do
let walletDb = c_dbPath config
accs <- getAccounts walletDb $ entityKey w accs <- getAccounts walletDb $ entityKey w
addrs <- concat <$> mapM (getAddresses walletDb . entityKey) accs addrs <- concat <$> mapM (getAddresses walletDb . entityKey) accs
lastBlock <- getMaxWalletBlock walletDb lastBlock <- getMaxWalletBlock walletDb
trNotes <- mapM (findTransparentNotes walletDb lastBlock . entityVal) addrs let startBlock =
if lastBlock > 0
then lastBlock
else zcashWalletBirthdayHeight $ entityVal w
trNotes <- mapM (findTransparentNotes walletDb startBlock . entityVal) addrs
mapM_ (saveWalletTrNote walletDb) $ concat trNotes
sapNotes <- sapNotes <-
mapM mapM
(findSaplingOutputs walletDb lastBlock (zcashWalletNetwork $ entityVal w) . (findSaplingOutputs config startBlock (zcashWalletNetwork $ entityVal w) .
zcashAccountSapSpendKey . entityVal) zcashAccountSapSpendKey . entityVal)
accs accs
print "Transparent Notes: " orchNotes <-
print trNotes mapM
print "Sapling notes: " (findOrchardActions config startBlock (zcashWalletNetwork $ entityVal w) .
print sapNotes zcashAccountOrchSpendKey . entityVal)
accs
return "Testing" return "Testing"
testSync :: Config -> IO ()
testSync config = do
let dbPath = c_dbPath config
w <- runSqlite dbPath $ selectFirst [ZcashWalletName ==. "Main"] []
case w of
Nothing -> print "No wallet"
Just w' -> do
r <- syncWallet config w'
print r

View file

@ -25,6 +25,7 @@ import Data.HexString
import Data.Maybe (fromJust, isJust) import Data.Maybe (fromJust, isJust)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as TE import qualified Data.Text.Encoding as TE
import Data.Word
import Database.Esqueleto.Experimental import Database.Esqueleto.Experimental
import qualified Database.Persist as P import qualified Database.Persist as P
import qualified Database.Persist.Sqlite as PS import qualified Database.Persist.Sqlite as PS
@ -41,18 +42,23 @@ import ZcashHaskell.Types
( DecodedNote(..) ( DecodedNote(..)
, OrchardAction(..) , OrchardAction(..)
, OrchardBundle(..) , OrchardBundle(..)
, OrchardWitness(..)
, SaplingBundle(..) , SaplingBundle(..)
, SaplingCommitmentTree(..)
, SaplingWitness(..)
, Scope(..) , Scope(..)
, ShieldedOutput(..) , ShieldedOutput(..)
, ShieldedSpend(..) , ShieldedSpend(..)
, Transaction(..) , Transaction(..)
, TransparentAddress(..) , TransparentAddress(..)
, TransparentBundle(..) , TransparentBundle(..)
, TransparentReceiver(..)
, UnifiedAddress(..) , UnifiedAddress(..)
, ZcashNet , ZcashNet
) )
import Zenith.Types import Zenith.Types
( HexStringDB(..) ( Config(..)
, HexStringDB(..)
, OrchardSpendingKeyDB(..) , OrchardSpendingKeyDB(..)
, PhraseDB(..) , PhraseDB(..)
, SaplingSpendingKeyDB(..) , SaplingSpendingKeyDB(..)
@ -100,40 +106,43 @@ share
deriving Show Eq deriving Show Eq
WalletTrNote WalletTrNote
tx WalletTransactionId tx WalletTransactionId
addrId WalletAddressId value Word64
value Int
rawId TransparentNoteId
spent Bool spent Bool
script BS.ByteString
UniqueTNote tx script
deriving Show Eq deriving Show Eq
WalletSapNote WalletSapNote
tx WalletTransactionId tx WalletTransactionId
addrId WalletAddressId value Word64
value Int
recipient BS.ByteString recipient BS.ByteString
memo T.Text memo T.Text
rawId ShieldOutputId
spent Bool spent Bool
nullifier HexStringDB nullifier HexStringDB
position Word64
witness HexStringDB
UniqueSapNote tx nullifier
deriving Show Eq deriving Show Eq
WalletOrchNote WalletOrchNote
tx WalletTransactionId tx WalletTransactionId
addrId WalletAddressId value Word64
value Int
recipient BS.ByteString recipient BS.ByteString
memo T.Text memo T.Text
rawId OrchActionId
spent Bool spent Bool
nullifier HexStringDB nullifier HexStringDB
position Word64
witness HexStringDB
UniqueOrchNote tx nullifier
deriving Show Eq deriving Show Eq
ZcashTransaction ZcashTransaction
block Int block Int
txId HexStringDB txId HexStringDB
conf Int conf Int
time Int time Int
UniqueTx block txId
deriving Show Eq deriving Show Eq
TransparentNote TransparentNote
tx ZcashTransactionId tx ZcashTransactionId
value Int value Word64
script BS.ByteString script BS.ByteString
position Int position Int
UniqueTNPos tx position UniqueTNPos tx position
@ -425,6 +434,70 @@ getMaxWalletBlock dbPath = do
Nothing -> return $ -1 Nothing -> return $ -1
Just x -> return $ walletTransactionBlock $ entityVal x Just x -> return $ walletTransactionBlock $ entityVal x
-- | Save a @WalletTransaction@
saveWalletTransaction ::
T.Text -> Entity ZcashTransaction -> IO WalletTransactionId
saveWalletTransaction dbPath zt = do
let zT' = entityVal zt
PS.runSqlite dbPath $ do
t <-
upsert
(WalletTransaction
(zcashTransactionTxId zT')
(zcashTransactionBlock zT')
(zcashTransactionConf zT')
(zcashTransactionTime zT'))
[]
return $ entityKey t
-- | Save a @WalletSapNote@
saveWalletSapNote ::
T.Text -- ^ The database path
-> WalletTransactionId -- ^ The index for the transaction that contains the note
-> Integer -- ^ note position
-> SaplingWitness -- ^ the Sapling incremental witness
-> DecodedNote -- The decoded Sapling note
-> IO ()
saveWalletSapNote dbPath wId pos wit dn = do
PS.runSqlite dbPath $ do
_ <-
upsert
(WalletSapNote
wId
(fromIntegral $ a_value dn)
(a_recipient dn)
(TE.decodeUtf8Lenient $ a_memo dn)
False
(HexStringDB $ a_nullifier dn)
(fromIntegral pos)
(HexStringDB $ sapWit wit))
[]
return ()
-- | Save a @WalletOrchNote@
saveWalletOrchNote ::
T.Text
-> WalletTransactionId
-> Integer
-> OrchardWitness
-> DecodedNote
-> IO ()
saveWalletOrchNote dbPath wId pos wit dn = do
PS.runSqlite dbPath $ do
_ <-
upsert
(WalletOrchNote
wId
(fromIntegral $ a_value dn)
(a_recipient dn)
(TE.decodeUtf8Lenient $ a_memo dn)
False
(HexStringDB $ a_nullifier dn)
(fromIntegral pos)
(HexStringDB $ orchWit wit))
[]
return ()
-- | Find the Transparent Notes that match the given transparent receiver -- | Find the Transparent Notes that match the given transparent receiver
findTransparentNotes :: findTransparentNotes ::
T.Text -- ^ The database path T.Text -- ^ The database path
@ -438,7 +511,7 @@ findTransparentNotes dbPath b t = do
let s = let s =
BS.concat BS.concat
[ BS.pack [0x76, 0xA9, 0x14] [ BS.pack [0x76, 0xA9, 0x14]
, (toBytes . ta_bytes) tR , (toBytes . tr_bytes) tR
, BS.pack [0x88, 0xAC] , BS.pack [0x88, 0xAC]
] ]
PS.runSqlite dbPath $ PS.runSqlite dbPath $
@ -456,9 +529,8 @@ findTransparentNotes dbPath b t = do
saveWalletTrNote :: saveWalletTrNote ::
T.Text -- ^ the database path T.Text -- ^ the database path
-> (Entity ZcashTransaction, Entity TransparentNote) -> (Entity ZcashTransaction, Entity TransparentNote)
-> WalletAddressId
-> IO () -> IO ()
saveWalletTrNote dbPath (zt, tn) wa = do saveWalletTrNote dbPath (zt, tn) = do
let zT' = entityVal zt let zT' = entityVal zt
PS.runSqlite dbPath $ do PS.runSqlite dbPath $ do
t <- t <-
@ -472,52 +544,49 @@ saveWalletTrNote dbPath (zt, tn) wa = do
insert_ $ insert_ $
WalletTrNote WalletTrNote
(entityKey t) (entityKey t)
wa
(transparentNoteValue $ entityVal tn) (transparentNoteValue $ entityVal tn)
(entityKey tn)
False False
(transparentNoteScript $ entityVal tn)
-- | Find the Sapling notes that match the given spending key -- | Save a Sapling note to the wallet database
findSaplingOutputs :: saveSapNote :: T.Text -> WalletSapNote -> IO ()
T.Text -- ^ the database path saveSapNote dbPath wsn = PS.runSqlite dbPath $ do insert_ wsn
-> Int -- ^ the starting block
-> ZcashNetDB -- ^ The network -- | Get the shielded outputs from the given blockheight forward
-> SaplingSpendingKeyDB -- ^ The spending key to trial decrypt getShieldedOutputs ::
-> IO [(Entity ZcashTransaction, DecodedNote)] T.Text -- ^ database path
findSaplingOutputs dbPath b znet sk = do -> Int -- ^ block
r <- -> IO [(Entity ZcashTransaction, Entity ShieldOutput)]
PS.runSqlite dbPath $ do getShieldedOutputs dbPath b =
select $ do PS.runSqlite dbPath $ do
(txs :& sOutputs) <- select $ do
from $ table @ZcashTransaction `innerJoin` table @ShieldOutput `on` (txs :& sOutputs) <-
(\(txs :& sOutputs) -> from $ table @ZcashTransaction `innerJoin` table @ShieldOutput `on`
txs ^. ZcashTransactionId ==. sOutputs ^. ShieldOutputTx) (\(txs :& sOutputs) ->
where_ (txs ^. ZcashTransactionBlock >. val b) txs ^. ZcashTransactionId ==. sOutputs ^. ShieldOutputTx)
pure (txs, sOutputs) where_ (txs ^. ZcashTransactionBlock >. val b)
let decryptedList = orderBy
map (saplingTrialDecrypt External (getNet znet)) r <> [ asc $ txs ^. ZcashTransactionId
map (saplingTrialDecrypt Internal (getNet znet)) r , asc $ sOutputs ^. ShieldOutputPosition
return $ map (second fromJust) $ filter (\(z, n) -> isJust n) decryptedList ]
where pure (txs, sOutputs)
saplingTrialDecrypt ::
Scope -- | Get the Orchard actions from the given blockheight forward
-> ZcashNet getOrchardActions ::
-> (Entity ZcashTransaction, Entity ShieldOutput) T.Text -- ^ database path
-> (Entity ZcashTransaction, Maybe DecodedNote) -> Int -- ^ block
saplingTrialDecrypt sc n (zt, so) = (zt, decodeShOut sc n so) -> IO [(Entity ZcashTransaction, Entity OrchAction)]
decodeShOut :: Scope -> ZcashNet -> Entity ShieldOutput -> Maybe DecodedNote getOrchardActions dbPath b =
decodeShOut scope n s = PS.runSqlite dbPath $ do
decodeSaplingOutputEsk select $ do
(getSapSK sk) (txs :& oActions) <-
(ShieldedOutput from $ table @ZcashTransaction `innerJoin` table @OrchAction `on`
(getHex $ shieldOutputCv $ entityVal s) (\(txs :& oActions) ->
(getHex $ shieldOutputCmu $ entityVal s) txs ^. ZcashTransactionId ==. oActions ^. OrchActionTx)
(getHex $ shieldOutputEphKey $ entityVal s) where_ (txs ^. ZcashTransactionBlock >. val b)
(getHex $ shieldOutputEncCipher $ entityVal s) orderBy
(getHex $ shieldOutputOutCipher $ entityVal s) [asc $ txs ^. ZcashTransactionId, asc $ oActions ^. OrchActionPosition]
(getHex $ shieldOutputProof $ entityVal s)) pure (txs, oActions)
n
scope
-- | Helper function to extract a Unified Address from the database -- | Helper function to extract a Unified Address from the database
readUnifiedAddressDB :: WalletAddress -> Maybe UnifiedAddress readUnifiedAddressDB :: WalletAddress -> Maybe UnifiedAddress

View file

@ -44,7 +44,10 @@ scanZebra b host port dbFilePath = do
if sb > zgb_blocks bStatus || sb < 1 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 = [sb .. (zgb_blocks bStatus)] print $
"Scanning from " ++
show (sb + 1) ++ " to " ++ show (zgb_blocks bStatus)
let bList = [(sb + 1) .. (zgb_blocks bStatus)]
displayConsoleRegions $ do displayConsoleRegions $ do
pg <- newProgressBar def {pgTotal = fromIntegral $ length bList} pg <- newProgressBar def {pgTotal = fromIntegral $ length bList}
txList <- txList <-

View file

@ -79,6 +79,13 @@ newtype TransparentSpendingKeyDB = TransparentSpendingKeyDB
derivePersistField "TransparentSpendingKeyDB" derivePersistField "TransparentSpendingKeyDB"
-- * RPC -- * RPC
-- | Type for Configuration parameters
data Config = Config
{ c_dbPath :: !T.Text
, c_zebraHost :: !T.Text
, c_zebraPort :: !Int
} deriving (Eq, Prelude.Show)
-- ** `zebrad` -- ** `zebrad`
-- | Type for modeling the tree state response -- | Type for modeling the tree state response
data ZebraTreeInfo = ZebraTreeInfo data ZebraTreeInfo = ZebraTreeInfo

View file

@ -107,5 +107,5 @@ main = do
case w of case w of
Nothing -> assertFailure "No wallet in DB" Nothing -> assertFailure "No wallet in DB"
Just w' -> do Just w' -> do
r <- syncWallet "zenith.db" w' r <- syncWallet (Config "zenith.db" "localhost" 18232) w'
r `shouldBe` "Done" r `shouldBe` "Done"

@ -1 +1 @@
Subproject commit ea937f8e5127f64be94bde06e5f1571df8dfbbde Subproject commit f39b37638047159eefdb6fd959ef79938491be8e