secp256k1

Pure Haskell cryptographic primitives on the secp256k1 elliptic curve.
git clone git://git.ppad.tech/secp256k1.git
Log | Files | Refs | LICENSE

commit 11ffcc37cc137834f9d8eb1a0c67076dd2da68e6
parent bd500270efe9a96fd477fa192b9abfc4c786647c
Author: Jared Tobin <jared@jtobin.io>
Date:   Thu, 10 Oct 2024 16:52:15 +0400

test: improve messages

Diffstat:
Mtest/Noble.hs | 54++++++++++++++++++++++++++----------------------------
Mtest/Wycheproof.hs | 11+----------
2 files changed, 27 insertions(+), 38 deletions(-)

diff --git a/test/Noble.hs b/test/Noble.hs @@ -5,10 +5,6 @@ module Noble ( Ecdsa(..) , execute_ecdsa - , execute_valid - - , parse_compact - , roll -- uh ) where import Crypto.Curve.Secp256k1 @@ -22,32 +18,48 @@ import qualified GHC.Num.Integer as I import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (assertEqual, testCase) +data Ecdsa = Ecdsa { + ec_valid :: ![(Int, ValidTest)] + , ec_invalid :: !InvalidTest + } deriving Show + +-- XX run noble's invalid suites +execute_ecdsa :: Ecdsa -> TestTree +execute_ecdsa Ecdsa {..} = testGroup "noble_ecdsa" [ + testGroup "valid" (fmap execute_valid ec_valid) + ] + +execute_valid :: (Int, ValidTest) -> TestTree +execute_valid (label, ValidTest {..}) = + testCase ("noble-secp256k1, valid (" <> show label <> ")") $ do + let msg = vt_m + x = vt_d + pec = parse_compact vt_signature + sig = _sign_no_hash x msg + assertEqual mempty pec sig + fi :: (Integral a, Num b) => a -> b fi = fromIntegral {-# INLINE fi #-} +-- parser helper toBS :: T.Text -> BS.ByteString toBS = B16.decodeLenient . TE.encodeUtf8 +-- parser helper toSecKey :: T.Text -> Integer toSecKey = roll . toBS -data Ecdsa = Ecdsa { - ec_valid :: ![(Int, ValidTest)] - , ec_invalid :: !InvalidTest - } deriving Show +-- big-endian bytestring decoding +roll :: BS.ByteString -> Integer +roll = BS.foldl' unstep 0 where + unstep a (fi -> b) = (a `I.integerShiftL` 8) `I.integerOr` b instance A.FromJSON Ecdsa where parseJSON = A.withObject "Ecdsa" $ \m -> Ecdsa <$> fmap (zip [0..]) (m .: "valid") <*> m .: "invalid" --- XX run noble's invalid suites -execute_ecdsa :: Ecdsa -> TestTree -execute_ecdsa Ecdsa {..} = testGroup "noble_ecdsa" [ - testGroup "valid" (fmap execute_valid ec_valid) - ] - data ValidTest = ValidTest { vt_d :: !Integer , vt_m :: !BS.ByteString @@ -60,25 +72,11 @@ instance A.FromJSON ValidTest where <*> fmap toBS (m .: "m") <*> fmap toBS (m .: "signature") --- big-endian bytestring decoding -roll :: BS.ByteString -> Integer -roll = BS.foldl' unstep 0 where - unstep a (fi -> b) = (a `I.integerShiftL` 8) `I.integerOr` b - parse_compact :: BS.ByteString -> ECDSA parse_compact bs = let (roll -> r, roll -> s) = BS.splitAt 32 bs in ECDSA r s -execute_valid :: (Int, ValidTest) -> TestTree -execute_valid (label, ValidTest {..}) = - testCase ("noble-secp256k1, valid (" <> show label <> ")") $ do - let msg = vt_m - x = vt_d - pec = parse_compact vt_signature - sig = _sign_no_hash x msg - assertEqual mempty pec sig - data InvalidTest = InvalidTest { iv_sign :: ![InvalidSignTest] , iv_verify :: ![InvalidVerifyTest] diff --git a/test/Wycheproof.hs b/test/Wycheproof.hs @@ -5,15 +5,6 @@ module Wycheproof ( Wycheproof(..) - , EcdsaTestGroup(..) - , PublicKey(..) - , EcdsaVerifyTest(..) - - , parse_der_sig - , toProjective - , toEcdsa - - , execute , execute_group ) where @@ -43,7 +34,7 @@ execute_group :: SigType -> EcdsaTestGroup -> TestTree execute_group ty EcdsaTestGroup {..} = testGroup msg (fmap (execute ty pk_uncompressed) etg_tests) where - msg = mempty + msg = "wycheproof (" <> T.unpack etg_type <> ", " <> T.unpack etg_sha <> ")" PublicKey {..} = etg_publicKey execute :: SigType -> Projective -> EcdsaVerifyTest -> TestTree