This repository has been archived by the owner on Mar 1, 2019. It is now read-only.
-
Notifications
You must be signed in to change notification settings - Fork 12
/
Ed25519Bip44.hs
342 lines (317 loc) · 12.7 KB
/
Ed25519Bip44.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
module Test.Spec.Ed25519Bip44 (spec) where
import Universum
import Cardano.Crypto.Wallet (generate)
import Pos.Crypto (EncryptedSecretKey, PassPhrase (..), PublicKey,
checkPassMatches, emptySalt, mkEncSecretWithSaltUnsafe)
import Cardano.Wallet.Kernel.Ed25519Bip44 (ChangeChain,
deriveAccountPrivateKey, deriveAddressKeyPair,
deriveAddressPrivateKey, deriveAddressPublicKey,
derivePublicKey)
import qualified Data.ByteString as BS
import Test.Hspec (Spec, describe, it)
import Test.Pos.Core.Arbitrary ()
import Test.QuickCheck (Arbitrary (..), InfiniteList (..), Property,
arbitraryBoundedIntegral, arbitrarySizedBoundedIntegral,
property, shrinkIntegral, (.&&.), (===), (==>))
-- A wrapper type for hardened keys generator
newtype Hardened
= Hardened Word32
deriving (Show, Eq, Ord, Enum, Real, Integral, Num)
-- A wrapper type for non-hardened keys generator
newtype NonHardened
= NonHardened Word32
deriving (Show, Eq, Ord, Enum, Real, Integral, Num)
instance Bounded Hardened where
minBound = Hardened 0x80000000 -- 2^31
maxBound = Hardened $ maxBound @Word32
instance Bounded NonHardened where
minBound = NonHardened $ minBound @Word32
maxBound = NonHardened 0x7FFFFFFF -- 2^31 - 1
-- TODO (akegalj): seems like Large from quickcheck which is using
-- arbitrarySizedBoundedIntegral doesn't work correctly. That implementation
-- doesn't repect minBound and produces numbers which are bellow minBound!
instance Arbitrary Hardened where
arbitrary = arbitraryBoundedIntegral
shrink = filter (>= minBound) . shrinkIntegral
instance Arbitrary NonHardened where
arbitrary = arbitrarySizedBoundedIntegral
shrink = shrinkIntegral
-- | Deriving address public key should fail if address index
-- is hardened. We should be able to derive Address public key
-- only with non-hardened address index
prop_deriveAddressPublicKeyHardened
:: PublicKey
-> ChangeChain
-> Hardened
-> Property
prop_deriveAddressPublicKeyHardened accPubKey change (Hardened addressIx) =
property $ isNothing addrPubKey
where
addrPubKey = deriveAddressPublicKey accPubKey change addressIx
-- | Deriving address public key should succeed if address index
-- is non-hardened.
prop_deriveAddressPublicKeyNonHardened
:: PublicKey
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressPublicKeyNonHardened accPubKey change (NonHardened addressIx) =
property $ isJust addrPubKey
where
addrPubKey = deriveAddressPublicKey accPubKey change addressIx
-- | 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
prop_deriveAddressPublicFromAccountPrivateKey
:: InfiniteList Word8
-> PassPhrase
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressPublicFromAccountPrivateKey (InfiniteList seed _) passPhrase@(PassPhrase passBytes) changeChain (NonHardened addressIx) =
-- TODO (akegalj): check coverage with quickcheck @cover@
isJust addrPubKey1 .&&. addrPubKey1 === addrPubKey2
where
accEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
-- N(CKDpriv((kpar, cpar), i))
addrPubKey1 =
derivePublicKey <$> deriveAddressPrivateKey
passPhrase
accEncPrvKey
changeChain
addressIx
-- CKDpub(N(kpar, cpar), i)
addrPubKey2 =
deriveAddressPublicKey
(derivePublicKey accEncPrvKey)
changeChain
addressIx
-- | Deriving address private key should always fail
-- if address index is hardened
prop_deriveAddressPrivateKeyHardened
:: InfiniteList Word8
-> PassPhrase
-> ChangeChain
-> Hardened
-> Property
prop_deriveAddressPrivateKeyHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) changeChain (Hardened addressIx) =
property $ isNothing addrPrvKey
where
accEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
addrPrvKey =
deriveAddressPrivateKey
passPhrase
accEncPrvKey
changeChain
addressIx
-- | Deriving address private key should always succeed
-- if address index is non-hardened
prop_deriveAddressPrivateKeyNonHardened
:: InfiniteList Word8
-> PassPhrase
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressPrivateKeyNonHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) changeChain (NonHardened addressIx) =
property $ isJust addrPrvKey
where
accEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
addrPrvKey =
deriveAddressPrivateKey
passPhrase
accEncPrvKey
changeChain
addressIx
-- | Deriving address private key should always fail for non-hardened key index
-- if password differs from account private key password
prop_deriveAddressPrivateKeyWrongPassword
:: PassPhrase
-> EncryptedSecretKey
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressPrivateKeyWrongPassword passPhrase accEncPrvKey changeChain (NonHardened addressIx) =
isNothing (checkPassMatches passPhrase accEncPrvKey) ==> isNothing addrPrvKey
where
addrPrvKey =
deriveAddressPrivateKey
passPhrase
accEncPrvKey
changeChain
addressIx
-- | Deriving address private key should always succeed for non-hardened key index
-- if password equals to account private key password
prop_deriveAddressPrivateKeyCorrectPassword
:: PassPhrase
-> EncryptedSecretKey
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressPrivateKeyCorrectPassword passPhrase accEncPrvKey changeChain (NonHardened addressIx) =
isJust (checkPassMatches passPhrase accEncPrvKey) ==> isJust addrPrvKey
where
addrPrvKey =
deriveAddressPrivateKey
passPhrase
accEncPrvKey
changeChain
addressIx
-- | Deriving account private key should always fail
-- if account index is non-hardened
prop_deriveAccountPrivateKeyNonHardened
:: InfiniteList Word8
-> PassPhrase
-> NonHardened
-> Property
prop_deriveAccountPrivateKeyNonHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) (NonHardened accountIx) =
property $ isNothing accPrvKey
where
masterEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
accPrvKey =
deriveAccountPrivateKey
passPhrase
masterEncPrvKey
accountIx
-- | Deriving account private key should always succeed
-- if account index is hardened
prop_deriveAccountPrivateKeyHardened
:: InfiniteList Word8
-> PassPhrase
-> Hardened
-> Property
prop_deriveAccountPrivateKeyHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) (Hardened accountIx) =
property $ isJust accPrvKey
where
masterEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
accPrvKey =
deriveAccountPrivateKey
passPhrase
masterEncPrvKey
accountIx
-- | Deriving address public/private key pair should always succeed
-- if account index is hardened (address index is fixed)
prop_deriveAddressKeyPairAccountKeyHardened
:: InfiniteList Word8
-> PassPhrase
-> Hardened
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressKeyPairAccountKeyHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) (Hardened accountIx) changeChain (NonHardened addressIx) =
property $ isJust addrPrvKey
where
masterEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
addrPrvKey =
deriveAddressKeyPair
passPhrase
masterEncPrvKey
accountIx
changeChain
addressIx
-- | Deriving address public/private key pair should always fail
-- if account index is non-hardened (address index is fixed)
prop_deriveAddressKeyPairAccountKeyNonHardened
:: InfiniteList Word8
-> PassPhrase
-> NonHardened
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressKeyPairAccountKeyNonHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) (NonHardened accountIx) changeChain (NonHardened addressIx) =
property $ isNothing addrPrvKey
where
masterEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
addrPrvKey =
deriveAddressKeyPair
passPhrase
masterEncPrvKey
accountIx
changeChain
addressIx
-- | Deriving address public/private key pair should always fail
-- if address index is hardened (account index is fixed)
prop_deriveAddressKeyPairAddressKeyHardened
:: InfiniteList Word8
-> PassPhrase
-> Hardened
-> ChangeChain
-> Hardened
-> Property
prop_deriveAddressKeyPairAddressKeyHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) (Hardened accountIx) changeChain (Hardened addressIx) =
property $ isNothing addrPrvKey
where
masterEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
addrPrvKey =
deriveAddressKeyPair
passPhrase
masterEncPrvKey
accountIx
changeChain
addressIx
-- | Deriving address public/private key pair should always succeed
-- if address index is non-hardened (account index is fixed)
prop_deriveAddressKeyPairAddressKeyNonHardened
:: InfiniteList Word8
-> PassPhrase
-> Hardened
-> ChangeChain
-> NonHardened
-> Property
prop_deriveAddressKeyPairAddressKeyNonHardened (InfiniteList seed _) passPhrase@(PassPhrase passBytes) (Hardened accountIx) changeChain (NonHardened addressIx) =
property $ isJust addrPrvKey
where
masterEncPrvKey = mkEncSecretWithSaltUnsafe emptySalt passPhrase $ generate (BS.pack $ take 32 seed) passBytes
addrPrvKey =
deriveAddressKeyPair
passPhrase
masterEncPrvKey
accountIx
changeChain
addressIx
spec :: Spec
spec = describe "Ed25519Bip44" $ do
describe "Deriving address public key" $ do
it "fails if address index is hardened" $
property prop_deriveAddressPublicKeyHardened
it "succeeds if address index is non-hardened" $
property prop_deriveAddressPublicKeyNonHardened
it "equals to deriving address private key and extracting public part from it: N(CKDpriv((kpar, cpar), i)) === CKDpub(N(kpar, cpar), i)" $
property prop_deriveAddressPublicFromAccountPrivateKey
describe "Deriving address private key" $ do
it "fails if address index is hardened" $
property prop_deriveAddressPrivateKeyHardened
it "succeeds if address index is non-hardened" $
property prop_deriveAddressPrivateKeyNonHardened
it "fails if passwords differ" $
property prop_deriveAddressPrivateKeyWrongPassword
it "succeeds if passwords are equal" $
property prop_deriveAddressPrivateKeyCorrectPassword
describe "Deriving account private key" $ do
it "fails if account index is non-hardened" $
property prop_deriveAccountPrivateKeyNonHardened
it "succeeds if account index is hardened" $
property prop_deriveAccountPrivateKeyHardened
describe "Deriving address private/public key pair" $ do
it "fails if account index is non-hardened" $
property prop_deriveAddressKeyPairAccountKeyNonHardened
it "succeeds if account index is hardened" $
property prop_deriveAddressKeyPairAccountKeyHardened
it "fails if address index is hardened" $
property prop_deriveAddressKeyPairAddressKeyHardened
it "succeeds if account index is non-hardened" $
property prop_deriveAddressKeyPairAddressKeyNonHardened