Skip to content

Commit c23d0a3

Browse files
committed
change secp256k1-haskell to libsecp256k1
1 parent 49da0f3 commit c23d0a3

22 files changed

+205
-231
lines changed

bitcoin-test/bitcoin-test.cabal

+2-2
Original file line numberDiff line numberDiff line change
@@ -78,9 +78,9 @@ library
7878
, bytestring >=0.10.10.0
7979
, containers >=0.6.2.1
8080
, hspec >=2.7.1
81+
, libsecp256k1 >=0.2.0
8182
, memory >=0.15.0
8283
, scientific >=0.3.6.2
83-
, secp256k1-haskell >=0.4.0
8484
, string-conversions >=0.4.0.1
8585
, text >=1.2.3.0
8686
, time >=1.9.3
@@ -107,9 +107,9 @@ test-suite spec
107107
, bytestring >=0.10.10.0
108108
, containers >=0.6.2.1
109109
, hspec >=2.7.1
110+
, libsecp256k1 >=0.2.0
110111
, memory >=0.15.0
111112
, scientific >=0.3.6.2
112-
, secp256k1-haskell >=0.4.0
113113
, string-conversions >=0.4.0.1
114114
, text >=1.2.3.0
115115
, time >=1.9.3

bitcoin-test/lib/Bitcoin/Crypto/SignatureSpec.hs

+26-23
Original file line numberDiff line numberDiff line change
@@ -2,27 +2,27 @@
22

33
module Bitcoin.Crypto.SignatureSpec (spec) where
44

5-
import Bitcoin (getCompactSig)
5+
import Bitcoin (exportSignatureCompact)
66
import Bitcoin.Address (
77
Address (WitnessPubKeyAddress),
88
pubKeyWitnessAddr,
99
)
1010
import Bitcoin.Constants (btc)
1111
import Bitcoin.Crypto (
1212
SecKey,
13-
Sig,
13+
Signature,
1414
decodeStrictSig,
1515
derivePubKey,
16-
exportCompactSig,
17-
exportSig,
16+
ecdsaSign,
17+
exportSignatureCompact,
18+
exportSignatureDer,
1819
getSig,
19-
importSig,
20+
importSecKey,
21+
importSignatureDer,
2022
isCanonicalHalfOrder,
2123
putSig,
22-
secKey,
2324
sha256,
2425
signHash,
25-
signMsg,
2626
verifyHashSig,
2727
)
2828
import Bitcoin.Keys (PubKeyI, derivePubKeyI, wrapSecKey)
@@ -53,7 +53,7 @@ import Data.ByteString (ByteString)
5353
import qualified Data.ByteString as BS
5454
import Data.Map.Strict (Map)
5555
import qualified Data.Map.Strict as Map
56-
import Data.Maybe (fromJust)
56+
import Data.Maybe (fromJust, fromMaybe)
5757
import Data.String.Conversions (cs)
5858
import Data.Text (Text)
5959
import Test.HUnit (
@@ -81,10 +81,10 @@ spec = do
8181
testIsCanonical . lst3
8282
prop "decodeStrictSig . exportSig identity" $
8383
forAll arbitrarySignature $
84-
(\s -> decodeStrictSig (exportSig s) == Just s) . lst3
84+
(\s -> decodeStrictSig (exportSignatureDer s) == Just s) . lst3
8585
prop "importSig . exportSig identity" $
8686
forAll arbitrarySignature $
87-
(\s -> importSig (exportSig s) == Just s) . lst3
87+
(\s -> importSignatureDer (exportSignatureDer s) == Just s) . lst3
8888
prop "getSig . putSig identity" $
8989
forAll arbitrarySignature $ \(_, _, s) ->
9090
(U.runGet getSig . runPut . putSig) s == Right s
@@ -105,7 +105,7 @@ spec = do
105105

106106
-- github.com/bitcoin/bitcoin/blob/master/src/script.cpp
107107
-- from function IsCanonicalSignature
108-
testIsCanonical :: Sig -> Bool
108+
testIsCanonical :: Signature -> Bool
109109
testIsCanonical sig =
110110
not $
111111
-- Non-canonical signature: too short
@@ -156,7 +156,7 @@ testIsCanonical sig =
156156
&& not (testBit (BS.index s (fromIntegral rlen + 7)) 7)
157157
)
158158
where
159-
s = exportSig sig
159+
s = exportSignatureDer sig
160160
len = fromIntegral $ BS.length s
161161
rlen = BS.index s 3
162162
slen = BS.index s (fromIntegral rlen + 5)
@@ -175,10 +175,13 @@ data ValidImpl
175175
implSig :: Text
176176
implSig =
177177
encodeHex $
178-
exportSig $
179-
signMsg
180-
"0000000000000000000000000000000000000000000000000000000000000001"
181-
"0000000000000000000000000000000000000000000000000000000000000000"
178+
exportSignatureDer $
179+
fromMaybe (error "Signing Failed") $
180+
ecdsaSign key "0000000000000000000000000000000000000000000000000000000000000000"
181+
where
182+
key =
183+
fromMaybe (error "Invalid SecKey") . (importSecKey <=< decodeHex) $
184+
"0000000000000000000000000000000000000000000000000000000000000001"
182185

