Skip to content

Commit

Permalink
[ADP-3488] Add unit tests for mapping from XPub to Address (#4859)
Browse files Browse the repository at this point in the history
This pull request adds unit tests for

* The mapping `XPub` → `Address`
* Verification of `XSignature`

by comparing `Cardano.Wallet.Address.Encoding` against the
implementation in `Cardano.Ledger`.

We adopt the fix of the mapping `XPub` → `Address` by adjusting to the
latest version of the `cardano-wallet-agda` repository.

### Issue Number

ADP-3488
  • Loading branch information
HeinrichApfelmus authored Nov 28, 2024
2 parents f1f8390 + 83c3c80 commit fff0234
Show file tree
Hide file tree
Showing 6 changed files with 210 additions and 51 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
6 changes: 6 additions & 0 deletions lib/customer-deposit-wallet/customer-deposit-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -117,6 +117,7 @@ library
Cardano.Wallet.Deposit.Testing.DSL.Types
Cardano.Wallet.Deposit.Time
Cardano.Wallet.Deposit.Write
Cardano.Wallet.Deposit.Write.Keys

test-suite scenario
import: language, opts-exe
Expand Down Expand Up @@ -216,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 @@ -224,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 @@ -246,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
Expand Up @@ -11,12 +11,9 @@ import Cardano.Crypto.Wallet
)
import Cardano.Wallet.Address.BIP32
( BIP32Path (..)
, DerivationType (..)
)
import Cardano.Wallet.Address.BIP32_Ed25519
( XPrv
, deriveXPrvHard
, deriveXPrvSoft
( deriveXPrvBIP32Path
)
import Cardano.Wallet.Deposit.Pure.State.Submissions
( availableUTxO
Expand Down Expand Up @@ -71,12 +68,5 @@ signTx tx passphrase w = signTx' <$> rootXSignKey w
(T.encodeUtf8 passphrase)
BS.empty
encryptedXPrv
keys = deriveBIP32Path unencryptedXPrv
keys = deriveXPrvBIP32Path unencryptedXPrv
<$> getBIP32PathsForOwnedInputs tx w

deriveBIP32Path :: XPrv -> BIP32Path -> XPrv
deriveBIP32Path xprv Root = xprv
deriveBIP32Path xprv (Segment path Hardened ix) =
deriveXPrvHard (deriveBIP32Path xprv path) ix
deriveBIP32Path xprv (Segment path Soft ix) =
deriveXPrvSoft (deriveBIP32Path xprv path) ix
41 changes: 4 additions & 37 deletions lib/customer-deposit-wallet/src/Cardano/Wallet/Deposit/Write.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,21 +50,11 @@ module Cardano.Wallet.Deposit.Write

import Prelude

import Cardano.Crypto.Wallet
( xpubPublicKey
)
import Cardano.Ledger.Keys
( SignedDSIGN
, VKey (..)
)
import Cardano.Read.Ledger.Tx.Output
( Output (..)
)
import Cardano.Wallet.Address.BIP32_Ed25519
( XPrv
, XPub
, XSignature
, rawSerialiseXSignature
, sign
, toXPub
)
Expand All @@ -77,6 +67,10 @@ import Cardano.Wallet.Deposit.Read
, TxOut
, Value
)
import Cardano.Wallet.Deposit.Write.Keys
( signedDSIGNfromXSignature
, vkeyFromXPub
)
import Cardano.Wallet.Read.Tx
( toConwayOutput
)
Expand All @@ -90,9 +84,6 @@ import Control.Lens
import Data.Map
( Map
)
import Data.Maybe
( fromMaybe
)
import Data.Maybe.Strict
( StrictMaybe (..)
, maybeToStrictMaybe
Expand All @@ -105,7 +96,6 @@ import Data.Set
( Set
)

import qualified Cardano.Crypto.DSIGN as DSIGN
import qualified Cardano.Ledger.Api as L
import qualified Cardano.Ledger.Api.Tx.In as L
import qualified Cardano.Ledger.Slot as L
Expand Down Expand Up @@ -139,29 +129,6 @@ addAddressWitness xprv tx@(Read.Tx ledgerTx) =
witnessVKey =
L.WitVKey (vkeyFromXPub xpub) (signedDSIGNfromXSignature xsign)

-- | Convert 'XPub' to a type that 'Cardano.Ledger' accepts.
vkeyFromXPub :: XPub -> VKey 'L.Witness L.StandardCrypto
vkeyFromXPub =
VKey
. fromMaybe impossible
. DSIGN.rawDeserialiseVerKeyDSIGN
. xpubPublicKey
where
impossible = error "impossible: Cannot convert XPub to VKey"

-- | Convert 'XSignature' to a type that 'Cardano.Ledger' accepts.
signedDSIGNfromXSignature
:: XSignature
-> SignedDSIGN L.StandardCrypto
(Hash.Hash Hash.Blake2b_256 Read.EraIndependentTxBody)
signedDSIGNfromXSignature =
DSIGN.SignedDSIGN
. fromMaybe impossible
. DSIGN.rawDeserialiseSigDSIGN
. rawSerialiseXSignature
where
impossible = error "impossible: Cannot convert XSignature to SignedDSIGN"

{-----------------------------------------------------------------------------
Convenience TxBody
------------------------------------------------------------------------------}
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,80 @@
{-# LANGUAGE DataKinds #-}

-- | Module for converting key types from
-- @Cardano.Ledger@ with key types from @Cardano.Crypto.Wallet@.
--
-- TODO: Match this up with the @Write@ hierarchy.
module Cardano.Wallet.Deposit.Write.Keys
( enterpriseAddressFromVKey
, vkeyFromXPub
, signedDSIGNfromXSignature
) where

import Prelude

import Cardano.Crypto.Wallet
( xpubPublicKey
)
import Cardano.Ledger.Keys
( SignedDSIGN
, VKey (..)
)
import Cardano.Wallet.Address.BIP32_Ed25519
( XPub
, XSignature
, rawSerialiseXSignature
)
import Cardano.Wallet.Deposit.Read
( Address
)
import Data.Maybe
( fromMaybe
)

import qualified Cardano.Crypto.DSIGN as DSIGN
import qualified Cardano.Ledger.Address as L
import qualified Cardano.Ledger.Api as L
import qualified Cardano.Ledger.BaseTypes as L
import qualified Cardano.Ledger.Credential as L
import qualified Cardano.Ledger.Hashes as L
import qualified Cardano.Ledger.Keys as L

{-----------------------------------------------------------------------------
Key conversion
------------------------------------------------------------------------------}
-- | Create an enterprise address from a ledger 'VKey'.
enterpriseAddressFromVKey
:: L.Network
-> VKey 'L.Witness L.StandardCrypto
-> Address
enterpriseAddressFromVKey network =
mkEnterpriseAddress
. L.coerceKeyRole
. L.hashKey
where
mkEnterpriseAddress h =
L.compactAddr
$ L.Addr network (L.KeyHashObj h) L.StakeRefNull

-- | Convert 'XPub' to a ledger verification key.
vkeyFromXPub :: XPub -> VKey 'L.Witness L.StandardCrypto
vkeyFromXPub =
VKey
. fromMaybe impossible
. DSIGN.rawDeserialiseVerKeyDSIGN
. xpubPublicKey
where
impossible = error "impossible: Cannot convert XPub to VKey"

-- | Convert 'XSignature' to a ledger signature.
signedDSIGNfromXSignature
:: XSignature
-> SignedDSIGN L.StandardCrypto
(L.Hash L.StandardCrypto L.EraIndependentTxBody)
signedDSIGNfromXSignature =
DSIGN.SignedDSIGN
. fromMaybe impossible
. DSIGN.rawDeserialiseSigDSIGN
. rawSerialiseXSignature
where
impossible = error "impossible: Cannot convert XSignature to SignedDSIGN"
Original file line number Diff line number Diff line change
@@ -0,0 +1,116 @@
{-# 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 (..)
, compactAddrFromEnterpriseAddr
, credentialFromXPub
)
import Cardano.Wallet.Deposit.Write.Keys
( enterpriseAddressFromVKey
, signedDSIGNfromXSignature
, vkeyFromXPub
)
import Test.Hspec
( Spec
, describe
, it
)
import Test.QuickCheck
( Arbitrary (..)
, Blind (..)
, Property
, elements
, 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 networkTag ->
let network = toLedgerNetwork networkTag
in enterpriseAddressFromVKey network (vkeyFromXPub xpub)
=== enterpriseAddressFromXPub networkTag 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 :: NetworkTag -> XPub -> Read.CompactAddr
enterpriseAddressFromXPub networkTag =
compactAddrFromEnterpriseAddr
. EnterpriseAddrC networkTag
. credentialFromXPub

toLedgerNetwork :: NetworkTag -> L.Network
toLedgerNetwork MainnetTag = L.Mainnet
toLedgerNetwork TestnetTag = L.Testnet

instance Arbitrary NetworkTag where
arbitrary = elements [MainnetTag, TestnetTag]

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 fff0234

Please sign in to comment.