Skip to content

Commit

Permalink
port and complete unit tests for AddressDerivation
Browse files Browse the repository at this point in the history
  • Loading branch information
KtorZ committed Mar 11, 2019
1 parent 5de0ef0 commit 80c2b68
Showing 1 changed file with 184 additions and 0 deletions.
184 changes: 184 additions & 0 deletions test/unit/Cardano/Wallet/AddressDerivationSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,184 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeApplications #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}

module Cardano.Wallet.AddressDerivationSpec
( spec
) where

import Prelude

import Cardano.Wallet.AddressDerivation
( ChangeChain (..)
, Depth (..)
, DerivationType (..)
, Index
, Passphrase (..)
, deriveAccountPrivateKey
, deriveAddressPrivateKey
, deriveAddressPublicKey
, generateKeyFromSeed
, getIndex
, publicKey
, unsafeGenerateKeyFromSeed
)
import Data.ByteString
( ByteString )
import Test.Hspec
( Spec, describe, it )
import Test.QuickCheck
( Arbitrary (..)
, InfiniteList (..)
, Property
, arbitraryBoundedEnum
, choose
, elements
, expectFailure
, property
, (.&&.)
, (===)
, (==>)
)

import qualified Data.ByteArray as BA
import qualified Data.ByteString as BS

spec :: Spec
spec = do
describe "Bounded / Enum relationship" $ do
it "The calls Index.succ maxBound should result in a runtime err (hard)"
prop_succMaxBoundHardIx
it "The calls Index.pred minBound should result in a runtime err (hard)"
prop_predMinBoundHardIx
it "The calls Index.succ maxBound should result in a runtime err (soft)"
prop_succMaxBoundSoftIx
it "The calls Index.pred minBound should result in a runtime err (soft)"
prop_predMinBoundSoftIx
it "Calling toEnum for invalid value gives a runtime err (ChangeChain)"
(property prop_toEnumChangeChain)

describe "Enum Roundtrip" $ do
it "ChangeChain" (property prop_roundtripEnumChangeChain)
it "Index @'Hardened _" (property prop_roundtripEnumIndexHard)
it "Index @'Soft _" (property prop_roundtripEnumIndexSoft)

describe "BIP-0044 Derivation Properties" $ do
it "deriveAccountPrivateKey works for various indexes" $
property prop_accountKeyDerivation
it "N(CKDpriv((kpar, cpar), i)) === CKDpub(N(kpar, cpar), i)" $
property prop_publicChildKeyDerivation


{-------------------------------------------------------------------------------
Properties
-------------------------------------------------------------------------------}


prop_succMaxBoundHardIx :: Property
prop_succMaxBoundHardIx = expectFailure $
property $ succ (maxBound @(Index 'Hardened _)) `seq` ()

prop_predMinBoundHardIx :: Property
prop_predMinBoundHardIx = expectFailure $
property $ pred (minBound @(Index 'Hardened _)) `seq` ()

prop_succMaxBoundSoftIx :: Property
prop_succMaxBoundSoftIx = expectFailure $
property $ succ (maxBound @(Index 'Soft _)) `seq` ()

prop_predMinBoundSoftIx :: Property
prop_predMinBoundSoftIx = expectFailure $
property $ pred (minBound @(Index 'Soft _)) `seq` ()

prop_toEnumChangeChain :: Int -> Property
prop_toEnumChangeChain n =
n > fromEnum InternalChain ==> expectFailure $ property $
(toEnum n :: ChangeChain) `seq` ()

prop_roundtripEnumChangeChain :: ChangeChain -> Property
prop_roundtripEnumChangeChain ix =
(toEnum . fromEnum) ix === ix

prop_roundtripEnumIndexHard :: Index 'Hardened 'AccountK -> Property
prop_roundtripEnumIndexHard ix =
(toEnum . fromEnum) ix === ix .&&. (toEnum . fromEnum . getIndex) ix === ix

prop_roundtripEnumIndexSoft :: Index 'Soft 'AddressK -> Property
prop_roundtripEnumIndexSoft ix =
(toEnum . fromEnum) ix === ix .&&. (toEnum . fromEnum . getIndex) ix === ix

-- | Deriving address public key should be equal to deriving address
-- private key and extracting public key from it (works only for non-hardened
-- child keys).
--
-- To compute the public child key of a parent private key:
-- * N(CKDpriv((kpar, cpar), i)) (works always).
-- * CKDpub(N(kpar, cpar), i) (works only for non-hardened child keys).
--
-- Thus:
--
-- N(CKDpriv((kpar, cpar), i)) === CKDpub(N(kpar, cpar), i)
--
-- if (kpar, cpar) is a non-hardened key.
--
-- For details see <https://github.com/bitcoin/bips/blob/master/bip-0032.mediawiki#private-parent-key--public-child-key bip-0039>
prop_publicChildKeyDerivation
:: Seed
-> Passphrase
-> ChangeChain
-> Index 'Soft 'AddressK
-> Property
prop_publicChildKeyDerivation (Seed seed) pwd cc ix =
addrXPub1 === addrXPub2
where
accXPrv = unsafeGenerateKeyFromSeed seed pwd
-- N(CKDpriv((kpar, cpar), i))
addrXPub1 = publicKey $ deriveAddressPrivateKey pwd accXPrv cc ix
-- CKDpub(N(kpar, cpar), i)
addrXPub2 = deriveAddressPublicKey (publicKey accXPrv) cc ix

prop_accountKeyDerivation
:: Seed
-> Passphrase
-> Index 'Hardened 'AccountK
-> Property
prop_accountKeyDerivation (Seed seed) pwd ix =
accXPub `seq` property ()
where
rootXPrv = generateKeyFromSeed seed pwd
accXPub = deriveAccountPrivateKey pwd rootXPrv ix


{-------------------------------------------------------------------------------
Arbitrary Instances
-------------------------------------------------------------------------------}

newtype Seed = Seed ByteString deriving (Show)

instance Arbitrary Seed where
shrink _ = []
arbitrary = do
InfiniteList bytes _ <- arbitrary
return $ Seed $ BS.pack $ take 32 bytes

instance Arbitrary (Index 'Soft 'AddressK) where
shrink _ = []
arbitrary = arbitraryBoundedEnum

instance Arbitrary (Index 'Hardened 'AccountK) where
shrink _ = []
arbitrary = arbitraryBoundedEnum

instance Arbitrary Passphrase where
shrink (Passphrase "") = []
shrink (Passphrase _ ) = [Passphrase ""]
arbitrary = do
n <- choose (0, 32)
InfiniteList bytes _ <- arbitrary
return $ Passphrase $ BA.convert $ BS.pack $ take n bytes

instance Arbitrary ChangeChain where
shrink _ = []
arbitrary = elements [InternalChain, ExternalChain]

0 comments on commit 80c2b68

Please sign in to comment.