-
Notifications
You must be signed in to change notification settings - Fork 217
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Add tests for
Cardano.Wallet.Deposit.Write.Keys
- Loading branch information
1 parent
39897fd
commit 2b82205
Showing
3 changed files
with
114 additions
and
2 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
107 changes: 107 additions & 0 deletions
107
lib/customer-deposit-wallet/test/unit/Cardano/Wallet/Deposit/Write/KeysSpec.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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 |