Balance display and transaction display
This commit is contained in:
parent
53c18a833b
commit
900d4f9da6
6 changed files with 154 additions and 58 deletions
12
CHANGELOG.md
12
CHANGELOG.md
|
@ -5,6 +5,18 @@ All notable changes to this project will be documented in this file.
|
||||||
The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),
|
The format is based on [Keep a Changelog](https://keepachangelog.com/en/1.0.0/),
|
||||||
and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html).
|
and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0.html).
|
||||||
|
|
||||||
|
## [0.4.6.0]
|
||||||
|
|
||||||
|
### Added
|
||||||
|
|
||||||
|
- Display of account balance
|
||||||
|
- Functions to identify spends
|
||||||
|
- Functions to display transactions per address
|
||||||
|
|
||||||
|
### Changed
|
||||||
|
|
||||||
|
- Update `zcash-haskell`
|
||||||
|
|
||||||
## [0.4.5.0]
|
## [0.4.5.0]
|
||||||
|
|
||||||
### Added
|
### Added
|
||||||
|
|
|
@ -37,6 +37,7 @@ import Brick.Widgets.Core
|
||||||
, padBottom
|
, padBottom
|
||||||
, str
|
, str
|
||||||
, strWrap
|
, strWrap
|
||||||
|
, strWrapWith
|
||||||
, txt
|
, txt
|
||||||
, txtWrap
|
, txtWrap
|
||||||
, txtWrapWith
|
, txtWrapWith
|
||||||
|
@ -281,7 +282,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.5.0")) <=>
|
C.hCenter (withAttr titleAttr (str "Zcash Wallet v0.4.6.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
|
||||||
|
@ -351,7 +352,10 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
||||||
show
|
show
|
||||||
(posixSecondsToUTCTime
|
(posixSecondsToUTCTime
|
||||||
(fromIntegral (userTxTime $ entityVal tx)))) <=>
|
(fromIntegral (userTxTime $ entityVal tx)))) <=>
|
||||||
str ("Tx ID: " ++ show (userTxHex $ entityVal tx)) <=>
|
(str "Tx ID: " <+>
|
||||||
|
strWrapWith
|
||||||
|
(WrapSettings False True NoFill FillAfterFirst)
|
||||||
|
(show (userTxHex $ entityVal tx))) <=>
|
||||||
str
|
str
|
||||||
("Amount: " ++
|
("Amount: " ++
|
||||||
if st ^. network == MainNet
|
if st ^. network == MainNet
|
||||||
|
@ -359,7 +363,10 @@ drawUI s = [splashDialog s, helpDialog s, displayDialog s, inputDialog s, ui s]
|
||||||
(fromIntegral $ userTxAmount $ entityVal tx)
|
(fromIntegral $ userTxAmount $ entityVal tx)
|
||||||
else displayTaz
|
else displayTaz
|
||||||
(fromIntegral $ userTxAmount $ entityVal tx)) <=>
|
(fromIntegral $ userTxAmount $ entityVal tx)) <=>
|
||||||
txt ("Memo: " <> userTxMemo (entityVal tx))))
|
(txt "Memo: " <+>
|
||||||
|
txtWrapWith
|
||||||
|
(WrapSettings False True NoFill FillAfterFirst)
|
||||||
|
(userTxMemo (entityVal tx)))))
|
||||||
BlankDisplay -> emptyWidget
|
BlankDisplay -> emptyWidget
|
||||||
|
|
||||||
mkInputForm :: DialogInput -> Form DialogInput e Name
|
mkInputForm :: DialogInput -> Form DialogInput e Name
|
||||||
|
|
103
src/Zenith/DB.hs
103
src/Zenith/DB.hs
|
@ -20,12 +20,11 @@ module Zenith.DB where
|
||||||
|
|
||||||
import Control.Exception (throwIO)
|
import Control.Exception (throwIO)
|
||||||
import Control.Monad (forM_, when)
|
import Control.Monad (forM_, when)
|
||||||
import Control.Monad.IO.Class (MonadIO)
|
import Control.Monad.IO.Class (MonadIO, liftIO)
|
||||||
import Data.Bifunctor
|
|
||||||
import qualified Data.ByteString as BS
|
import qualified Data.ByteString as BS
|
||||||
import Data.HexString
|
import Data.HexString
|
||||||
import Data.List (group, sort)
|
import Data.List (group, sort)
|
||||||
import Data.Maybe (fromJust, isJust)
|
import Data.Maybe (catMaybes, 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 Data.Word
|
||||||
|
@ -122,7 +121,7 @@ share
|
||||||
UniqueUTx hex address
|
UniqueUTx hex address
|
||||||
deriving Show Eq
|
deriving Show Eq
|
||||||
WalletTrNote
|
WalletTrNote
|
||||||
tx WalletTransactionId
|
tx WalletTransactionId OnDeleteCascade OnUpdateCascade
|
||||||
accId ZcashAccountId
|
accId ZcashAccountId
|
||||||
value Word64
|
value Word64
|
||||||
spent Bool
|
spent Bool
|
||||||
|
@ -132,13 +131,13 @@ share
|
||||||
UniqueTNote tx script
|
UniqueTNote tx script
|
||||||
deriving Show Eq
|
deriving Show Eq
|
||||||
WalletTrSpend
|
WalletTrSpend
|
||||||
tx WalletTransactionId
|
tx WalletTransactionId OnDeleteCascade OnUpdateCascade
|
||||||
note WalletTrNoteId
|
note WalletTrNoteId
|
||||||
accId ZcashAccountId
|
accId ZcashAccountId
|
||||||
value Word64
|
value Word64
|
||||||
deriving Show Eq
|
deriving Show Eq
|
||||||
WalletSapNote
|
WalletSapNote
|
||||||
tx WalletTransactionId
|
tx WalletTransactionId OnDeleteCascade OnUpdateCascade
|
||||||
accId ZcashAccountId
|
accId ZcashAccountId
|
||||||
value Word64
|
value Word64
|
||||||
recipient BS.ByteString
|
recipient BS.ByteString
|
||||||
|
@ -151,13 +150,13 @@ share
|
||||||
UniqueSapNote tx nullifier
|
UniqueSapNote tx nullifier
|
||||||
deriving Show Eq
|
deriving Show Eq
|
||||||
WalletSapSpend
|
WalletSapSpend
|
||||||
tx WalletTransactionId
|
tx WalletTransactionId OnDeleteCascade OnUpdateCascade
|
||||||
note WalletSapNoteId
|
note WalletSapNoteId
|
||||||
accId ZcashAccountId
|
accId ZcashAccountId
|
||||||
value Word64
|
value Word64
|
||||||
deriving Show Eq
|
deriving Show Eq
|
||||||
WalletOrchNote
|
WalletOrchNote
|
||||||
tx WalletTransactionId
|
tx WalletTransactionId OnDeleteCascade OnUpdateCascade
|
||||||
accId ZcashAccountId
|
accId ZcashAccountId
|
||||||
value Word64
|
value Word64
|
||||||
recipient BS.ByteString
|
recipient BS.ByteString
|
||||||
|
@ -170,7 +169,7 @@ share
|
||||||
UniqueOrchNote tx nullifier
|
UniqueOrchNote tx nullifier
|
||||||
deriving Show Eq
|
deriving Show Eq
|
||||||
WalletOrchSpend
|
WalletOrchSpend
|
||||||
tx WalletTransactionId
|
tx WalletTransactionId OnDeleteCascade OnUpdateCascade
|
||||||
note WalletOrchNoteId
|
note WalletOrchNoteId
|
||||||
accId ZcashAccountId
|
accId ZcashAccountId
|
||||||
value Word64
|
value Word64
|
||||||
|
@ -647,7 +646,7 @@ saveWalletTrNote dbPath ch za (zt, tn) = do
|
||||||
saveSapNote :: T.Text -> WalletSapNote -> IO ()
|
saveSapNote :: T.Text -> WalletSapNote -> IO ()
|
||||||
saveSapNote dbPath wsn = PS.runSqlite dbPath $ do insert_ wsn
|
saveSapNote dbPath wsn = PS.runSqlite dbPath $ do insert_ wsn
|
||||||
|
|
||||||
-- | Get the shielded outputs from the given blockheight forward
|
-- | Get the shielded outputs from the given blockheight
|
||||||
getShieldedOutputs ::
|
getShieldedOutputs ::
|
||||||
T.Text -- ^ database path
|
T.Text -- ^ database path
|
||||||
-> Int -- ^ block
|
-> Int -- ^ block
|
||||||
|
@ -659,7 +658,7 @@ getShieldedOutputs dbPath b =
|
||||||
from $ table @ZcashTransaction `innerJoin` table @ShieldOutput `on`
|
from $ table @ZcashTransaction `innerJoin` table @ShieldOutput `on`
|
||||||
(\(txs :& sOutputs) ->
|
(\(txs :& sOutputs) ->
|
||||||
txs ^. ZcashTransactionId ==. sOutputs ^. ShieldOutputTx)
|
txs ^. ZcashTransactionId ==. sOutputs ^. ShieldOutputTx)
|
||||||
where_ (txs ^. ZcashTransactionBlock >. val b)
|
where_ (txs ^. ZcashTransactionBlock >=. val b)
|
||||||
orderBy
|
orderBy
|
||||||
[ asc $ txs ^. ZcashTransactionId
|
[ asc $ txs ^. ZcashTransactionId
|
||||||
, asc $ sOutputs ^. ShieldOutputPosition
|
, asc $ sOutputs ^. ShieldOutputPosition
|
||||||
|
@ -678,7 +677,7 @@ getOrchardActions dbPath b =
|
||||||
from $ table @ZcashTransaction `innerJoin` table @OrchAction `on`
|
from $ table @ZcashTransaction `innerJoin` table @OrchAction `on`
|
||||||
(\(txs :& oActions) ->
|
(\(txs :& oActions) ->
|
||||||
txs ^. ZcashTransactionId ==. oActions ^. OrchActionTx)
|
txs ^. ZcashTransactionId ==. oActions ^. OrchActionTx)
|
||||||
where_ (txs ^. ZcashTransactionBlock >. val b)
|
where_ (txs ^. ZcashTransactionBlock >=. val b)
|
||||||
orderBy
|
orderBy
|
||||||
[asc $ txs ^. ZcashTransactionId, asc $ oActions ^. OrchActionPosition]
|
[asc $ txs ^. ZcashTransactionId, asc $ oActions ^. OrchActionPosition]
|
||||||
pure (txs, oActions)
|
pure (txs, oActions)
|
||||||
|
@ -692,6 +691,8 @@ getWalletTransactions dbPath w = do
|
||||||
let w' = entityVal w
|
let w' = entityVal w
|
||||||
chgAddr <- getInternalAddresses dbPath $ walletAddressAccId $ entityVal w
|
chgAddr <- getInternalAddresses dbPath $ walletAddressAccId $ entityVal w
|
||||||
let ctReceiver = t_rec =<< readUnifiedAddressDB (entityVal $ head chgAddr)
|
let ctReceiver = t_rec =<< readUnifiedAddressDB (entityVal $ head chgAddr)
|
||||||
|
let csReceiver = s_rec =<< readUnifiedAddressDB (entityVal $ head chgAddr)
|
||||||
|
let coReceiver = o_rec =<< readUnifiedAddressDB (entityVal $ head chgAddr)
|
||||||
let tReceiver = t_rec =<< readUnifiedAddressDB w'
|
let tReceiver = t_rec =<< readUnifiedAddressDB w'
|
||||||
let sReceiver = s_rec =<< readUnifiedAddressDB w'
|
let sReceiver = s_rec =<< readUnifiedAddressDB w'
|
||||||
let oReceiver = o_rec =<< readUnifiedAddressDB w'
|
let oReceiver = o_rec =<< readUnifiedAddressDB w'
|
||||||
|
@ -730,7 +731,8 @@ getWalletTransactions dbPath w = do
|
||||||
select $ do
|
select $ do
|
||||||
trSpends <- from $ table @WalletTrSpend
|
trSpends <- from $ table @WalletTrSpend
|
||||||
where_
|
where_
|
||||||
(trSpends ^. WalletTrSpendNote `in_` valList (map entityKey trNotes))
|
(trSpends ^. WalletTrSpendNote `in_`
|
||||||
|
valList (map entityKey (trNotes <> trChgNotes)))
|
||||||
pure trSpends
|
pure trSpends
|
||||||
sapNotes <-
|
sapNotes <-
|
||||||
case sReceiver of
|
case sReceiver of
|
||||||
|
@ -741,14 +743,16 @@ getWalletTransactions dbPath w = do
|
||||||
snotes <- from $ table @WalletSapNote
|
snotes <- from $ table @WalletSapNote
|
||||||
where_ (snotes ^. WalletSapNoteRecipient ==. val (getBytes sR))
|
where_ (snotes ^. WalletSapNoteRecipient ==. val (getBytes sR))
|
||||||
pure snotes
|
pure snotes
|
||||||
sapSpends <-
|
sapChgNotes <-
|
||||||
|
case csReceiver of
|
||||||
|
Nothing -> return []
|
||||||
|
Just sR -> do
|
||||||
PS.runSqlite dbPath $ do
|
PS.runSqlite dbPath $ do
|
||||||
select $ do
|
select $ do
|
||||||
sapSpends <- from $ table @WalletSapSpend
|
snotes <- from $ table @WalletSapNote
|
||||||
where_
|
where_ (snotes ^. WalletSapNoteRecipient ==. val (getBytes sR))
|
||||||
(sapSpends ^. WalletSapSpendNote `in_`
|
pure snotes
|
||||||
valList (map entityKey sapNotes))
|
sapSpends <- mapM (getSapSpends . entityKey) (sapNotes <> sapChgNotes)
|
||||||
pure sapSpends
|
|
||||||
orchNotes <-
|
orchNotes <-
|
||||||
case oReceiver of
|
case oReceiver of
|
||||||
Nothing -> return []
|
Nothing -> return []
|
||||||
|
@ -758,22 +762,40 @@ getWalletTransactions dbPath w = do
|
||||||
onotes <- from $ table @WalletOrchNote
|
onotes <- from $ table @WalletOrchNote
|
||||||
where_ (onotes ^. WalletOrchNoteRecipient ==. val (getBytes oR))
|
where_ (onotes ^. WalletOrchNoteRecipient ==. val (getBytes oR))
|
||||||
pure onotes
|
pure onotes
|
||||||
orchSpends <-
|
orchChgNotes <-
|
||||||
|
case coReceiver of
|
||||||
|
Nothing -> return []
|
||||||
|
Just oR -> do
|
||||||
PS.runSqlite dbPath $ do
|
PS.runSqlite dbPath $ do
|
||||||
select $ do
|
select $ do
|
||||||
orchSpends <- from $ table @WalletOrchSpend
|
onotes <- from $ table @WalletOrchNote
|
||||||
where_
|
where_ (onotes ^. WalletOrchNoteRecipient ==. val (getBytes oR))
|
||||||
(orchSpends ^. WalletOrchSpendNote `in_`
|
pure onotes
|
||||||
valList (map entityKey orchNotes))
|
orchSpends <- mapM (getOrchSpends . entityKey) (orchNotes <> orchChgNotes)
|
||||||
pure orchSpends
|
|
||||||
mapM_ addTr trNotes
|
mapM_ addTr trNotes
|
||||||
mapM_ addTr trChgNotes
|
mapM_ addTr trChgNotes
|
||||||
mapM_ addSap sapNotes
|
mapM_ addSap sapNotes
|
||||||
|
mapM_ addSap sapChgNotes
|
||||||
mapM_ addOrch orchNotes
|
mapM_ addOrch orchNotes
|
||||||
|
mapM_ addOrch orchChgNotes
|
||||||
mapM_ subTSpend trSpends
|
mapM_ subTSpend trSpends
|
||||||
mapM_ subSSpend sapSpends
|
mapM_ subSSpend $ catMaybes sapSpends
|
||||||
mapM_ subOSpend orchSpends
|
mapM_ subOSpend $ catMaybes orchSpends
|
||||||
where
|
where
|
||||||
|
getSapSpends :: WalletSapNoteId -> IO (Maybe (Entity WalletSapSpend))
|
||||||
|
getSapSpends n = do
|
||||||
|
PS.runSqlite dbPath $ do
|
||||||
|
selectOne $ do
|
||||||
|
sapSpends <- from $ table @WalletSapSpend
|
||||||
|
where_ (sapSpends ^. WalletSapSpendNote ==. val n)
|
||||||
|
pure sapSpends
|
||||||
|
getOrchSpends :: WalletOrchNoteId -> IO (Maybe (Entity WalletOrchSpend))
|
||||||
|
getOrchSpends n = do
|
||||||
|
PS.runSqlite dbPath $ do
|
||||||
|
selectOne $ do
|
||||||
|
orchSpends <- from $ table @WalletOrchSpend
|
||||||
|
where_ (orchSpends ^. WalletOrchSpendNote ==. val n)
|
||||||
|
pure orchSpends
|
||||||
addTr :: Entity WalletTrNote -> IO ()
|
addTr :: Entity WalletTrNote -> IO ()
|
||||||
addTr n =
|
addTr n =
|
||||||
upsertUserTx
|
upsertUserTx
|
||||||
|
@ -850,14 +872,14 @@ getWalletTransactions dbPath w = do
|
||||||
Just uTx -> do
|
Just uTx -> do
|
||||||
_ <-
|
_ <-
|
||||||
PS.runSqlite dbPath $ do
|
PS.runSqlite dbPath $ do
|
||||||
upsert
|
update $ \t -> do
|
||||||
(UserTx
|
set
|
||||||
(walletTransactionTxId $ entityVal $ head tr)
|
t
|
||||||
wId
|
[ UserTxAmount +=. val amt
|
||||||
(walletTransactionTime $ entityVal $ head tr)
|
, UserTxMemo =.
|
||||||
(amt + userTxAmount (entityVal uTx))
|
val (memo <> " " <> userTxMemo (entityVal uTx))
|
||||||
(memo <> " " <> userTxMemo (entityVal uTx)))
|
]
|
||||||
[]
|
where_ (t ^. UserTxId ==. val (entityKey uTx))
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
getUserTx :: T.Text -> WalletAddressId -> IO [Entity UserTx]
|
getUserTx :: T.Text -> WalletAddressId -> IO [Entity UserTx]
|
||||||
|
@ -1053,18 +1075,18 @@ getBalance dbPath za = do
|
||||||
clearWalletTransactions :: T.Text -> IO ()
|
clearWalletTransactions :: T.Text -> IO ()
|
||||||
clearWalletTransactions dbPath = do
|
clearWalletTransactions dbPath = do
|
||||||
PS.runSqlite dbPath $ do
|
PS.runSqlite dbPath $ do
|
||||||
delete $ do
|
|
||||||
_ <- from $ table @WalletOrchNote
|
|
||||||
return ()
|
|
||||||
delete $ do
|
delete $ do
|
||||||
_ <- from $ table @WalletOrchSpend
|
_ <- from $ table @WalletOrchSpend
|
||||||
return ()
|
return ()
|
||||||
delete $ do
|
delete $ do
|
||||||
_ <- from $ table @WalletSapNote
|
_ <- from $ table @WalletOrchNote
|
||||||
return ()
|
return ()
|
||||||
delete $ do
|
delete $ do
|
||||||
_ <- from $ table @WalletSapSpend
|
_ <- from $ table @WalletSapSpend
|
||||||
return ()
|
return ()
|
||||||
|
delete $ do
|
||||||
|
_ <- from $ table @WalletSapNote
|
||||||
|
return ()
|
||||||
delete $ do
|
delete $ do
|
||||||
_ <- from $ table @WalletTrNote
|
_ <- from $ table @WalletTrNote
|
||||||
return ()
|
return ()
|
||||||
|
@ -1074,6 +1096,9 @@ clearWalletTransactions dbPath = do
|
||||||
delete $ do
|
delete $ do
|
||||||
_ <- from $ table @WalletTransaction
|
_ <- from $ table @WalletTransaction
|
||||||
return ()
|
return ()
|
||||||
|
delete $ do
|
||||||
|
_ <- from $ table @UserTx
|
||||||
|
return ()
|
||||||
|
|
||||||
-- | 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
|
||||||
|
|
69
test/Spec.hs
69
test/Spec.hs
|
@ -1,17 +1,27 @@
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
||||||
|
import Data.HexString
|
||||||
import Database.Persist
|
import Database.Persist
|
||||||
import Database.Persist.Sqlite
|
import Database.Persist.Sqlite
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Test.HUnit
|
import Test.HUnit
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import ZcashHaskell.Orchard (isValidUnifiedAddress)
|
import ZcashHaskell.Orchard (isValidUnifiedAddress)
|
||||||
|
import ZcashHaskell.Sapling
|
||||||
|
( decodeSaplingOutputEsk
|
||||||
|
, getSaplingNotePosition
|
||||||
|
, getSaplingWitness
|
||||||
|
, updateSaplingCommitmentTree
|
||||||
|
)
|
||||||
import ZcashHaskell.Types
|
import ZcashHaskell.Types
|
||||||
( OrchardSpendingKey(..)
|
( DecodedNote(..)
|
||||||
|
, OrchardSpendingKey(..)
|
||||||
, Phrase(..)
|
, Phrase(..)
|
||||||
|
, SaplingCommitmentTree(..)
|
||||||
, SaplingSpendingKey(..)
|
, SaplingSpendingKey(..)
|
||||||
, Scope(..)
|
, Scope(..)
|
||||||
|
, ShieldedOutput(..)
|
||||||
, ZcashNet(..)
|
, ZcashNet(..)
|
||||||
)
|
)
|
||||||
import Zenith.Core
|
import Zenith.Core
|
||||||
|
@ -39,6 +49,7 @@ main = do
|
||||||
Phrase
|
Phrase
|
||||||
"one two three four five six seven eight nine ten eleven twelve")
|
"one two three four five six seven eight nine ten eleven twelve")
|
||||||
2000000
|
2000000
|
||||||
|
0
|
||||||
fromSqlKey s `shouldBe` 1
|
fromSqlKey s `shouldBe` 1
|
||||||
it "read wallet record" $ do
|
it "read wallet record" $ do
|
||||||
s <-
|
s <-
|
||||||
|
@ -70,6 +81,7 @@ main = do
|
||||||
Phrase
|
Phrase
|
||||||
"cloth swing left trap random tornado have great onion element until make shy dad success art tuition canvas thunder apple decade elegant struggle invest")
|
"cloth swing left trap random tornado have great onion element until make shy dad success art tuition canvas thunder apple decade elegant struggle invest")
|
||||||
2200000
|
2200000
|
||||||
|
0
|
||||||
zw `shouldNotBe` Nothing
|
zw `shouldNotBe` Nothing
|
||||||
it "Save Account:" $ do
|
it "Save Account:" $ do
|
||||||
s <-
|
s <-
|
||||||
|
@ -100,12 +112,51 @@ main = do
|
||||||
"utest1mvlny48qd4x94w8vz5u2lrxx0enuquajt72yekgq24p6pjaky3czk6m7x358h7g900ex6gzvdehaekl96qnakjzw8yaasp8y0u3j5jnlfd33trduznh6k3fcn5ek9qc857fgz8ehm37etx94sj58nrkc0k5hurxnuxpcpms3j8uy2t8kt2vy6vetvsfxxdhtjq0yqulqprvh7mf2u3x"
|
"utest1mvlny48qd4x94w8vz5u2lrxx0enuquajt72yekgq24p6pjaky3czk6m7x358h7g900ex6gzvdehaekl96qnakjzw8yaasp8y0u3j5jnlfd33trduznh6k3fcn5ek9qc857fgz8ehm37etx94sj58nrkc0k5hurxnuxpcpms3j8uy2t8kt2vy6vetvsfxxdhtjq0yqulqprvh7mf2u3x"
|
||||||
isValidUnifiedAddress ua `shouldNotBe` Nothing
|
isValidUnifiedAddress ua `shouldNotBe` Nothing
|
||||||
describe "Function tests" $ do
|
describe "Function tests" $ do
|
||||||
it "Wallet sync" $ do
|
describe "Sapling Decoding" $ do
|
||||||
w <-
|
let sk =
|
||||||
|
SaplingSpendingKey
|
||||||
|
"\ETX}\195.\SUB\NUL\NUL\NUL\128\NUL\203\"\229IL\CANJ*\209\EM\145\228m\172\&4\SYNNl\DC3\161\147\SO\157\238H\192\147eQ\143L\201\216\163\180\147\145\156Zs+\146>8\176`ta\161\223\SO\140\177\b;\161\SO\236\151W\148<\STX\171|\DC2\172U\195(I\140\146\214\182\137\211\228\159\128~bV\STXy{m'\224\175\221\219\180!\ENQ_\161\132\240?\255\236\"6\133\181\170t\181\139\143\207\170\211\ENQ\167a\184\163\243\246\140\158t\155\133\138X\a\241\200\140\EMT\GS~\175\249&z\250\214\231\239mi\223\206\STX\t\EM<{V~J\253FB"
|
||||||
|
let tree =
|
||||||
|
SaplingCommitmentTree $
|
||||||
|
hexString
|
||||||
|
"01818f2bd58b1e392334d0565181cc7843ae09e3533b2a50a8f1131af657340a5c001001161f962245812ba5e1804fd0a336bc78fa4ee4441a8e0f1525ca5da1b285d35101120f45afa700b8c1854aa8b9c8fe8ed92118ef790584bfcb926078812a10c83a00000000012f4f72c03f8c937a94919a01a07f21165cc8394295291cb888ca91ed003810390107114fe4bb4cd08b47f6ae47477c182d5da9fe5c189061808c1091e9bf3b4524000001447d6b9100cddd5f80c8cf4ddee2b87eba053bd987465aec2293bd0514e68b0d015f6c95e75f4601a0a31670a7deb970fc8988c611685161d2e1629d0a1a0ebd07015f8b9205e0514fa235d75c150b87e23866b882b39786852d1ab42aab11d31a4a0117ddeb3a5f8d2f6b2d0a07f28f01ab25e03a05a9319275bb86d72fcaef6fc01501f08f39275112dd8905b854170b7f247cf2df18454d4fa94e6e4f9320cca05f24011f8322ef806eb2430dc4a7a41c1b344bea5be946efc7b4349c1c9edb14ff9d39"
|
||||||
|
let nextTree =
|
||||||
|
SaplingCommitmentTree $
|
||||||
|
hexString
|
||||||
|
"01bd8a3f3cfc964332a2ada8c09a0da9dfc24174befb938abb086b9be5ca049e4900100000019f0d7efb00169bb2202152d3266059d208ab17d14642c3339f9075e997160657000000012f4f72c03f8c937a94919a01a07f21165cc8394295291cb888ca91ed003810390107114fe4bb4cd08b47f6ae47477c182d5da9fe5c189061808c1091e9bf3b4524000001447d6b9100cddd5f80c8cf4ddee2b87eba053bd987465aec2293bd0514e68b0d015f6c95e75f4601a0a31670a7deb970fc8988c611685161d2e1629d0a1a0ebd07015f8b9205e0514fa235d75c150b87e23866b882b39786852d1ab42aab11d31a4a0117ddeb3a5f8d2f6b2d0a07f28f01ab25e03a05a9319275bb86d72fcaef6fc01501f08f39275112dd8905b854170b7f247cf2df18454d4fa94e6e4f9320cca05f24011f8322ef806eb2430dc4a7a41c1b344bea5be946efc7b4349c1c9edb14ff9d39"
|
||||||
|
it "Sapling is decoded correctly" $ do
|
||||||
|
so <-
|
||||||
runSqlite "zenith.db" $
|
runSqlite "zenith.db" $
|
||||||
selectFirst [ZcashWalletBirthdayHeight >. 0] []
|
selectList [ShieldOutputTx ==. toSqlKey 38318] []
|
||||||
case w of
|
let cmus = map (getHex . shieldOutputCmu . entityVal) so
|
||||||
Nothing -> assertFailure "No wallet in DB"
|
let pos =
|
||||||
Just w' -> do
|
getSaplingNotePosition <$>
|
||||||
r <- syncWallet (Config "zenith.db" "localhost" 18232) w'
|
(getSaplingWitness =<<
|
||||||
r `shouldBe` "Done"
|
updateSaplingCommitmentTree tree (head cmus))
|
||||||
|
let pos1 = getSaplingNotePosition <$> getSaplingWitness tree
|
||||||
|
let pos2 = getSaplingNotePosition <$> getSaplingWitness nextTree
|
||||||
|
case pos of
|
||||||
|
Nothing -> assertFailure "couldn't get note position"
|
||||||
|
Just p -> do
|
||||||
|
print p
|
||||||
|
print pos1
|
||||||
|
print pos2
|
||||||
|
let dn =
|
||||||
|
decodeSaplingOutputEsk
|
||||||
|
sk
|
||||||
|
(ShieldedOutput
|
||||||
|
(getHex $ shieldOutputCv $ entityVal $ head so)
|
||||||
|
(getHex $ shieldOutputCmu $ entityVal $ head so)
|
||||||
|
(getHex $ shieldOutputEphKey $ entityVal $ head so)
|
||||||
|
(getHex $ shieldOutputEncCipher $ entityVal $ head so)
|
||||||
|
(getHex $ shieldOutputOutCipher $ entityVal $ head so)
|
||||||
|
(getHex $ shieldOutputProof $ entityVal $ head so))
|
||||||
|
TestNet
|
||||||
|
External
|
||||||
|
p
|
||||||
|
case dn of
|
||||||
|
Nothing -> assertFailure "couldn't decode Sap output"
|
||||||
|
Just d ->
|
||||||
|
a_nullifier d `shouldBe`
|
||||||
|
hexString
|
||||||
|
"6c5d1413c63a9a88db71c3f41dc12cd60197ee742fc75b217215e7144db48bd3"
|
||||||
|
|
|
@ -1 +1 @@
|
||||||
Subproject commit f39b37638047159eefdb6fd959ef79938491be8e
|
Subproject commit 00400c433dd8a584ef19af58fcab7fdd108d4110
|
|
@ -1,6 +1,6 @@
|
||||||
cabal-version: 3.0
|
cabal-version: 3.0
|
||||||
name: zenith
|
name: zenith
|
||||||
version: 0.4.5.0
|
version: 0.4.6.0
|
||||||
license: MIT
|
license: MIT
|
||||||
license-file: LICENSE
|
license-file: LICENSE
|
||||||
author: Rene Vergara
|
author: Rene Vergara
|
||||||
|
@ -121,6 +121,7 @@ test-suite zenith-tests
|
||||||
, persistent
|
, persistent
|
||||||
, persistent-sqlite
|
, persistent-sqlite
|
||||||
, hspec
|
, hspec
|
||||||
|
, hexstring
|
||||||
, HUnit
|
, HUnit
|
||||||
, directory
|
, directory
|
||||||
, zcash-haskell
|
, zcash-haskell
|
||||||
|
|
Loading…
Reference in a new issue