183186

184187
-- We have test vectors for these cases
@@ -201,7 +204,7 @@ validImplMap =
201204

202205

203206
getImpl :: Maybe ValidImpl
204-
getImpl = implSig `Map.lookup` validImplMap
207+
getImpl = pure ImplCore
205208

206209

207210
rfc6979files :: ValidImpl -> (FilePath, FilePath)
@@ -223,32 +226,32 @@ checkDistSig go =
223226
-- github.com/trezor/python-ecdsa/blob/master/ecdsa/test_pyecdsa.py
224227

225228
toVector :: (Text, Text, Text) -> (SecKey, ByteString, Text)
226-
toVector (prv, m, res) = (fromJust $ (secKey <=< decodeHex) prv, cs m, res)
229+
toVector (prv, m, res) = (fromJust $ (importSecKey <=< decodeHex) prv, cs m, res)
227230

228231

229232
testRFC6979Vector :: (SecKey, ByteString, Text) -> Assertion
230233
testRFC6979Vector (prv, m, res) = do
231-
assertEqual "RFC 6979 Vector" res $ encodeHex . getCompactSig $ exportCompactSig s
234+
assertEqual "RFC 6979 Vector" res $ encodeHex . exportSignatureCompact $ s
232235
assertBool "Signature is valid" $ verifyHashSig h s (derivePubKey prv)
233236
assertBool "Signature is canonical" $ testIsCanonical s
234237
assertBool "Signature is normalized" $ isCanonicalHalfOrder s
235238
where
236239
h = sha256 m
237-
s = signHash prv h
240+
s = fromMaybe (error "Signing Failed") $ signHash prv h
238241

239242

240243
-- Test vectors from:
241244
-- https://crypto.stackexchange.com/questions/20838/request-for-data-to-test-deterministic-ecdsa-signature-algorithm-for-secp256k1
242245

243246
testRFC6979DERVector :: (SecKey, ByteString, Text) -> Assertion
244247
testRFC6979DERVector (prv, m, res) = do
245-
assertEqual "RFC 6979 DER Vector" res (encodeHex $ exportSig s)
248+
assertEqual "RFC 6979 DER Vector" res (encodeHex $ exportSignatureDer s)
246249
assertBool "DER Signature is valid" $ verifyHashSig h s (derivePubKey prv)
247250
assertBool "DER Signature is canonical" $ testIsCanonical s
248251
assertBool "DER Signature is normalized" $ isCanonicalHalfOrder s
249252
where
250253
h = sha256 m
251-
s = signHash prv h
254+
s = fromMaybe (error "Signing Failed") $ signHash prv h
252255

253256

254257
-- Reproduce the P2WPKH example from BIP 143
@@ -497,7 +500,7 @@ testBip143p2shp2wpkhMulsig =
497500

498501

499502
secHexKey :: Text -> Maybe SecKey
500-
secHexKey = decodeHex >=> secKey
503+
secHexKey = decodeHex >=> importSecKey
501504

502505

503506
toPubKey :: SecKey -> PubKeyI

