secp256k1

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

commit 7bef37114b040f1a374d308e7520678300eca6f8
parent 164cc1dd9d5a0a3f58a38ba922856afe4b25cbea
Author: Jared Tobin <jared@jtobin.io>
Date:   Thu, 10 Oct 2024 09:11:42 +0400

test: all wycheproof vectors passing

Diffstat:
Mlib/Crypto/Curve/Secp256k1.hs | 31++++++++++++++++++-------------
Mtest/Main.hs | 24+++++++++++++-----------
Mtest/Wycheproof.hs | 6++++++
3 files changed, 37 insertions(+), 24 deletions(-)

diff --git a/lib/Crypto/Curve/Secp256k1.hs b/lib/Crypto/Curve/Secp256k1.hs @@ -19,13 +19,13 @@ module Crypto.Curve.Secp256k1 ( , mul_safe , parse_point - , roll -- XX don't export - , unroll -- XX don't export , ECDSA(..) + , SigType(..) , sign - , sign_unrestricted , verify + , sign_unrestricted + , verify_unrestricted ) where import Control.Monad (when) @@ -572,8 +572,8 @@ low (ECDSA r s) = ECDSA r ms where {-# INLINE low #-} -- SEC1-v2 4.1.4 -verify :: BS.ByteString -> Projective -> ECDSA -> Bool -verify m p (ECDSA r s) +verify_unrestricted :: BS.ByteString -> Projective -> ECDSA -> Bool +verify_unrestricted m p (ECDSA r s) | not (ge r) || not (ge s) = False | otherwise = let e = modQ (bits2int h) @@ -590,12 +590,17 @@ verify m p (ECDSA r s) where h = SHA256.hash m --- XX test - -test_h1 :: BS.ByteString -test_h1 = B16.decodeLenient - "AF2BDBE1AA9B6EC1E2ADE1D694F41FC71A831D0268E9891562113D8A62ADD1BF" - -test_x :: Integer -test_x = 0x09A4D6792295A7F730FC3F2B49CBC0F62E862272F +verify :: BS.ByteString -> Projective -> ECDSA -> Bool +verify m p sig@(ECDSA _ s) + | s > B.unsafeShiftR _CURVE_Q 1 = False + | otherwise = verify_unrestricted m p sig +-- -- XX test +-- +-- test_h1 :: BS.ByteString +-- test_h1 = B16.decodeLenient +-- "AF2BDBE1AA9B6EC1E2ADE1D694F41FC71A831D0268E9891562113D8A62ADD1BF" +-- +-- test_x :: Integer +-- test_x = 0x09A4D6792295A7F730FC3F2B49CBC0F62E862272F +-- diff --git a/test/Main.hs b/test/Main.hs @@ -35,30 +35,32 @@ main = do Nothing -> error "couldn't parse wycheproof vectors" Just (w0, w1) -> defaultMain $ testGroup "ppad-secp256k1" [ units - , wycheproof_tests "(ecdsa, sha256)" w0 - -- , wycheproof_tests "(ecdsa, sha256, bitcoin)" w1 + , wycheproof_ecdsa_verify_tests "(ecdsa, sha256)" Unrestricted w0 + , wycheproof_ecdsa_verify_tests "(ecdsa, sha256, bitcoin)" LowS w1 ] -wycheproof_tests :: String -> W.Wycheproof -> TestTree -wycheproof_tests msg W.Wycheproof {..} = +wycheproof_ecdsa_verify_tests :: String -> SigType -> W.Wycheproof -> TestTree +wycheproof_ecdsa_verify_tests msg ty W.Wycheproof {..} = testGroup ("wycheproof vectors " <> msg) $ - fmap execute_group wp_testGroups + fmap (execute_group ty) wp_testGroups -execute_group :: W.EcdsaTestGroup -> TestTree -execute_group W.EcdsaTestGroup {..} = - testGroup msg (fmap (execute pk_uncompressed) etg_tests) +execute_group :: SigType -> W.EcdsaTestGroup -> TestTree +execute_group ty W.EcdsaTestGroup {..} = + testGroup msg (fmap (execute ty pk_uncompressed) etg_tests) where msg = mempty W.PublicKey {..} = etg_publicKey -execute :: Projective -> W.EcdsaVerifyTest -> TestTree -execute pub W.EcdsaVerifyTest {..} = testCase report $ do +execute :: SigType -> Projective -> W.EcdsaVerifyTest -> TestTree +execute ty pub W.EcdsaVerifyTest {..} = testCase report $ do let msg = B16.decodeLenient (TE.encodeUtf8 t_msg) sig = W.toEcdsa t_sig case sig of Left _ -> assertBool mempty (t_result == "invalid") Right s -> do - let ver = verify msg pub s + let ver = case ty of + LowS -> verify msg pub s + Unrestricted -> verify_unrestricted msg pub s if t_result == "invalid" then assertBool mempty (not ver) else assertBool mempty ver diff --git a/test/Wycheproof.hs b/test/Wycheproof.hs @@ -22,11 +22,17 @@ import qualified Data.ByteString as BS import qualified Data.ByteString.Base16 as B16 import qualified Data.Text as T import qualified Data.Text.Encoding as TE +import qualified GHC.Num.Integer as I fi :: (Integral a, Num b) => a -> b fi = fromIntegral {-# INLINE fi #-} +-- 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_der_sig :: AT.Parser ECDSA parse_der_sig = do _ <- AT.word8 0x30