{-# LANGUAGE OverloadedStrings #-} module Crypto.Secp256k1.Internal.Tests (tests) where import Control.Monad import Control.Monad.Trans import Crypto.Secp256k1.Internal import Data.ByteString (packCStringLen, useAsCStringLen) import qualified Data.ByteString.Base16 as B16 import Foreign import System.Entropy import Test.Framework (Test, testGroup) import Test.Framework.Providers.HUnit (testCase) import Test.HUnit (Assertion, assertBool, assertEqual) tests :: [Test] tests = [ testGroup "Housekeeping" [ testCase "Create context" create_context_test , testCase "Randomize context" randomize_context_test , testCase "Clone context" clone_context_test -- TODO: -- , testCase "Set illegal callback" set_illegal_callback_test -- TODO: -- , testCase "Set error callback" set_error_callback_test ] , testGroup "Serialization" [ testCase "Parse public key" ec_pubkey_parse_test , testCase "Serialize public key" ec_pubkey_serialize_test , testCase "Storable public key" pubkey_storable_test , testCase "Parse DER signature" ecdsa_signature_parse_der_test , testCase "Serialize DER signature" ecdsa_signature_serialize_der_test ] , testGroup "Signatures" [ testCase "ECDSA verify" ecdsa_verify_test -- TODO: -- , testCase "RFC6979 nonce function" nonce_function_rfc6979_test , testCase "ECDSA sign" ecdsa_sign_test ] , testGroup "Secret keys" [ testCase "Verify secret key" ec_seckey_verify_test , testCase "Create public key" ec_pubkey_create_test , testCase "Serialize BER secret key" ec_privkey_export_test , testCase "Import BER secret key" ec_privkey_import_test , testCase "Tweak add secret key" ec_privkey_tweak_add_test , testCase "Tweak mult. secret key" ec_privkey_tweak_mul_test ] , testGroup "Public keys" [ testCase "Tweak add public key" ec_pubkey_tweak_add_test , testCase "Tweak mult. public key" ec_pubkey_tweak_mul_test , testCase "Combine public keys" ec_pubkey_combine_test ] ] withEntropy :: (Ptr Seed32 -> IO a) -> IO a withEntropy f = getEntropy 32 >>= \e -> alloca $ \s -> poke s (Seed32 e) >> f s create_context_test :: Assertion create_context_test = do context_ptr <- liftIO $ context_create signVerify assertBool "context not null" $ context_ptr /= nullPtr randomize_context_test :: Assertion randomize_context_test = do ret <- liftIO $ context_create sign >>= \x -> withEntropy (context_randomize x) assertBool "context randomized" $ isSuccess ret clone_context_test :: Assertion clone_context_test = do (x1, x2) <- liftIO $ do x1 <- context_create signVerify ret <- withEntropy $ context_randomize x1 unless (isSuccess ret) $ error "failed to randomize context" x2 <- context_clone(x1) return (x1, x2) assertBool "original context not null" $ x1 /= nullPtr assertBool "cloned context not null" $ x2 /= nullPtr assertBool "context ptrs different" $ x1 /= x2 ec_pubkey_parse_test :: Assertion ec_pubkey_parse_test = do ret <- liftIO $ useAsCStringLen der $ \(i, il) -> do x <- context_create verify alloca $ \pubkey -> ec_pubkey_parse x pubkey (castPtr i) (fromIntegral il) assertBool "parsed public key" (isSuccess ret) where der = fst $ B16.decode "03dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd44705" ec_pubkey_serialize_test :: Assertion ec_pubkey_serialize_test = do (ret, dec) <- liftIO $ useAsCStringLen der $ \(i, il) -> alloca $ \k -> alloca $ \ol -> allocaBytes 72 $ \o -> do poke ol 72 x <- context_create verify ret1 <- ec_pubkey_parse x k (castPtr i) (fromIntegral il) unless (isSuccess ret1) $ error "failed to parse pubkey" ret2 <- ec_pubkey_serialize x o ol k compressed len <- fromIntegral <$> peek ol decoded <- packCStringLen (castPtr o, len) return (ret2, decoded) assertBool "serialized public key successfully" $ isSuccess ret assertEqual "public key matches" der dec where der = fst $ B16.decode "03dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd44705" pubkey_storable_test :: Assertion pubkey_storable_test = do (pk1, pk2, dec) <- liftIO $ useAsCStringLen der $ \(i, il) -> do x <- context_create verify pk1 <- alloca $ \pk -> do ret <- ec_pubkey_parse x pk (castPtr i) (fromIntegral il) unless (isSuccess ret) $ error "failed to parse pubkey" peek pk (pk2, dec) <- alloca $ \pk -> alloca $ \ol -> allocaBytes 72 $ \o -> do poke ol 72 poke pk pk1 ret <- ec_pubkey_serialize x o ol pk compressed unless (isSuccess ret) $ error "failed to serialize pubkey" len <- fromIntegral <$> peek ol dec <- packCStringLen (castPtr o, len) pk2 <- peek pk return (pk2, dec) return (pk1, pk2, dec) assertEqual "poke/peek public key" pk1 pk2 assertEqual "public key matches" der dec where der = fst $ B16.decode "03dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd44705" ecdsa_signature_parse_der_test :: Assertion ecdsa_signature_parse_der_test = do ret <- liftIO $ useAsCStringLen der $ \(d, dl) -> alloca $ \s -> do x <- context_create verify ecdsa_signature_parse_der x s (castPtr d) (fromIntegral dl) assertBool "parsed signature successfully" $ isSuccess ret where der = fst $ B16.decode $ "3045022100f502bfa07af43e7ef265618b0d929a7619ee01d6150e37eb6eaaf2c8bd37\ \fb2202206f0415ab0e9a977afd78b2c26ef39b3952096d319fd4b101c768ad6c132e30\ \45" ecdsa_signature_serialize_der_test :: Assertion ecdsa_signature_serialize_der_test = do (ret, enc) <- liftIO $ do x <- context_create verify sig <- useAsCStringLen der $ \(d, dl) -> alloca $ \s -> do ret <- ecdsa_signature_parse_der x s (castPtr d) (fromIntegral dl) unless (isSuccess ret) $ error "could not parse DER" peek s alloca $ \s -> alloca $ \ol -> allocaBytes 72 $ \o -> do poke ol 72 poke s sig ret <- ecdsa_signature_serialize_der x o ol s len <- fromIntegral <$> peek ol enc <- packCStringLen (castPtr o, len) return (ret, enc) assertBool "serialization successful" $ isSuccess ret assertEqual "signatures match" der enc where der = fst $ B16.decode $ "3045022100f502bfa07af43e7ef265618b0d929a7619ee01d6150e37eb6eaaf2c8bd37\ \fb2202206f0415ab0e9a977afd78b2c26ef39b3952096d319fd4b101c768ad6c132e30\ \45" ecdsa_verify_test :: Assertion ecdsa_verify_test = do ret <- liftIO $ do x <- context_create verify sig <- useAsCStringLen der $ \(d, dl) -> alloca $ \s -> do ret <- ecdsa_signature_parse_der x s (castPtr d) (fromIntegral dl) unless (isSuccess ret) $ error "could not parse DER" peek s pk <- useAsCStringLen pub $ \(p, pl) -> alloca $ \k -> do ret <- ec_pubkey_parse x k (castPtr p) (fromIntegral pl) unless (isSuccess ret) $ error "could not parse public key" peek k alloca $ \m -> alloca $ \k -> alloca $ \s -> do poke m msg poke k pk poke s sig ecdsa_verify x s m k assertBool "signature valid" $ isSuccess ret where der = fst $ B16.decode $ "3045022100f502bfa07af43e7ef265618b0d929a7619ee01d6150e37eb6eaaf2c8bd37\ \fb2202206f0415ab0e9a977afd78b2c26ef39b3952096d319fd4b101c768ad6c132e30\ \45" pub = fst $ B16.decode $ "04dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd447051221\ \3d5ed790522c042dee8e85c4c0ec5f96800b72bc5940c8bc1c5e11e4fcbf" msg = Msg32 $ fst $ B16.decode $ "f5cbe7d88182a4b8e400f96b06128921864a18187d114c8ae8541b566c8ace00" -- TODO: -- nonce_function_rfc6979_test :: Assertion -- nonce_function_rfc6979_test = do -- (ret, nonce) <- alloca $ \n -> alloca $ \m -> alloca $ \k -> do -- poke m msg -- poke k key -- let ret = mkNonceFunction -- nonce_function_rfc6979 n m k nullPtr nullPtr 0 -- nonce <- peek n -- return (ret, nonce) -- assertBool "nonce calculated" $ isSuccess ret -- assertEqual "nonce correct" expected nonce -- where -- msg = Msg32 $ fst $ B16.decode $ -- "f5cbe7d88182a4b8e400f96b06128921864a18187d114c8ae8541b566c8ace00" -- key = SecKey32 $ fst $ B16.decode $ -- "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" -- expected = Nonce $ fst $ B16.decode $ -- "8f30c2bf5a3e1199b19a6703fa578376e5225d6ecfc7ecf817aa8b8b16203d64" ecdsa_sign_test :: Assertion ecdsa_sign_test = do (ret, sig) <- liftIO $ do x <- context_create sign retr <- withEntropy $ context_randomize x unless (isSuccess retr) $ error "failed to randomize context" alloca $ \s -> alloca $ \m -> alloca $ \k -> alloca $ \ol -> allocaBytes 72 $ \o -> do poke ol 72 poke m msg poke k key ret1 <- -- TODO: -- ecdsa_sign x s m k nonce_function_default nullPtr ecdsa_sign x s m k nullFunPtr nullPtr ret2 <- ecdsa_signature_serialize_der x o ol s unless (isSuccess ret2) $error "could not serialize signature" len <- peek ol sig <- packCStringLen (castPtr o, fromIntegral len) return (ret1, sig) assertBool "successful signing" $ isSuccess ret assertEqual "signature matches" sig der where msg = Msg32 $ fst $ B16.decode $ "f5cbe7d88182a4b8e400f96b06128921864a18187d114c8ae8541b566c8ace00" key = SecKey32 $ fst $ B16.decode $ "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" der = fst $ B16.decode $ "3045022100f502bfa07af43e7ef265618b0d929a7619ee01d6150e37eb6eaaf2c8bd37\ \fb2202206f0415ab0e9a977afd78b2c26ef39b3952096d319fd4b101c768ad6c132e30\ \45" ec_seckey_verify_test :: Assertion ec_seckey_verify_test = do ret <- liftIO $ alloca $ \k -> do poke k key x <- context_create sign retr <- withEntropy $ context_randomize x unless (isSuccess retr) $ error "failed to randomize context" ec_seckey_verify x k assertBool "valid secret key" $ isSuccess ret where key = SecKey32 $ fst $ B16.decode $ "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" ec_pubkey_create_test :: Assertion ec_pubkey_create_test = do (ret, pk) <- liftIO $ alloca $ \p -> alloca $ \k -> do poke k key x <- context_create sign retr <- withEntropy $ context_randomize x unless (isSuccess retr) $ error "failed to randomize context" ret <- ec_pubkey_create x p k allocaBytes 65 $ \o -> alloca $ \ol -> do poke ol 65 rets <- ec_pubkey_serialize x o ol p uncompressed unless (isSuccess rets) $ error "failed to serialive public key" len <- fromIntegral <$> peek ol pk <- packCStringLen (castPtr o, len) return (ret, pk) assertBool "successful pubkey creation" $ isSuccess ret assertEqual "public key matches" pub pk where key = SecKey32 $ fst $ B16.decode $ "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" pub = fst $ B16.decode $ "04dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd447051221\ \3d5ed790522c042dee8e85c4c0ec5f96800b72bc5940c8bc1c5e11e4fcbf" ec_privkey_export_test :: Assertion ec_privkey_export_test = do ret <- liftIO $ alloca $ \k -> allocaBytes 279 $ \o -> alloca $ \ol -> do poke ol 279 poke k key x <- context_create sign retr <- withEntropy $ context_randomize x unless (isSuccess retr) $ error "failed to randomize context" ec_privkey_export x o ol k uncompressed assertBool "successful secret key BER serialization" $ isSuccess ret where key = SecKey32 $ fst $ B16.decode $ "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" ec_privkey_import_test :: Assertion ec_privkey_import_test = do (ret, dec) <- liftIO $ do x <- context_create sign retr <- withEntropy $ context_randomize x unless (isSuccess retr) $ error "failed to randomize context" ber <- allocaBytes 279 $ \o -> alloca $ \ol -> alloca $ \k -> do poke ol 279 poke k key rets <- ec_privkey_export x o ol k uncompressed unless (isSuccess rets) $ error "failed to serialize key" len <- fromIntegral <$> peek ol packCStringLen (castPtr o, len) useAsCStringLen ber $ \(b, bl) -> alloca $ \k -> do ret <- ec_privkey_import x k (castPtr b) (fromIntegral bl) dec <- peek k return (ret, dec) assertBool "successful secret key BER deserialization" $ isSuccess ret assertEqual "keys match" key dec where key = SecKey32 $ fst $ B16.decode $ "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" ec_privkey_tweak_add_test :: Assertion ec_privkey_tweak_add_test = do (ret, tweaked) <- liftIO $ do x <- context_create sign retr <- withEntropy $ context_randomize x unless (isSuccess retr) $ error "failed to randomize context" alloca $ \w -> alloca $ \k -> do poke w tweak poke k key ret <- ec_privkey_tweak_add x k w tweaked <- peek k return (ret, tweaked) assertBool "successful secret key tweak" $ isSuccess ret assertEqual "tweaked keys match" expected tweaked where key = SecKey32 $ fst $ B16.decode $ "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" tweak = Tweak32 $ fst $ B16.decode $ "f5cbe7d88182a4b8e400f96b06128921864a18187d114c8ae8541b566c8ace00" expected = SecKey32 $ fst $ B16.decode $ "ec1e3ce1cefa18a671d51125e2b249688d934b0e28f5d1665384d9b02f929059" ec_privkey_tweak_mul_test :: Assertion ec_privkey_tweak_mul_test = do (ret, tweaked) <- liftIO $ do x <- context_create sign retr <- withEntropy $ context_randomize x unless (isSuccess retr) $ error "failed to randomize context" alloca $ \w -> alloca $ \k -> do poke w tweak poke k key ret <- ec_privkey_tweak_mul x k w tweaked <- peek k return (ret, tweaked) assertBool "successful secret key tweak" $ isSuccess ret assertEqual "tweaked keys match" expected tweaked where key = SecKey32 $ fst $ B16.decode $ "f65255094d7773ed8dd417badc9fc045c1f80fdc5b2d25172b031ce6933e039a" tweak = Tweak32 $ fst $ B16.decode $ "f5cbe7d88182a4b8e400f96b06128921864a18187d114c8ae8541b566c8ace00" expected = SecKey32 $ fst $ B16.decode $ "a96f5962493acb179f60a86a9785fc7a30e0c39b64c09d24fe064d9aef15e4c0" ec_pubkey_tweak_add_test :: Assertion ec_pubkey_tweak_add_test = do (ret, tweaked) <- liftIO $ do x <- context_create verify pk <- alloca $ \p -> useAsCStringLen pub $ \(d, dl) -> do ret <- ec_pubkey_parse x p (castPtr d) (fromIntegral dl) unless (isSuccess ret) $ error "could not parse public key" peek p alloca $ \w -> alloca $ \p -> allocaBytes 72 $ \d -> alloca $ \dl -> do poke w tweak poke p pk poke dl 72 ret <- ec_pubkey_tweak_add x p w rets <- ec_pubkey_serialize x d dl p uncompressed unless (isSuccess rets) $ error "could not serialize public key" len <- peek dl tweaked <- packCStringLen (castPtr d, fromIntegral len) return (ret, tweaked) assertBool "successful secret key tweak" $ isSuccess ret assertEqual "tweaked keys match" expected tweaked where pub = fst $ B16.decode $ "04dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd447051221\ \3d5ed790522c042dee8e85c4c0ec5f96800b72bc5940c8bc1c5e11e4fcbf" tweak = Tweak32 $ fst $ B16.decode $ "f5cbe7d88182a4b8e400f96b06128921864a18187d114c8ae8541b566c8ace00" expected = fst $ B16.decode $ "04441c3982b97576646e0df0c96736063df6b42f2ee566d13b9f6424302d1379e518fd\ \c87a14c5435bff7a5db4552042cb4120c6b86a4bbd3d0643f3c14ad01368" ec_pubkey_tweak_mul_test :: Assertion ec_pubkey_tweak_mul_test = do (ret, tweaked) <- liftIO $ do x <- context_create verify pk <- alloca $ \p -> useAsCStringLen pub $ \(d, dl) -> do ret <- ec_pubkey_parse x p (castPtr d) (fromIntegral dl) unless (isSuccess ret) $ error "could not parse public key" peek p alloca $ \w -> alloca $ \p -> allocaBytes 72 $ \d -> alloca $ \dl -> do poke w tweak poke p pk poke dl 72 ret <- ec_pubkey_tweak_mul x p w rets <- ec_pubkey_serialize x d dl p uncompressed unless (isSuccess rets) $ error "could not serialize public key" len <- peek dl tweaked <- packCStringLen (castPtr d, fromIntegral len) return (ret, tweaked) assertBool "successful secret key tweak" $ isSuccess ret assertEqual "tweaked keys match" expected tweaked where pub = fst $ B16.decode $ "04dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd447051221\ \3d5ed790522c042dee8e85c4c0ec5f96800b72bc5940c8bc1c5e11e4fcbf" tweak = Tweak32 $ fst $ B16.decode $ "f5cbe7d88182a4b8e400f96b06128921864a18187d114c8ae8541b566c8ace00" expected = fst $ B16.decode $ "04f379dc99cdf5c83e433defa267fbb3377d61d6b779c06a0e4ce29ae3ff5353b12ae4\ \9c9d07e7368f2ba5a446c203255ce912322991a2d6a9d5d5761c61ed1845" ec_pubkey_combine_test :: Assertion ec_pubkey_combine_test = do (ret, com) <- liftIO $ alloca $ \p1 -> alloca $ \p2 -> alloca $ \p3 -> allocaBytes 72 $ \d -> alloca $ \dl -> allocaArray 3 $ \a -> alloca $ \p -> do x <- context_create verify parse x pub1 p1 parse x pub2 p2 parse x pub3 p3 pokeArray a [p1, p2, p3] poke dl 72 ret <- ec_pubkey_combine x p a 3 rets <- ec_pubkey_serialize x d dl p uncompressed unless (isSuccess rets) $ error "could not serialize public key" len <- peek dl com <- packCStringLen (castPtr d, fromIntegral len) return (ret, com) assertBool "successful key combination" $ isSuccess ret assertEqual "combined keys match" expected com where parse x pub p = useAsCStringLen pub $ \(d, dl) -> do ret <- ec_pubkey_parse x p (castPtr d) (fromIntegral dl) unless (isSuccess ret) $ error "could not parse public key" pub1 = fst $ B16.decode $ "04dded4203dac96a7e85f2c374a37ce3e9c9a155a72b64b4551b0bfe779dd447051221\ \3d5ed790522c042dee8e85c4c0ec5f96800b72bc5940c8bc1c5e11e4fcbf" pub2 = fst $ B16.decode $ "0487d82042d93447008dfe2af762068a1e53ff394a5bf8f68a045fa642b99ea5d153f5\ \77dd2dba6c7ae4cfd7b6622409d7edd2d76dd13a8092cd3af97b77bd2c77" pub3 = fst $ B16.decode $ "049b101edcbe1ee37ff6b2318526a425b629e823d7d8d9154417880595a28000ee3feb\ \d908754b8ce4e491aa6fe488b41fb5d4bb3788e33c9ff95a7a9229166d59" expected = fst $ B16.decode $ "043d9a7ec70011efc23c33a7e62d2ea73cca87797e3b659d93bea6aa871aebde56c3bc\ \6134ca82e324b0ab9c0e601a6d2933afe7fb5d9f3aae900f5c5dc6e362c8"