Skip to content

Commit

Permalink
change secp256k1-haskell to libsecp256k1
Browse files Browse the repository at this point in the history
  • Loading branch information
ProofOfKeags committed May 3, 2024
1 parent 49da0f3 commit c23d0a3
Show file tree
Hide file tree
Showing 22 changed files with 205 additions and 231 deletions.
4 changes: 2 additions & 2 deletions bitcoin-test/bitcoin-test.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -78,9 +78,9 @@ library
, bytestring >=0.10.10.0
, containers >=0.6.2.1
, hspec >=2.7.1
, libsecp256k1 >=0.2.0
, memory >=0.15.0
, scientific >=0.3.6.2
, secp256k1-haskell >=0.4.0
, string-conversions >=0.4.0.1
, text >=1.2.3.0
, time >=1.9.3
Expand All @@ -107,9 +107,9 @@ test-suite spec
, bytestring >=0.10.10.0
, containers >=0.6.2.1
, hspec >=2.7.1
, libsecp256k1 >=0.2.0
, memory >=0.15.0
, scientific >=0.3.6.2
, secp256k1-haskell >=0.4.0
, string-conversions >=0.4.0.1
, text >=1.2.3.0
, time >=1.9.3
Expand Down
49 changes: 26 additions & 23 deletions bitcoin-test/lib/Bitcoin/Crypto/SignatureSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,27 +2,27 @@

module Bitcoin.Crypto.SignatureSpec (spec) where

import Bitcoin (getCompactSig)
import Bitcoin (exportSignatureCompact)
import Bitcoin.Address (
Address (WitnessPubKeyAddress),
pubKeyWitnessAddr,
)
import Bitcoin.Constants (btc)
import Bitcoin.Crypto (
SecKey,
Sig,
Signature,
decodeStrictSig,
derivePubKey,
exportCompactSig,
exportSig,
ecdsaSign,
exportSignatureCompact,
exportSignatureDer,
getSig,
importSig,
importSecKey,
importSignatureDer,
isCanonicalHalfOrder,
putSig,
secKey,
sha256,
signHash,
signMsg,
verifyHashSig,
)
import Bitcoin.Keys (PubKeyI, derivePubKeyI, wrapSecKey)
Expand Down Expand Up @@ -53,7 +53,7 @@ import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust)
import Data.Maybe (fromJust, fromMaybe)
import Data.String.Conversions (cs)
import Data.Text (Text)
import Test.HUnit (
Expand Down Expand Up @@ -81,10 +81,10 @@ spec = do
testIsCanonical . lst3
prop "decodeStrictSig . exportSig identity" $
forAll arbitrarySignature $
(\s -> decodeStrictSig (exportSig s) == Just s) . lst3
(\s -> decodeStrictSig (exportSignatureDer s) == Just s) . lst3
prop "importSig . exportSig identity" $
forAll arbitrarySignature $
(\s -> importSig (exportSig s) == Just s) . lst3
(\s -> importSignatureDer (exportSignatureDer s) == Just s) . lst3
prop "getSig . putSig identity" $
forAll arbitrarySignature $ \(_, _, s) ->
(U.runGet getSig . runPut . putSig) s == Right s
Expand All @@ -105,7 +105,7 @@ spec = do

-- github.com/bitcoin/bitcoin/blob/master/src/script.cpp
-- from function IsCanonicalSignature
testIsCanonical :: Sig -> Bool
testIsCanonical :: Signature -> Bool
testIsCanonical sig =
not $
-- Non-canonical signature: too short
Expand Down Expand Up @@ -156,7 +156,7 @@ testIsCanonical sig =
&& not (testBit (BS.index s (fromIntegral rlen + 7)) 7)
)
where
s = exportSig sig
s = exportSignatureDer sig
len = fromIntegral $ BS.length s
rlen = BS.index s 3
slen = BS.index s (fromIntegral rlen + 5)
Expand All @@ -175,10 +175,13 @@ data ValidImpl
implSig :: Text
implSig =
encodeHex $
exportSig $
signMsg
"0000000000000000000000000000000000000000000000000000000000000001"
"0000000000000000000000000000000000000000000000000000000000000000"
exportSignatureDer $
fromMaybe (error "Signing Failed") $
ecdsaSign key "0000000000000000000000000000000000000000000000000000000000000000"
where
key =
fromMaybe (error "Invalid SecKey") . (importSecKey <=< decodeHex) $
"0000000000000000000000000000000000000000000000000000000000000001"


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


