csecp256k1

Haskell FFI bindings to bitcoin-core/secp256k1 (docs.ppad.tech/csecp256k1).
git clone git://git.ppad.tech/csecp256k1.git
Log | Files | Refs | README | LICENSE

Main.hs (9417B)


      1 {-# LANGUAGE OverloadedStrings #-}
      2 {-# LANGUAGE RecordWildCards #-}
      3 
      4 module Main where
      5 
      6 import Crypto.Curve.Secp256k1
      7 import qualified Data.Aeson as A
      8 import qualified Data.Attoparsec.ByteString as AT
      9 import qualified Data.ByteString as BS
     10 import qualified Data.Text.IO as TIO
     11 import Test.Tasty
     12 import Test.Tasty.HUnit
     13 import qualified Wycheproof as W
     14 import qualified BIP340
     15 
     16 main :: IO ()
     17 main = do
     18   wp_ecdsa_sha256_bitcoin <- TIO.readFile
     19     "etc/ecdsa_secp256k1_sha256_bitcoin_test.json"
     20   bip340 <- BS.readFile "etc/bip-0340-test-vectors.csv"
     21   let duo = do
     22         wyc <- A.decodeStrictText wp_ecdsa_sha256_bitcoin :: Maybe W.Wycheproof
     23         bip <- case AT.parseOnly BIP340.cases bip340 of
     24                  Left _ -> Nothing
     25                  Right b -> pure b
     26         pure (wyc, bip)
     27   case duo of
     28     Nothing -> error "couldn't parse wycheproof vectors"
     29     Just (W.Wycheproof {..}, bip) -> wcontext $ \tex -> do
     30       tree <- traverse (W.execute_group tex) wp_testGroups
     31       defaultMain $ testGroup "ppad-csecp256k1" [
     32           units
     33         , wycheproof_ecdsa_verify_tests "(ecdsa, sha256, low-s)" tree
     34         , testGroup "bip0340 vectors (schnorr)" (fmap (BIP340.execute tex) bip)
     35         ]
     36 
     37 wycheproof_ecdsa_verify_tests :: String -> [TestTree] -> TestTree
     38 wycheproof_ecdsa_verify_tests msg ts =
     39   testGroup ("wycheproof vectors " <> msg) ts
     40 
     41 units :: TestTree
     42 units = testGroup "unit tests" [
     43     parse_pub_test
     44   , serialize_pub_test
     45   , serialize_pub_u_test
     46   , derive_pub_test
     47   , tweak_pub_add_test
     48   , tweak_pub_mul_test
     49   , tweak_sec_add_test
     50   , tweak_sec_mul_test
     51   , parse_der_test
     52   , serialize_der_test
     53   , compact_test
     54   , parse_xonly_test
     55   , serialize_xonly_test
     56   , keypair_test
     57   , sign_ecdsa_test
     58   , verify_ecdsa_test
     59   , sign_schnorr_test
     60   , verify_schnorr_test
     61   ]
     62 
     63 parse_pub_test :: TestTree
     64 parse_pub_test = testCase "parse_pub (success)" $
     65   wcontext $ \tex -> do
     66     -- throws on failure, so any return implies success
     67     _ <- parse_pub tex _PUB_COMPRESSED
     68     assertBool "success" True
     69 
     70 serialize_pub_test :: TestTree
     71 serialize_pub_test = testCase "serialize_pub (success)" $
     72   wcontext $ \tex -> do
     73     par <- parse_pub tex _PUB_COMPRESSED
     74     pub <- serialize_pub tex par
     75     assertEqual "success" pub _PUB_COMPRESSED
     76 
     77 serialize_pub_u_test :: TestTree
     78 serialize_pub_u_test = testCase "serialize_pub_u (success)" $
     79   wcontext $ \tex -> do
     80     par <- parse_pub tex _PUB_UNCOMPRESSED
     81     pub <- serialize_pub_u tex par
     82     assertEqual "success" pub _PUB_UNCOMPRESSED
     83 
     84 derive_pub_test :: TestTree
     85 derive_pub_test = testCase "derive_pub (success)" $
     86   wcontext $ \tex -> do
     87     -- throws on failure, so any return implies success
     88     _ <- derive_pub tex _SEC
     89     assertBool "success" True
     90 
     91 tweak_pub_add_test :: TestTree
     92 tweak_pub_add_test =
     93   testCase "tweak_pub_add (success)" $
     94     wcontext $ \tex -> do
     95       pub <- parse_pub tex _PUB_COMPRESSED
     96       add <- tweak_pub_add tex pub _TWEAK
     97       eek <- serialize_pub_u tex add
     98       assertEqual "success" eek _PUB_ADD_TWEAKED
     99 
    100 tweak_pub_mul_test :: TestTree
    101 tweak_pub_mul_test =
    102   testCase "tweak_pub_mul (success)" $
    103     wcontext $ \tex -> do
    104       pub <- parse_pub tex _PUB_COMPRESSED
    105       add <- tweak_pub_mul tex pub _TWEAK
    106       eek <- serialize_pub_u tex add
    107       assertEqual "success" eek _PUB_MUL_TWEAKED
    108 
    109 tweak_sec_add_test :: TestTree
    110 tweak_sec_add_test =
    111   testCase "tweak_sec_add (success)" $
    112     wcontext $ \tex -> do
    113       eek <- tweak_sec_add tex _SEC _TWEAK
    114       assertEqual "success" eek _SEC_ADD_TWEAKED
    115 
    116 tweak_sec_mul_test :: TestTree
    117 tweak_sec_mul_test =
    118   testCase "tweak_sec_mul (success)" $
    119     wcontext $ \tex -> do
    120       eek <- tweak_sec_mul tex _SEC _TWEAK
    121       assertEqual "success" eek _SEC_MUL_TWEAKED
    122 
    123 parse_der_test :: TestTree
    124 parse_der_test =
    125   testCase "parse_der (success)" $
    126     wcontext $ \tex -> do
    127       -- throws on failure, so any return implies success
    128       _ <- parse_der tex _DER
    129       assertBool "success" True
    130 
    131 serialize_der_test :: TestTree
    132 serialize_der_test =
    133   testCase "serialize_der (success)" $
    134     wcontext $ \tex -> do
    135       par <- parse_der tex _DER
    136       der <- serialize_der tex par
    137       assertEqual "success" der _DER
    138 
    139 -- joint parse, serialize test
    140 compact_test :: TestTree
    141 compact_test =
    142   testCase "{parse, serialize}_compact (success)" $
    143     wcontext $ \tex -> do
    144       sig <- parse_der tex _DER
    145       com <- serialize_compact tex sig
    146       par <- parse_compact tex com
    147       der <- serialize_der tex par
    148       assertEqual "success" der _DER
    149 
    150 parse_xonly_test :: TestTree
    151 parse_xonly_test =
    152   testCase "parse_xonly (success)" $ do
    153     wcontext $ \tex -> do
    154       pux <- parse_xonly tex _PUB_XONLY
    155       pub <- serialize_xonly tex pux
    156       assertEqual "success" pub _PUB_XONLY
    157 
    158 serialize_xonly_test :: TestTree
    159 serialize_xonly_test =
    160   testCase "serialize_xonly (success)" $
    161     wcontext $ \tex -> do
    162       pub <- parse_pub tex _PUB_COMPRESSED
    163       key <- xonly tex pub
    164       pux <- serialize_xonly tex key
    165       assertEqual "success" pux _PUB_XONLY
    166 
    167 keypair_test :: TestTree
    168 keypair_test =
    169   testCase "keypair (success)" $ do
    170     wcontext $ \tex -> do
    171       per <- keypair tex _SEC
    172       sec <- keypair_sec tex per
    173       pub <- keypair_pub tex per
    174       ser <- serialize_pub tex pub
    175       assertEqual "success" sec _SEC
    176       assertEqual "success" ser _PUB_COMPRESSED
    177 
    178 sign_ecdsa_test :: TestTree
    179 sign_ecdsa_test = testCase "sign_ecdsa (success)" $
    180   wcontext $ \tex -> do
    181     sig <- sign_ecdsa tex _SEC _HAS
    182     der <- serialize_der tex sig
    183     assertEqual "success" _DER der
    184 
    185 verify_ecdsa_test :: TestTree
    186 verify_ecdsa_test = testCase "verify_ecdsa (success)" $
    187   wcontext $ \tex -> do
    188     pub <- parse_pub tex _PUB_UNCOMPRESSED
    189     sig <- parse_der tex _DER
    190     suc <- verify_ecdsa tex pub _HAS sig
    191     assertBool "success" suc
    192 
    193 sign_schnorr_test :: TestTree
    194 sign_schnorr_test = testCase "sign_schnorr (success)" $
    195   wcontext $ \tex -> do
    196     let enn = BS.replicate 32 0
    197     sig <- sign_schnorr tex _HAS _SEC enn
    198     assertEqual "success" sig _SIG_SCHNORR
    199 
    200 verify_schnorr_test :: TestTree
    201 verify_schnorr_test = testCase "verify_schnorr (success)" $
    202   wcontext $ \tex -> do
    203     pub <- parse_pub tex _PUB_UNCOMPRESSED
    204     suc <- verify_schnorr tex pub _HAS _SIG_SCHNORR
    205     assertBool "success" suc
    206 
    207 ecdh_test :: TestTree
    208 ecdh_test = testCase "ecdh (success)" $
    209   wcontext $ \tex -> do
    210     pub <- parse_pub tex _PUB_COMPRESSED
    211     -- throws on failure, so any return implies success
    212     _ <- ecdh tex pub _SEC
    213     assertBool "success" True
    214 
    215 -- test inputs
    216 
    217 -- mostly grabbed from haskoin/secp256k1-haskell
    218 
    219 -- DER-encoded signature
    220 _DER :: BS.ByteString
    221 _DER = mconcat [
    222     "0E\STX!\NUL\245\STX\191\160z\244>~\242ea\139\r\146\154v\EM\238\SOH\214"
    223   , "\NAK\SO7\235n\170\242\200\189\&7\251\"\STX o\EOT\NAK\171\SO\154\151z"
    224   , "\253x\178\194n\243\155\&9R\tm1\159\212\177\SOH\199h\173l\DC3.0E"
    225   ]
    226 
    227 -- a 32-byte message hash
    228 _HAS :: BS.ByteString
    229 _HAS = mconcat [
    230     "\245\203\231\216\129\130\164\184\228\NUL\249k\ACK\DC2\137!\134J"
    231   , "\CAN\CAN}\DC1L\138\232T\ESCVl\138\206\NUL"
    232   ]
    233 
    234 -- a 32-byte secret key
    235 _SEC :: BS.ByteString
    236 _SEC = mconcat [
    237     "\246RU\tMws\237\141\212\ETB\186\220\159\192E\193\248\SI\220[-%\ETB"
    238   , "+\ETX\FS\230\147>\ETX\154"
    239   ]
    240 
    241 -- 32 bytes
    242 _TWEAK :: BS.ByteString
    243 _TWEAK = mconcat [
    244     "\245\203\231\216\129\130\164\184\228\NUL\249k\ACK\DC2\137!\134J"
    245   , "\CAN\CAN}\DC1L\138\232T\ESCVl\138\206\NUL"
    246   ]
    247 
    248 -- _PUB add-tweaked with _TWEAK
    249 _PUB_ADD_TWEAKED :: BS.ByteString
    250 _PUB_ADD_TWEAKED = mconcat [
    251     "\EOTD\FS9\130\185uvdn\r\240\201g6\ACK=\246\180/.\229f\209;\159d$0-"
    252   , "\DC3y\229\CAN\253\200z\DC4\197C[\255z]\180U B\203A \198\184jK\189="
    253   , "\ACKC\243\193J\208\DC3h"
    254   ]
    255 
    256 -- _PUB mul-tweaked with _TWEAK
    257 _PUB_MUL_TWEAKED :: BS.ByteString
    258 _PUB_MUL_TWEAKED = mconcat [
    259     "\EOT\243y\220\153\205\245\200>C=\239\162g\251\179\&7}a\214\183y"
    260   , "\192j\SOL\226\154\227\255SS\177*\228\156\157\a\231\&6\143+\165"
    261   , "\164F\194\ETX%\\\233\DC22)\145\162\214\169\213\213v\FSa\237\CANE"
    262   ]
    263 
    264 -- _SEC add-tweaked with _TWEAK
    265 _SEC_ADD_TWEAKED :: BS.ByteString
    266 _SEC_ADD_TWEAKED = mconcat [
    267     "\236\RS<\225\206\250\CAN\166q\213\DC1%\226\178Ih\141\147K\SO(\245"
    268   , "\209fS\132\217\176/\146\144Y"
    269   ]
    270 
    271 -- _SEC mul-tweaked with _TWEAK
    272 _SEC_MUL_TWEAKED :: BS.ByteString
    273 _SEC_MUL_TWEAKED = mconcat [
    274     "\169oYbI:\203\ETB\159`\168j\151\133\252z0\224\195\155d\192\157$\254"
    275   , "\ACKM\154\239\NAK\228\192"
    276   ]
    277 
    278 -- 33-byte (compressed) public key
    279 _PUB_COMPRESSED :: BS.ByteString
    280 _PUB_COMPRESSED = mconcat [
    281     "\ETX\221\237B\ETX\218\201j~\133\242\195t\163|\227\233\201\161U"
    282   , "\167+d\180U\ESC\v\254w\157\212G\ENQ"
    283   ]
    284 
    285 -- 65-byte (uncompressed) public key
    286 _PUB_UNCOMPRESSED :: BS.ByteString
    287 _PUB_UNCOMPRESSED = mconcat [
    288     "\EOT\221\237B\ETX\218\201j~\133\242\195t\163|\227\233\201\161U\167"
    289   , "+d\180U\ESC\v\254w\157\212G\ENQ\DC2!=^\215\144R,\EOT-\238\142\133"
    290   , "\196\192\236_\150\128\vr\188Y@\200\188\FS^\DC1\228\252\191"
    291   ]
    292 
    293 -- 32-byte x-only pubkey
    294 _PUB_XONLY :: BS.ByteString
    295 _PUB_XONLY = mconcat [
    296     "\221\237B\ETX\218\201j~\133\242\195t\163|\227\233\201\161U\167+d"
    297   , "\180U\ESC\v\254w\157\212G\ENQ"
    298   ]
    299 
    300 -- 64-byte schnorr signature
    301 _SIG_SCHNORR :: BS.ByteString
    302 _SIG_SCHNORR  = mconcat [
    303     "\214\185AtJ\189\250Gp\NAK2\221\DC2[\182\209\192j{\140^\222R\NUL~"
    304   , "\139d@<\138\163rh\247\152\r\228\175\236\219\156\151\214~\135\&7"
    305   , "\225\&6\234\220;\164R\191\170\186\243\NAK\147\f\144\156ez"
    306   ]
    307