Skip to content

Commit

Permalink
Add tests for rollForward and rollBackward
Browse files Browse the repository at this point in the history
  • Loading branch information
HeinrichApfelmus committed Sep 19, 2024
1 parent 870ac59 commit 4aff6d9
Show file tree
Hide file tree
Showing 2 changed files with 122 additions and 0 deletions.
2 changes: 2 additions & 0 deletions lib/customer-deposit-wallet/customer-deposit-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -167,6 +167,7 @@ test-suite unit
, cardano-crypto
, cardano-wallet-read
, cardano-wallet-test-utils
, containers
, contra-tracer
, customer-deposit-wallet
, customer-deposit-wallet:customer-deposit-wallet-http
Expand All @@ -182,6 +183,7 @@ test-suite unit
other-modules:
Cardano.Wallet.Deposit.HTTP.JSON.JSONSpec
Cardano.Wallet.Deposit.HTTP.OpenAPISpec
Cardano.Wallet.Deposit.PureSpec
Cardano.Wallet.Deposit.RESTSpec
Paths_customer_deposit_wallet
Spec
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,120 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-|
Copyright: © 2024 Cardano Foundation
License: Apache-2.0
Property tests for the deposit wallet.
-}
module Cardano.Wallet.Deposit.PureSpec
( spec
) where

import Prelude

import Cardano.Crypto.Wallet
( XPub
, generate
, toXPub
)
import Test.Hspec
( Spec
, describe
, it
)
import Test.QuickCheck
( Property
, (.&&.)
, (===)
)

import qualified Cardano.Wallet.Deposit.Pure as Wallet
import qualified Cardano.Wallet.Deposit.Read as Read
import qualified Cardano.Wallet.Deposit.Write as Write
import qualified Data.ByteString.Char8 as B8
import qualified Data.Map.Strict as Map

spec :: Spec
spec = do
describe "UTxO availableBalance" $ do
it "rollForward twice"
prop_availableBalance_rollForward_twice
it "rollBackward . rollForward"
prop_availableBalance_rollForward_rollBackward

{-----------------------------------------------------------------------------
Properties
------------------------------------------------------------------------------}
prop_availableBalance_rollForward_twice :: Property
prop_availableBalance_rollForward_twice =
Wallet.availableBalance w2 === Write.mkAda 3
where
w00 = emptyWallet
(addr1, w01) = Wallet.createAddress 1 w00
(addr2, w02) = Wallet.createAddress 2 w01
w0 = w02

tx1 = payFromFaucet [(addr1, Write.mkAda 1)]
block1 = Read.mockNextBlock Read.GenesisPoint [tx1]
chainPoint1 = Read.getChainPoint block1
w1 = Wallet.rollForwardOne block1 w0

tx2 = payFromFaucet [(addr2, Write.mkAda 2)]
block2 = Read.mockNextBlock chainPoint1 [tx2]
w2 = Wallet.rollForwardOne block2 w1

prop_availableBalance_rollForward_rollBackward :: Property
prop_availableBalance_rollForward_rollBackward =
Wallet.availableBalance (fst $ Wallet.rollBackward chainPoint0 w2)
=== Wallet.availableBalance w0
.&&.
Wallet.availableBalance (fst $ Wallet.rollBackward chainPoint1 w2)
=== Wallet.availableBalance w1
where
w00 = emptyWallet
(addr1, w01) = Wallet.createAddress 1 w00
(addr2, w02) = Wallet.createAddress 2 w01

w0 = w02
chainPoint0 = Read.GenesisPoint

tx1 = payFromFaucet [(addr1, Write.mkAda 1)]
block1 = Read.mockNextBlock chainPoint0 [tx1]
chainPoint1 = Read.getChainPoint block1
w1 = Wallet.rollForwardOne block1 w0

tx2 = payFromFaucet [(addr2, Write.mkAda 2)]
block2 = Read.mockNextBlock chainPoint1 [tx2]
w2 = Wallet.rollForwardOne block2 w1

emptyWallet :: Wallet.WalletState
emptyWallet = Wallet.fromXPubAndGenesis testXPub 0 testGenesis

testXPub :: XPub
testXPub =
toXPub
$ generate (B8.pack "random seed for a testing xpub lala") B8.empty

{-----------------------------------------------------------------------------
Test blockchain
------------------------------------------------------------------------------}

testGenesis :: Read.GenesisData
testGenesis = undefined

payFromFaucet :: [(Write.Address, Write.Value)] -> Read.Tx
payFromFaucet destinations =
Write.toConwayTx txid tx
where
toTxOut (addr, value) = Write.mkTxOut addr value
txBody = Write.TxBody
{ Write.spendInputs = mempty
, Write.collInputs = mempty
, Write.txouts =
Map.fromList $ zip [toEnum 0..] $ map toTxOut destinations
, Write.collRet = Nothing
}
tx = Write.Tx
{ Write.txbody = txBody
, Write.txwits = ()
}
txid = Write.mockTxId txBody

0 comments on commit 4aff6d9

Please sign in to comment.