getImpl :: Maybe ValidImpl
getImpl = implSig `Map.lookup` validImplMap
getImpl = pure ImplCore


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

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


testRFC6979Vector :: (SecKey, ByteString, Text) -> Assertion
testRFC6979Vector (prv, m, res) = do
assertEqual "RFC 6979 Vector" res $ encodeHex . getCompactSig $ exportCompactSig s
assertEqual "RFC 6979 Vector" res $ encodeHex . exportSignatureCompact $ s
assertBool "Signature is valid" $ verifyHashSig h s (derivePubKey prv)
assertBool "Signature is canonical" $ testIsCanonical s
assertBool "Signature is normalized" $ isCanonicalHalfOrder s
where
h = sha256 m
s = signHash prv h
s = fromMaybe (error "Signing Failed") $ signHash prv h


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

testRFC6979DERVector :: (SecKey, ByteString, Text) -> Assertion
testRFC6979DERVector (prv, m, res) = do
assertEqual "RFC 6979 DER Vector" res (encodeHex $ exportSig s)
assertEqual "RFC 6979 DER Vector" res (encodeHex $ exportSignatureDer s)
assertBool "DER Signature is valid" $ verifyHashSig h s (derivePubKey prv)
assertBool "DER Signature is canonical" $ testIsCanonical s
assertBool "DER Signature is normalized" $ isCanonicalHalfOrder s
where
h = sha256 m
s = signHash prv h
s = fromMaybe (error "Signing Failed") $ signHash prv h


-- Reproduce the P2WPKH example from BIP 143
Expand Down Expand Up @@ -497,7 +500,7 @@ testBip143p2shp2wpkhMulsig =


secHexKey :: Text -> Maybe SecKey
secHexKey = decodeHex >=> secKey
secHexKey = decodeHex >=> importSecKey


