Skip to content

Commit

Permalink
Add tests for Cardano.Wallet.Deposit.Write.Keys
Browse files Browse the repository at this point in the history
  • Loading branch information
HeinrichApfelmus committed Nov 27, 2024
1 parent 39897fd commit 2b82205
Show file tree
Hide file tree
Showing 3 changed files with 114 additions and 2 deletions.
4 changes: 2 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -157,8 +157,8 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/cardano-foundation/cardano-wallet-agda
tag: 4a95dadc7c7033d9cb83a3cd4a72cd34f04aaa48
--sha256: 1kk3v22pv8kr5ywjd3grb4s276cx1vcyz2djgg9dckn4nmywzdcs
tag: 7d223bf59e84f6bb0ec65761fbedfde9b7d453ae
--sha256: 1xq89f6x92pi5hrcsh71say36w8gy1g31782bcrgybb22k3pjm8f
subdir:
lib/customer-deposit-wallet-pure
lib/cardano-wallet-read
Expand Down
5 changes: 5 additions & 0 deletions lib/customer-deposit-wallet/customer-deposit-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -217,6 +217,9 @@ test-suite unit
, base58-bytestring
, bytestring
, cardano-crypto
, cardano-crypto-class
, cardano-ledger-api
, cardano-ledger-core
, cardano-ledger-core:testlib
, cardano-wallet-read
, cardano-wallet-test-utils
Expand All @@ -225,6 +228,7 @@ test-suite unit
, customer-deposit-wallet
, customer-deposit-wallet:http
, customer-deposit-wallet:rest
, customer-deposit-wallet-pure
, directory
, hspec
, hspec-golden
Expand All @@ -247,6 +251,7 @@ test-suite unit
Cardano.Wallet.Deposit.Pure.API.AddressSpec
Cardano.Wallet.Deposit.PureSpec
Cardano.Wallet.Deposit.RESTSpec
Cardano.Wallet.Deposit.Write.KeysSpec
Paths_customer_deposit_wallet
Spec

Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,107 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}

-- |
-- Copyright: © 2024 Cardano Foundation
-- License: Apache-2.0
--
-- Property tests for the deposit wallet.
module Cardano.Wallet.Deposit.Write.KeysSpec
( spec
) where

import Prelude

import Cardano.Crypto.Wallet
( generate
)
import Cardano.Wallet.Address.BIP32_Ed25519
( XPrv
, XPub
, sign
, toXPub
)
import Cardano.Wallet.Address.Encoding
( EnterpriseAddr (..)
, NetworkTag (..)
, credentialFromXPub
, compactAddrFromEnterpriseAddr
)
import Cardano.Wallet.Deposit.Write.Keys
( enterpriseAddressFromVKey
, vkeyFromXPub
, signedDSIGNfromXSignature
)
import Test.Hspec
( Spec
, describe
, it
)
import Test.QuickCheck
( Arbitrary (..)
, Blind (..)
, Property
, (===)
, property
, vectorOf
, withMaxSuccess
)

import qualified Cardano.Crypto.Hash.Blake2b as Hash
import qualified Cardano.Crypto.Hash.Class as Hash
import qualified Cardano.Ledger.BaseTypes as L
import qualified Cardano.Ledger.Hashes as L
import qualified Cardano.Ledger.Keys as L
import qualified Cardano.Wallet.Read as Read
import qualified Data.ByteString as BS

{-----------------------------------------------------------------------------
Spec
------------------------------------------------------------------------------}
spec :: Spec
spec = do
describe "commutes with ledger" $ do
it "address" $ lessCryptography $ property $
\xpub ->
enterpriseAddressFromVKey L.Mainnet (vkeyFromXPub xpub)
=== enterpriseAddressFromXPub xpub

it "verify" $ lessCryptography $ property $
\(Blind xprv) hash ->
let xpub = toXPub xprv
xsig = sign xprv (Hash.hashToBytes hash)
in
True ===
L.verifySignedDSIGN
(vkeyFromXPub xpub)
hash
(signedDSIGNfromXSignature xsig)

lessCryptography :: Property -> Property
lessCryptography = withMaxSuccess 20

{-----------------------------------------------------------------------------
Helper functions
------------------------------------------------------------------------------}
enterpriseAddressFromXPub :: XPub -> Read.CompactAddr
enterpriseAddressFromXPub =
compactAddrFromEnterpriseAddr
. EnterpriseAddrC MainnetTag
. credentialFromXPub

instance Arbitrary XPrv where
arbitrary =
generate
<$> (BS.pack <$> vectorOf 100 arbitrary)
<*> pure BS.empty

instance Arbitrary XPub where
arbitrary = toXPub <$> arbitrary

instance Arbitrary (Hash.Hash Hash.Blake2b_256 L.EraIndependentTxBody) where
arbitrary = do
bytes <- BS.pack <$> vectorOf (32) arbitrary
let Just hash = Hash.hashFromBytes bytes
pure hash

0 comments on commit 2b82205

Please sign in to comment.