Do not dependen on hardcoded DER signatures in tests

The version of libsecp256k1 provided by Fedora adds an optional algorithm
string when computing a deterministic nonce for a signature, making it
different from the signature produced by the upstream version of libsecp256k1
from the Bitcoin Core repository.
This commit is contained in:
Jean-Pierre Rupp 2020-04-10 20:40:21 +01:00
parent d5d01fc826
commit 539999933e
5 changed files with 35 additions and 40 deletions

View File

@ -4,6 +4,10 @@ All notable changes to this project will be documented in this file.
The format is based on [Keep a Changelog](http://keepachangelog.com/en/1.0.0/)
and this project adheres to [Semantic Versioning](http://semver.org/spec/v2.0.0.html).
## 0.2.1
### Changed
- Do not depend on hardcoded DER signatures in tests.
## 0.2.0
### Added
- Support for ECDH APIs.

View File

@ -1,5 +1,5 @@
name: secp256k1-haskell
version: 0.2.0
version: 0.2.1
synopsis: Bindings for secp256k1 library from Bitcoin Core
description: Sign and verify signatures using the very fast C secp256k1 library from Pieter Wuille. Has Haskell types and abstractions for keys and signatures.
category: Crypto

View File

@ -89,14 +89,12 @@ import qualified Data.ByteString.Base16 as B16
import Data.ByteString.Short (fromShort, toShort)
import Data.Hashable (Hashable (..))
import Data.Maybe (fromJust, fromMaybe, isJust)
import Data.Serialize (decode, encode)
import Data.String (IsString (..))
import Data.String.Conversions (ConvertibleStrings, cs)
import Foreign (ForeignPtr, alloca, allocaArray,
allocaBytes, mallocForeignPtr,
nullFunPtr, nullPtr, peek, poke,
pokeArray, withForeignPtr)
import Foreign.C (CInt)
nullPtr, peek, poke, pokeArray,
withForeignPtr)
import System.IO.Unsafe (unsafePerformIO)
import Test.QuickCheck (Arbitrary (..),
arbitraryBoundedRandom, suchThat)
@ -425,7 +423,7 @@ signMsg :: SecKey -> Msg -> Sig
signMsg (SecKey fk) (Msg fm) = withContext $ \ctx ->
withForeignPtr fk $ \k -> withForeignPtr fm $ \m -> do
fg <- mallocForeignPtr
ret <- withForeignPtr fg $ \g -> ecdsaSign ctx g m k nullFunPtr nullPtr
ret <- withForeignPtr fg $ \g -> ecdsaSign ctx g m k nullPtr nullPtr
unless (isSuccess ret) $ error "could not sign message"
return $ Sig fg

View File

@ -14,19 +14,23 @@ exposed for hacking and experimentation.
-}
module Crypto.Secp256k1.Internal where
import Control.DeepSeq
import Control.Monad
import Control.DeepSeq (NFData)
import Control.Monad (guard, unless)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.ByteString.Short (ShortByteString, fromShort, toShort)
import Data.Serialize (Serialize (..))
import qualified Data.Serialize.Get as Get
import qualified Data.Serialize.Put as Put
import Foreign
import Foreign.C
import Data.Void (Void)
import Foreign (ForeignPtr, FunPtr, Ptr, Storable (..),
alloca, castPtr, copyArray,
newForeignPtr, withForeignPtr)
import Foreign.C (CInt (..), CSize (..), CString, CUChar,
CUInt (..))
import GHC.Generics (Generic)
import System.Entropy
import System.IO.Unsafe
import System.Entropy (getEntropy)
import System.IO.Unsafe (unsafeDupablePerformIO, unsafePerformIO)
data Ctx = Ctx
@ -91,16 +95,6 @@ newtype SchnorrSig64 = SchnorrSig64 { getSchnorrSig64 :: ShortByteString }
deriving (Read, Show, Eq, Ord, Generic, NFData)
#endif
-- | Nonce32-generating function
type NonceFunction a
= Ptr Nonce32
-> Ptr Msg32
-> Ptr SecKey32
-> Ptr Algo16
-> Ptr a -- ^ extra data
-> CUInt -- ^ attempt
-> Ret
verify :: CtxFlags
verify = CtxFlags 0x0101
@ -158,27 +152,27 @@ instance Storable CompactSig where
alignment _ = 1
peek p = do
bs <- BS.packCStringLen (castPtr p, 64)
let (s, r) = BS.splitAt 32 bs
guard $ BS.length s == 32
let (r, s) = BS.splitAt 32 bs
guard $ BS.length r == 32
guard $ BS.length s == 32
return CompactSig { getCompactSigR = toShort r
, getCompactSigS = toShort s
}
poke p CompactSig{..} =
useByteString bs $ \(b, _) -> copyArray (castPtr p) b 64
where
bs = fromShort getCompactSigS `BS.append` fromShort getCompactSigR
bs = fromShort getCompactSigR `BS.append` fromShort getCompactSigS
instance Serialize CompactSig where
get = do
s <- Get.getByteString 32
r <- Get.getByteString 32
s <- Get.getByteString 32
return CompactSig { getCompactSigR = toShort r
, getCompactSigS = toShort s
}
put (CompactSig r s) = do
Put.putShortByteString s
Put.putShortByteString r
Put.putShortByteString s
#ifdef RECOVERY
instance Storable RecSig65 where
@ -193,7 +187,7 @@ instance Storable CompactRecSig where
alignment _ = 1
peek p = do
bs <- BS.packCStringLen (castPtr p, 65)
let (s, r) = BS.splitAt 32 $ BS.take 64 bs
let (r, s) = BS.splitAt 32 $ BS.take 64 bs
v = BS.last bs
return CompactRecSig { getCompactRecSigR = toShort r
, getCompactRecSigS = toShort s
@ -202,22 +196,22 @@ instance Storable CompactRecSig where
poke p CompactRecSig{..} =
useByteString bs $ \(b, _) -> copyArray (castPtr p) b 65
where
bs = fromShort getCompactRecSigS `BS.append`
fromShort getCompactRecSigR `BS.snoc`
bs = fromShort getCompactRecSigR `BS.append`
fromShort getCompactRecSigS `BS.snoc`
getCompactRecSigV
instance Serialize CompactRecSig where
get = do
s <- Get.getByteString 32
r <- Get.getByteString 32
s <- Get.getByteString 32
v <- Get.getWord8
return CompactRecSig { getCompactRecSigR = toShort r
, getCompactRecSigS = toShort s
, getCompactRecSigV = v
}
put (CompactRecSig r s v) = do
Put.putShortByteString s
Put.putShortByteString r
Put.putShortByteString s
Put.putWord8 v
#endif
@ -392,7 +386,7 @@ foreign import ccall
-> Ptr Sig64
-> Ptr Msg32
-> Ptr SecKey32
-> FunPtr (NonceFunction a)
-> Ptr Void
-> Ptr a -- ^ nonce data
-> IO Ret
@ -500,7 +494,7 @@ foreign import ccall
-> Ptr RecSig65
-> Ptr Msg32
-> Ptr SecKey32
-> FunPtr (NonceFunction a)
-> Ptr Void
-> Ptr a -- ^ nonce data
-> IO Ret
@ -550,7 +544,7 @@ foreign import ccall
-- TODO
-- This is actually an "extended nonce function" in the C code. So this signature is broken,
-- but we pass a nullFunPtr (and this module is Internal), so it doesn't matter right now.
-> FunPtr (NonceFunction a)
-> Ptr Void
-> Ptr a -- ^ nonce data
-> IO Ret

View File

@ -229,9 +229,7 @@ ecdsaSignTest = do
poke m msg
poke k key
ret1 <-
-- TODO:
-- ecdsaSign x s m k nonce_function_default nullPtr
ecdsaSign x s m k nullFunPtr nullPtr
ecdsaSign x s m k nullPtr nullPtr
unless (isSuccess ret1) $ error "could not sign message"
ret2 <- ecdsaSignatureSerializeDer x o ol s
unless (isSuccess ret2) $ error "could not serialize signature"
@ -247,9 +245,9 @@ ecdsaSignTest = do
return p
alloca $ \m -> alloca $ \s -> do
x <- contextCreate verify
sig <- parseDer x der
g <- parseDer x der
poke m msg
poke s sig
poke s g
ecdsaVerify x s m p
assertBool "signature matches" (isSuccess ret)
where
@ -258,6 +256,7 @@ ecdsaSignTest = do
key = SecKey32 $ toShort $ fst $ B16.decode
"f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a"
ecSecKeyVerifyTest :: Assertion
ecSecKeyVerifyTest = do
ret <- liftIO $ alloca $ \k -> do