toPubKey :: SecKey -> PubKeyI
Expand Down
8 changes: 4 additions & 4 deletions bitcoin-test/lib/Bitcoin/Keys/ExtendedSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,8 @@ import Bitcoin.Keys (
derivePath,
derivePubPath,
deriveXPubKey,
exportPubKey,
getSecKey,
exportPubKeyXY,
exportSecKey,
getXPrvKey,
getXPubKey,
hardSubKey,
Expand Down Expand Up @@ -451,10 +451,10 @@ runVector m v = do
assertBool "bip44Addr" $
addrToText btc (xPubAddr $ deriveXPubKey $ derivePath bip44Addr m)
== Just (v !! 3)
assertBool "prvKey" $ encodeHex (getSecKey $ xPrvKey m) == v !! 4
assertBool "prvKey" $ encodeHex (exportSecKey $ xPrvKey m) == v !! 4
assertBool "xPrvWIF" $ xPrvWif btc m == v !! 5
assertBool "pubKey" $
encodeHex (exportPubKey True $ xPubKey $ deriveXPubKey m) == v !! 6
encodeHex (exportPubKeyXY True $ xPubKey $ deriveXPubKey m) == v !! 6
assertBool "chain code" $ encodeHex (U.encodeS $ xPrvChain m) == v !! 7
assertBool "Hex PubKey" $
(encodeHex . BSL.toStrict . runPut . putXPubKey btc) (deriveXPubKey m) == v !! 8
Expand Down
20 changes: 10 additions & 10 deletions bitcoin-test/lib/Bitcoin/KeysSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

module Bitcoin.KeysSpec (spec) where

import Bitcoin (getSecKey, secKey)
import Bitcoin (exportSecKey, importSecKey)
import Bitcoin.Address (
addrToText,
addressToOutput,
Expand Down Expand Up @@ -147,7 +147,7 @@ testMiniKey :: Assertion
testMiniKey =
assertEqual "fromMiniKey" (Just res) (go "S6c56bnXQiBjk9mqSYE7ykVQ7NzrRy")
where
go = fmap (encodeHex . getSecKey . secKeyData) . fromMiniKey
go = fmap (encodeHex . exportSecKey . secKeyData) . fromMiniKey
res = "4c7a9640c72dc2099f23715d0c8a0d8a35f8906e3cab61dd3f78b67bf887c9ab"


Expand All @@ -161,14 +161,14 @@ testKeyIOValidVector (a, payload, obj)
-- Test from WIF to SecKey
let Just isComp = A.lookup "isCompressed" obj >>= getBool
prvKeyM = fromWif net a
prvKeyHexM = encodeHex . getSecKey . secKeyData <$> prvKeyM
prvKeyHexM = encodeHex . exportSecKey . secKeyData <$> prvKeyM
assertBool "Valid PrvKey" $ isJust prvKeyM
assertEqual "Valid compression" (Just isComp) (secKeyCompressed <$> prvKeyM)
assertEqual "WIF matches payload" (Just payload) prvKeyHexM
let prvAsPubM = (eitherToMaybe . decodeOutputBS <=< decodeHex) a
assertBool "PrvKey is invalid ScriptOutput" $ isNothing prvAsPubM
-- Test from SecKey to WIF
let secM = secKey =<< decodeHex payload
let secM = importSecKey =<< decodeHex payload
wifM = toWif net . wrapSecKey isComp <$> secM
assertEqual "Payload matches WIF" (Just a) wifM
| otherwise = do
Expand All @@ -178,7 +178,7 @@ testKeyIOValidVector (a, payload, obj)
assertBool ("Valid Address " <> cs a) $ isJust addrM
assertEqual "Address matches payload" (Just payload) scriptM
let pubAsWifM = fromWif net a
pubAsSecM = secKey =<< decodeHex a
pubAsSecM = importSecKey =<< decodeHex a
assertBool "Address is invalid Wif" $ isNothing pubAsWifM
assertBool "Address is invalid PrvKey" $ isNothing pubAsSecM
-- Test Script to Addr
Expand All @@ -203,7 +203,7 @@ testKeyIOValidVector (a, payload, obj)
testKeyIOInvalidVector :: [Text] -> Assertion
testKeyIOInvalidVector [a] = do
let wifMs = (`fromWif` a) <$> allNets
secKeyM = (secKey <=< decodeHex) a :: Maybe SecKey
secKeyM = (importSecKey <=< decodeHex) a :: Maybe SecKey
scriptM = (eitherToMaybe . decodeOutputBS <=< decodeHex) a :: Maybe ScriptOutput
assertBool "Payload is invalid WIF" $ all isNothing wifMs
assertBool "Payload is invalid SecKey" $ isNothing secKeyM
Expand Down Expand Up @@ -260,10 +260,10 @@ sigMsg =

testSignature :: Hash256 -> Assertion
testSignature h = do
let sign1 = signHash (secKeyData sec1) h
sign2 = signHash (secKeyData sec2) h
sign1C = signHash (secKeyData sec1C) h
sign2C = signHash (secKeyData sec2C) h
sign1 <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec1) h
sign2 <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec2) h
sign1C <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec1C) h
sign2C <- maybe (assertFailure "Signing Failed") pure $ signHash (secKeyData sec2C) h
assertBool "Key 1, Sign1" $ verifyHashSig h sign1 (pubKeyPoint pub1)
assertBool "Key 1, Sign2" $ not $ verifyHashSig h sign2 (pubKeyPoint pub1)
assertBool "Key 1, Sign1C" $ verifyHashSig h sign1C (pubKeyPoint pub1)
Expand Down
20 changes: 16 additions & 4 deletions bitcoin-test/lib/Bitcoin/Orphans.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,15 +14,16 @@ import Bitcoin (
OutPoint (OutPoint),
ParsedPath (..),
PubKeyI,
PubKeyXO,
ScriptOutput,
SecKey,
SigHash (..),
SigInput (SigInput),
SoftPath,
Tx (Tx),
TxHash,
TxIn (TxIn),
TxOut (TxOut),
XOnlyPubKey,
blockHashToHex,
decodeHex,
decodeOutputBS,
Expand All @@ -32,6 +33,8 @@ import Bitcoin (
hexBuilder,
hexToBlockHash,
hexToTxHash,
importPubKeyXO,
importSecKey,
maybeToEither,
parseHard,
parsePath,
Expand All @@ -57,10 +60,12 @@ import Data.Aeson (
import Data.Aeson.Encoding (text, unsafeToEncoding)
import qualified Data.Binary as Bin
import Data.ByteString.Builder (char7)
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as BSL
import Data.Maybe (maybeToList)
import Data.Scientific (toBoundedInteger)
import Data.String.Conversions (cs)
import Test.QuickCheck


instance FromJSON BlockHash where
Expand Down Expand Up @@ -345,8 +350,15 @@ instance FromJSON SigInput where


-- | Hex encoding
instance FromJSON XOnlyPubKey where
instance FromJSON PubKeyXO where
parseJSON =
withText "XOnlyPubKey" $
either fail pure
. (U.decode . BSL.fromStrict <=< maybe (Left "Unable to decode hex") Right . decodeHex)
maybe (fail "") pure
. (importPubKeyXO <=< decodeHex)


-- | Arbitrary
instance Arbitrary SecKey where
arbitrary = do
bytes <- B8.pack <$> vectorOf 32 arbitrary
maybe arbitrary pure (importSecKey bytes)
12 changes: 6 additions & 6 deletions bitcoin-test/lib/Bitcoin/ScriptSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Bitcoin.ScriptSpec (spec) where

import Bitcoin.Address (addrToText, payToScriptAddress)
import Bitcoin.Constants (Network (getNetworkName), btc)
import Bitcoin.Keys (derivePubKeyI, secKey, wrapSecKey)
import Bitcoin.Keys (derivePubKeyI, importSecKey, wrapSecKey)
import Bitcoin.Orphans ()
import Bitcoin.Script (
Script (Script),
Expand Down Expand Up @@ -179,7 +179,7 @@ standardSpec net = do
derivePubKeyI $
wrapSecKey True $
fromJust $
secKey $
importSecKey $
BS.replicate 32 1
decodeInput net (Script [OP_0, opPushData $ U.encodeS pk])
`shouldBe` Right (RegularInput (SpendPKHash TxSignatureEmpty pk))
Expand Down Expand Up @@ -225,9 +225,9 @@ scriptSpec net =
"DERSIG"
`isInfixOf` flags
|| "STRICTENC"
`isInfixOf` flags
`isInfixOf` flags
|| "NULLDUMMY"
`isInfixOf` flags
`isInfixOf` flags
scriptSig = parseScript siStr
scriptPubKey = parseScript soStr
decodedOutput = decodeOutputBS scriptPubKey
Expand Down Expand Up @@ -369,8 +369,8 @@ sigHashSpec net = do

testSigHashOne :: Network -> Tx -> Script -> Word64 -> Bool -> Property
testSigHashOne net tx s val acp =
not (null $ txIn tx) ==>
if length (txIn tx) > length (txOut tx)
not (null $ txIn tx)
==> if length (txIn tx) > length (txOut tx)
then res `shouldBe` one
else res `shouldNotBe` one
where
Expand Down

0 comments on commit c23d0a3

Please sign in to comment.