bitcoin-test/lib/Bitcoin/Keys/ExtendedSpec.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@ import Bitcoin.Keys (
1717
derivePath,
1818
derivePubPath,
1919
deriveXPubKey,
20-
exportPubKey,
21-
getSecKey,
20+
exportPubKeyXY,
21+
exportSecKey,
2222
getXPrvKey,
2323
getXPubKey,
2424
hardSubKey,
@@ -451,10 +451,10 @@ runVector m v = do
451451
assertBool "bip44Addr" $
452452
addrToText btc (xPubAddr $ deriveXPubKey $ derivePath bip44Addr m)
453453
== Just (v !! 3)
454-
assertBool "prvKey" $ encodeHex (getSecKey $ xPrvKey m) == v !! 4
454+
assertBool "prvKey" $ encodeHex (exportSecKey $ xPrvKey m) == v !! 4
455455
assertBool "xPrvWIF" $ xPrvWif btc m == v !! 5
456456
assertBool "pubKey" $
457-
encodeHex (exportPubKey True $ xPubKey $ deriveXPubKey m) == v !! 6
457+
encodeHex (exportPubKeyXY True $ xPubKey $ deriveXPubKey m) == v !! 6
458458
assertBool "chain code" $ encodeHex (U.encodeS $ xPrvChain m) == v !! 7
459459
assertBool "Hex PubKey" $
460460
(encodeHex . BSL.toStrict . runPut . putXPubKey btc) (deriveXPubKey m) == v !! 8

bitcoin-test/lib/Bitcoin/KeysSpec.hs

+10-10
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33

44
module Bitcoin.KeysSpec (spec) where
55

6-
import Bitcoin (getSecKey, secKey)
6+
import Bitcoin (exportSecKey, importSecKey)
77
import Bitcoin.Address (
88
addrToText,
99
addressToOutput,
@@ -147,7 +147,7 @@ testMiniKey :: Assertion
147147
testMiniKey =
148148
assertEqual "fromMiniKey" (Just res) (go "S6c56bnXQiBjk9mqSYE7ykVQ7NzrRy")
149149
where
150-
go = fmap (encodeHex . getSecKey . secKeyData) . fromMiniKey
150+
go = fmap (encodeHex . exportSecKey . secKeyData) . fromMiniKey
151151
res = "4c7a9640c72dc2099f23715d0c8a0d8a35f8906e3cab61dd3f78b67bf887c9ab"
152152

153153

@@ -161,14 +161,14 @@ testKeyIOValidVector (a, payload, obj)
161161
-- Test from WIF to SecKey
162162
let Just isComp = A.lookup "isCompressed" obj >>= getBool
163163
prvKeyM = fromWif net a
164-
prvKeyHexM = encodeHex . getSecKey . secKeyData <$> prvKeyM
164+
prvKeyHexM = encodeHex . exportSecKey . secKeyData <$> prvKeyM
165165
assertBool "Valid PrvKey" $ isJust prvKeyM
166166
assertEqual "Valid compression" (Just isComp) (secKeyCompressed <$> prvKeyM)
167167
assertEqual "WIF matches payload" (Just payload) prvKeyHexM
168168
let prvAsPubM = (eitherToMaybe . decodeOutputBS <=< decodeHex) a
169169
assertBool "PrvKey is invalid ScriptOutput" $ isNothing prvAsPubM
170170
-- Test from SecKey to WIF
171-
let secM = secKey =<< decodeHex payload
171+
let secM = importSecKey =<< decodeHex payload
172172
wifM = toWif net . wrapSecKey isComp <$> secM
173173
assertEqual "Payload matches WIF" (Just a) wifM
174174
| otherwise = do
@@ -178,7 +178,7 @@ testKeyIOValidVector (a, payload, obj)
178178
assertBool ("Valid Address " <> cs a) $ isJust addrM
179179
assertEqual "Address matches payload" (Just payload) scriptM
180180
let pubAsWifM = fromWif net a
181-
pubAsSecM = secKey =<< decodeHex a
181+
pubAsSecM = importSecKey =<< decodeHex a
182182
assertBool "Address is invalid Wif" $ isNothing pubAsWifM
183183
assertBool "Address is invalid PrvKey" $ isNothing pubAsSecM
184184
-- Test Script to Addr
@@ -203,7 +203,7 @@ testKeyIOValidVector (a, payload, obj)
203203
testKeyIOInvalidVector :: [Text] -> Assertion
204204
testKeyIOInvalidVector [a] = do
205205
let wifMs = (`fromWif` a) <$> allNets
206-
secKeyM = (secKey <=< decodeHex) a :: Maybe SecKey
206+
secKeyM = (importSecKey <=< decodeHex) a :: Maybe SecKey
207207
scriptM = (eitherToMaybe . decodeOutputBS <=< decodeHex) a :: Maybe ScriptOutput
208208
assertBool "Payload is invalid WIF" $ all isNothing wifMs
209209
assertBool "Payload is invalid SecKey" $ isNothing secKeyM
@@ -260,10 +260,10 @@ sigMsg =
260260

261261
testSignature :: Hash256 -> Assertion
262262
testSignature h = do
263-
let sign1 = signHash (secKeyData sec1) h
264-
sign2 = signHash (secKeyData sec2) h
265-
sign1C = signHash (secKeyData sec1C) h
266-
sign2C = signHash (secKeyData sec2C) h
263+
sign1 <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec1) h
264+
sign2 <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec2) h
265+
sign1C <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec1C) h
266+
sign2C <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec2C) h
267267
assertBool "Key 1, Sign1" $ verifyHashSig h sign1 (pubKeyPoint pub1)
268268
assertBool "Key 1, Sign2" $ not $ verifyHashSig h sign2 (pubKeyPoint pub1)
269269
assertBool "Key 1, Sign1C" $ verifyHashSig h sign1C (pubKeyPoint pub1)

