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

Internal.hs (8301B)


      1 {-# LANGUAGE CApiFFI #-}
      2 
      3 module Crypto.Secp256k1.Internal (
      4   -- constants
      5     _DER_BYTES
      6   , _PUB_BYTES_INTERNAL
      7   , _PUB_BYTES_COMPRESSED
      8   , _PUB_BYTES_UNCOMPRESSED
      9   , _PUB_BYTES_XONLY
     10   , _SEC_BYTES
     11   , _SIG_BYTES
     12   , _KEYPAIR_BYTES
     13   , _COMPRESSED_FLAG
     14   , _UNCOMPRESSED_FLAG
     15 
     16   -- context
     17   , _SECP256K1_CONTEXT_NONE
     18   , Context
     19   , Seed32
     20   , secp256k1_context_create
     21   , secp256k1_context_destroy
     22   , secp256k1_context_randomize
     23   , wcontext
     24 
     25   -- ec
     26   , PubKey64
     27   , SecKey32
     28   , Tweak32
     29   , secp256k1_ec_pubkey_parse
     30   , secp256k1_ec_pubkey_serialize
     31   , secp256k1_ec_pubkey_create
     32   , secp256k1_ec_pubkey_tweak_add
     33   , secp256k1_ec_pubkey_tweak_mul
     34   , secp256k1_ec_seckey_tweak_add
     35   , secp256k1_ec_seckey_tweak_mul
     36 
     37   -- ecdsa
     38   , MsgHash32
     39   , Sig64
     40   , secp256k1_ecdsa_sign
     41   , secp256k1_ecdsa_verify
     42   , secp256k1_ecdsa_signature_parse_der
     43   , secp256k1_ecdsa_signature_serialize_der
     44   , secp256k1_ecdsa_signature_parse_compact
     45   , secp256k1_ecdsa_signature_serialize_compact
     46 
     47   -- ecdh
     48   , secp256k1_ecdh
     49 
     50   -- extrakeys
     51   , KeyPair96
     52   , XOnlyPublicKey64
     53   , secp256k1_keypair_create
     54   , secp256k1_keypair_sec
     55   , secp256k1_keypair_pub
     56   , secp256k1_xonly_pubkey_parse
     57   , secp256k1_xonly_pubkey_serialize
     58   , secp256k1_xonly_pubkey_from_pubkey
     59 
     60   -- schnorr
     61   , secp256k1_schnorrsig_sign32
     62   , secp256k1_schnorrsig_verify
     63   ) where
     64 
     65 import Control.Exception (bracket)
     66 import Foreign.Ptr (Ptr)
     67 import Foreign.C.Types (CUChar(..), CInt(..), CUInt(..), CSize(..))
     68 
     69 -- size constants
     70 
     71 -- bytesize of a DER-encoded signature
     72 _DER_BYTES :: Int
     73 _DER_BYTES = 72
     74 
     75 -- bytesize of an x-only pubkey
     76 _PUB_BYTES_XONLY :: Int
     77 _PUB_BYTES_XONLY = 32
     78 
     79 -- bytesize of a compressed pubkey
     80 _PUB_BYTES_COMPRESSED :: Int
     81 _PUB_BYTES_COMPRESSED = 33
     82 
     83 -- bytesize of an uncompressed pubkey
     84 _PUB_BYTES_UNCOMPRESSED :: Int
     85 _PUB_BYTES_UNCOMPRESSED = 65
     86 
     87 -- bytesize of a secp256k1-internal pubkey
     88 _PUB_BYTES_INTERNAL :: Int
     89 _PUB_BYTES_INTERNAL = 64
     90 
     91 -- bytesize of a secret key
     92 _SEC_BYTES :: Int
     93 _SEC_BYTES = 32
     94 
     95 -- bytesize of a secp256k1-internal signature
     96 _SIG_BYTES :: Int
     97 _SIG_BYTES = 64
     98 
     99 -- bytesize of a secp256k1-internal keypair
    100 _KEYPAIR_BYTES :: Int
    101 _KEYPAIR_BYTES = 96
    102 
    103 -- flag to indicate a compressed pubkey when parsing
    104 _COMPRESSED_FLAG :: CUInt
    105 _COMPRESSED_FLAG = 0x0102
    106 
    107 -- flag to indicate an uncompressed pubkey when parsing
    108 _UNCOMPRESSED_FLAG :: CUInt
    109 _UNCOMPRESSED_FLAG = 0x0002
    110 
    111 -- context
    112 
    113 -- secp256k1 context
    114 data Context
    115 
    116 -- 32-byte random seed
    117 data Seed32
    118 
    119 -- per secp256k1.h:
    120 --
    121 --  > The only valid non-deprecated flag in recent library versions is
    122 --  > SECP256K1_CONTEXT_NONE, which will create a context sufficient for
    123 --  > all functionality
    124 --
    125 -- where SECP256K1_CONTEXT_NONE = 1, via:
    126 --
    127 -- #define SECP256K1_FLAGS_TYPE_CONTEXT (1 << 0)
    128 -- #define SECP256K1_CONTEXT_NONE (SECP256K1_FLAGS_TYPE_CONTEXT)
    129 _SECP256K1_CONTEXT_NONE :: Integral a => a
    130 _SECP256K1_CONTEXT_NONE = 1
    131 
    132 foreign import capi
    133   "secp256k1.h haskellsecp256k1_v0_1_0_context_create"
    134   secp256k1_context_create
    135     :: CUInt
    136     -> IO (Ptr Context)
    137 
    138 foreign import capi
    139   "secp256k1.h haskellsecp256k1_v0_1_0_context_destroy"
    140   secp256k1_context_destroy
    141     :: Ptr Context
    142     -> IO ()
    143 
    144 foreign import capi
    145   "secp256k1.h haskellsecp256k1_v0_1_0_context_randomize"
    146   secp256k1_context_randomize
    147     :: Ptr Context
    148     -> Ptr Seed32
    149     -> IO CInt
    150 
    151 -- returning the context itself and attempting to use it outside of a
    152 -- 'wcontext' block will produce segfaults
    153 wcontext :: (Ptr Context -> IO a) -> IO a
    154 wcontext =
    155   bracket
    156     (secp256k1_context_create _SECP256K1_CONTEXT_NONE)
    157     secp256k1_context_destroy
    158 
    159 -- ec
    160 
    161 -- 64-byte public key
    162 data PubKey64
    163 
    164 -- 32-byte secret key
    165 data SecKey32
    166 
    167 -- 32-byte tweak
    168 data Tweak32
    169 
    170 foreign import capi
    171   "secp256k1.h haskellsecp256k1_v0_1_0_ec_pubkey_parse"
    172   secp256k1_ec_pubkey_parse
    173     :: Ptr Context
    174     -> Ptr PubKey64
    175     -> Ptr CUChar
    176     -> CSize
    177     -> IO CInt
    178 
    179 foreign import capi
    180   "secp256k1.h haskellsecp256k1_v0_1_0_ec_pubkey_serialize"
    181   secp256k1_ec_pubkey_serialize
    182     :: Ptr Context
    183     -> Ptr CUChar
    184     -> Ptr CSize
    185     -> Ptr PubKey64
    186     -> CUInt
    187     -> IO CInt
    188 
    189 foreign import capi
    190   "secp256k1.h haskellsecp256k1_v0_1_0_ec_pubkey_create"
    191   secp256k1_ec_pubkey_create
    192     :: Ptr Context
    193     -> Ptr PubKey64
    194     -> Ptr SecKey32
    195     -> IO CInt
    196 
    197 foreign import capi
    198   "secp256k1.h haskellsecp256k1_v0_1_0_ec_seckey_tweak_add"
    199   secp256k1_ec_seckey_tweak_add
    200     :: Ptr Context
    201     -> Ptr SecKey32
    202     -> Ptr Tweak32
    203     -> IO CInt
    204 
    205 foreign import capi
    206   "secp256k1.h haskellsecp256k1_v0_1_0_ec_pubkey_tweak_add"
    207   secp256k1_ec_pubkey_tweak_add
    208     :: Ptr Context
    209     -> Ptr PubKey64
    210     -> Ptr Tweak32
    211     -> IO CInt
    212 
    213 foreign import capi
    214   "secp256k1.h haskellsecp256k1_v0_1_0_ec_seckey_tweak_mul"
    215   secp256k1_ec_seckey_tweak_mul
    216     :: Ptr Context
    217     -> Ptr SecKey32
    218     -> Ptr Tweak32
    219     -> IO CInt
    220 
    221 foreign import capi
    222   "secp256k1.h haskellsecp256k1_v0_1_0_ec_pubkey_tweak_mul"
    223   secp256k1_ec_pubkey_tweak_mul
    224     :: Ptr Context
    225     -> Ptr PubKey64
    226     -> Ptr Tweak32
    227     -> IO CInt
    228 
    229 -- ecdsa
    230 
    231 -- 32-byte message hash
    232 data MsgHash32
    233 
    234 -- 64-byte signature
    235 data Sig64
    236 
    237 foreign import capi
    238   "secp256k1.h haskellsecp256k1_v0_1_0_ecdsa_sign"
    239   secp256k1_ecdsa_sign
    240     :: Ptr Context
    241     -> Ptr Sig64
    242     -> Ptr MsgHash32
    243     -> Ptr SecKey32
    244     -> Ptr a
    245     -> Ptr b
    246     -> IO CInt
    247 
    248 foreign import capi
    249   "secp256k1.h haskellsecp256k1_v0_1_0_ecdsa_verify"
    250   secp256k1_ecdsa_verify
    251     :: Ptr Context
    252     -> Ptr Sig64
    253     -> Ptr MsgHash32
    254     -> Ptr PubKey64
    255     -> IO CInt
    256 
    257 foreign import capi
    258   "secp256k1.h haskellsecp256k1_v0_1_0_ecdsa_signature_parse_der"
    259   secp256k1_ecdsa_signature_parse_der
    260     :: Ptr Context
    261     -> Ptr Sig64
    262     -> Ptr CUChar
    263     -> CSize
    264     -> IO CInt
    265 
    266 foreign import capi
    267   "secp256k1.h haskellsecp256k1_v0_1_0_ecdsa_signature_serialize_der"
    268   secp256k1_ecdsa_signature_serialize_der
    269     :: Ptr Context
    270     -> Ptr CUChar
    271     -> Ptr CSize
    272     -> Ptr Sig64
    273     -> IO CInt
    274 
    275 foreign import capi
    276   "secp256k1.h haskellsecp256k1_v0_1_0_ecdsa_signature_parse_compact"
    277   secp256k1_ecdsa_signature_parse_compact
    278     :: Ptr Context
    279     -> Ptr Sig64
    280     -> Ptr CUChar
    281     -> IO CInt
    282 
    283 foreign import capi
    284   "secp256k1.h haskellsecp256k1_v0_1_0_ecdsa_signature_serialize_compact"
    285   secp256k1_ecdsa_signature_serialize_compact
    286     :: Ptr Context
    287     -> Ptr CUChar
    288     -> Ptr Sig64
    289     -> IO CInt
    290 
    291 -- ecdh
    292 
    293 foreign import capi
    294   "secp256k1_ecdh.h haskellsecp256k1_v0_1_0_ecdh"
    295   secp256k1_ecdh
    296     :: Ptr Context
    297     -> Ptr CUChar
    298     -> Ptr PubKey64
    299     -> Ptr SecKey32
    300     -> Ptr a
    301     -> Ptr b
    302     -> IO CInt
    303 
    304 -- extrakeys
    305 
    306 data KeyPair96
    307 
    308 data XOnlyPublicKey64
    309 
    310 foreign import capi
    311   "secp256k1_extrakeys.h haskellsecp256k1_v0_1_0_keypair_create"
    312   secp256k1_keypair_create
    313     :: Ptr Context
    314     -> Ptr KeyPair96
    315     -> Ptr SecKey32
    316     -> IO CInt
    317 
    318 foreign import capi
    319   "secp256k1_extrakeys.h haskellsecp256k1_v0_1_0_keypair_pub"
    320   secp256k1_keypair_pub
    321     :: Ptr Context
    322     -> Ptr PubKey64
    323     -> Ptr KeyPair96
    324     -> IO CInt
    325 
    326 foreign import capi
    327   "secp256k1_extrakeys.h haskellsecp256k1_v0_1_0_keypair_sec"
    328   secp256k1_keypair_sec
    329     :: Ptr Context
    330     -> Ptr SecKey32
    331     -> Ptr KeyPair96
    332     -> IO CInt
    333 
    334 foreign import capi
    335   "secp256k1_extrakeys.h haskellsecp256k1_v0_1_0_xonly_pubkey_parse"
    336   secp256k1_xonly_pubkey_parse
    337     :: Ptr Context
    338     -> Ptr XOnlyPublicKey64
    339     -> Ptr CUChar
    340     -> IO CInt
    341 
    342 foreign import capi
    343   "secp256k1_extrakeys.h haskellsecp256k1_v0_1_0_xonly_pubkey_serialize"
    344   secp256k1_xonly_pubkey_serialize
    345     :: Ptr Context
    346     -> Ptr CUChar
    347     -> Ptr XOnlyPublicKey64
    348     -> IO CInt
    349 
    350 foreign import capi
    351   "secp256k1_extrakeys.h haskellsecp256k1_v0_1_0_xonly_pubkey_from_pubkey"
    352   secp256k1_xonly_pubkey_from_pubkey
    353     :: Ptr Context
    354     -> Ptr XOnlyPublicKey64
    355     -> Ptr CInt
    356     -> Ptr PubKey64
    357     -> IO CInt
    358 
    359 -- schnorr
    360 
    361 foreign import capi
    362   "secp256k1_schnorrsig.h haskellsecp256k1_v0_1_0_schnorrsig_sign32"
    363   secp256k1_schnorrsig_sign32
    364     :: Ptr Context
    365     -> Ptr Sig64
    366     -> Ptr MsgHash32
    367     -> Ptr KeyPair96
    368     -> Ptr CUChar
    369     -> IO CInt
    370 
    371 foreign import capi
    372   "secp256k1_schnorrsig.h haskellsecp256k1_v0_1_0_schnorrsig_verify"
    373   secp256k1_schnorrsig_verify
    374     :: Ptr Context
    375     -> Ptr Sig64
    376     -> Ptr CUChar
    377     -> CSize
    378     -> Ptr XOnlyPublicKey64
    379     -> IO CInt
    380