bitcoin-test/lib/Bitcoin/Orphans.hs

+16-4
Original file line numberDiff line numberDiff line change
@@ -14,15 +14,16 @@ import Bitcoin (
1414
OutPoint (OutPoint),
1515
ParsedPath (..),
1616
PubKeyI,
17+
PubKeyXO,
1718
ScriptOutput,
19+
SecKey,
1820
SigHash (..),
1921
SigInput (SigInput),
2022
SoftPath,
2123
Tx (Tx),
2224
TxHash,
2325
TxIn (TxIn),
2426
TxOut (TxOut),
25-
XOnlyPubKey,
2627
blockHashToHex,
2728
decodeHex,
2829
decodeOutputBS,
@@ -32,6 +33,8 @@ import Bitcoin (
3233
hexBuilder,
3334
hexToBlockHash,
3435
hexToTxHash,
36+
importPubKeyXO,
37+
importSecKey,
3538
maybeToEither,
3639
parseHard,
3740
parsePath,
@@ -57,10 +60,12 @@ import Data.Aeson (
5760
import Data.Aeson.Encoding (text, unsafeToEncoding)
5861
import qualified Data.Binary as Bin
5962
import Data.ByteString.Builder (char7)
63+
import qualified Data.ByteString.Char8 as B8
6064
import qualified Data.ByteString.Lazy as BSL
6165
import Data.Maybe (maybeToList)
6266
import Data.Scientific (toBoundedInteger)
6367
import Data.String.Conversions (cs)
68+
import Test.QuickCheck
6469

6570

6671
instance FromJSON BlockHash where
@@ -345,8 +350,15 @@ instance FromJSON SigInput where
345350

346351

347352
-- | Hex encoding
348-
instance FromJSON XOnlyPubKey where
353+
instance FromJSON PubKeyXO where
349354
parseJSON =
350355
withText "XOnlyPubKey" $
351-
either fail pure
352-
. (U.decode . BSL.fromStrict <=< maybe (Left "Unable to decode hex") Right . decodeHex)
356+
maybe (fail "") pure
357+
. (importPubKeyXO <=< decodeHex)
358+
359+
360+
-- | Arbitrary
361+
instance Arbitrary SecKey where
362+
arbitrary = do
363+
bytes <- B8.pack <$> vectorOf 32 arbitrary
364+
maybe arbitrary pure (importSecKey bytes)

bitcoin-test/lib/Bitcoin/ScriptSpec.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module Bitcoin.ScriptSpec (spec) where
44

55
import Bitcoin.Address (addrToText, payToScriptAddress)
66
import Bitcoin.Constants (Network (getNetworkName), btc)
7-
import Bitcoin.Keys (derivePubKeyI, secKey, wrapSecKey)
7+
import Bitcoin.Keys (derivePubKeyI, importSecKey, wrapSecKey)
88
import Bitcoin.Orphans ()
99
import Bitcoin.Script (
1010
Script (Script),
@@ -179,7 +179,7 @@ standardSpec net = do
179179
derivePubKeyI $
180180
wrapSecKey True $
181181
fromJust $
182-
secKey $
182+
importSecKey $
183183
BS.replicate 32 1
184184
decodeInput net (Script [OP_0, opPushData $ U.encodeS pk])
185185
`shouldBe` Right (RegularInput (SpendPKHash TxSignatureEmpty pk))
@@ -225,9 +225,9 @@ scriptSpec net =
225225
"DERSIG"
226226
`isInfixOf` flags
227227
|| "STRICTENC"
228-
`isInfixOf` flags
228+
`isInfixOf` flags
229229
|| "NULLDUMMY"
230-
`isInfixOf` flags
230+
`isInfixOf` flags
231231
scriptSig = parseScript siStr
232232
scriptPubKey = parseScript soStr
233233
decodedOutput = decodeOutputBS scriptPubKey
@@ -369,8 +369,8 @@ sigHashSpec net = do
369369

370370
testSigHashOne :: Network -> Tx -> Script -> Word64 -> Bool -> Property
371371
testSigHashOne net tx s val acp =
372-
not (null $ txIn tx) ==>
373-
if length (txIn tx) > length (txOut tx)
372+
not (null $ txIn tx)
373+
==> if length (txIn tx) > length (txOut tx)
374374
then res `shouldBe` one
375375
else res `shouldNotBe` one
376376
where

0 commit comments

Comments
 (0)