secp256k1-haskell-0.1.4: Bindings for secp256k1 library from Bitcoin Core

LicenseMIT
MaintainerJean-Pierre Rupp <root@haskoin.com>
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Crypto.Secp256k1.Internal

Description

The API for this module may change at any time. This is an internal module only exposed for hacking and experimentation.

Synopsis

Documentation

data Ctx Source #

Constructors

Ctx 

newtype Msg32 Source #

Constructors

Msg32 
Instances
Eq Msg32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

(==) :: Msg32 -> Msg32 -> Bool #

(/=) :: Msg32 -> Msg32 -> Bool #

Ord Msg32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

compare :: Msg32 -> Msg32 -> Ordering #

(<) :: Msg32 -> Msg32 -> Bool #

(<=) :: Msg32 -> Msg32 -> Bool #

(>) :: Msg32 -> Msg32 -> Bool #

(>=) :: Msg32 -> Msg32 -> Bool #

max :: Msg32 -> Msg32 -> Msg32 #

min :: Msg32 -> Msg32 -> Msg32 #

Read Msg32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Show Msg32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

showsPrec :: Int -> Msg32 -> ShowS #

show :: Msg32 -> String #

showList :: [Msg32] -> ShowS #

Storable Msg32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

sizeOf :: Msg32 -> Int #

alignment :: Msg32 -> Int #

peekElemOff :: Ptr Msg32 -> Int -> IO Msg32 #

pokeElemOff :: Ptr Msg32 -> Int -> Msg32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Msg32 #

pokeByteOff :: Ptr b -> Int -> Msg32 -> IO () #

peek :: Ptr Msg32 -> IO Msg32 #

poke :: Ptr Msg32 -> Msg32 -> IO () #

newtype Sig64 Source #

Constructors

Sig64 
Instances
Eq Sig64 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

(==) :: Sig64 -> Sig64 -> Bool #

(/=) :: Sig64 -> Sig64 -> Bool #

Ord Sig64 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

compare :: Sig64 -> Sig64 -> Ordering #

(<) :: Sig64 -> Sig64 -> Bool #

(<=) :: Sig64 -> Sig64 -> Bool #

(>) :: Sig64 -> Sig64 -> Bool #

(>=) :: Sig64 -> Sig64 -> Bool #

max :: Sig64 -> Sig64 -> Sig64 #

min :: Sig64 -> Sig64 -> Sig64 #

Read Sig64 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Show Sig64 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

showsPrec :: Int -> Sig64 -> ShowS #

show :: Sig64 -> String #

showList :: [Sig64] -> ShowS #

Storable Sig64 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

sizeOf :: Sig64 -> Int #

alignment :: Sig64 -> Int #

peekElemOff :: Ptr Sig64 -> Int -> IO Sig64 #

pokeElemOff :: Ptr Sig64 -> Int -> Sig64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Sig64 #

pokeByteOff :: Ptr b -> Int -> Sig64 -> IO () #

peek :: Ptr Sig64 -> IO Sig64 #

poke :: Ptr Sig64 -> Sig64 -> IO () #

data CompactRecSig Source #

newtype Seed32 Source #

Constructors

Seed32 
Instances
Eq Seed32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

(==) :: Seed32 -> Seed32 -> Bool #

(/=) :: Seed32 -> Seed32 -> Bool #

Ord Seed32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Read Seed32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Show Seed32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Storable Seed32 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

newtype Algo16 Source #

Constructors

Algo16 
Instances
Eq Algo16 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

(==) :: Algo16 -> Algo16 -> Bool #

(/=) :: Algo16 -> Algo16 -> Bool #

Ord Algo16 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Read Algo16 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Show Algo16 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Storable Algo16 Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

newtype Ret Source #

Constructors

Ret 

Fields

Instances
Eq Ret Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

(==) :: Ret -> Ret -> Bool #

(/=) :: Ret -> Ret -> Bool #

Ord Ret Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

compare :: Ret -> Ret -> Ordering #

(<) :: Ret -> Ret -> Bool #

(<=) :: Ret -> Ret -> Bool #

(>) :: Ret -> Ret -> Bool #

(>=) :: Ret -> Ret -> Bool #

max :: Ret -> Ret -> Ret #

min :: Ret -> Ret -> Ret #

Read Ret Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Show Ret Source # 
Instance details

Defined in Crypto.Secp256k1.Internal

Methods

showsPrec :: Int -> Ret -> ShowS #

show :: Ret -> String #

showList :: [Ret] -> ShowS #

type NonceFunction a Source #

Arguments

 = Ptr Nonce32 
-> Ptr Msg32 
-> Ptr SecKey32 
-> Ptr Algo16 
-> Ptr a

extra data

-> CUInt

attempt

-> Ret 

Nonce32-generating function

withContext :: (Ptr Ctx -> IO a) -> a Source #

setIllegalCallback Source #

Arguments

:: Ptr Ctx 
-> FunPtr (CString -> Ptr a -> IO ())

message, data

-> Ptr a

data

-> IO () 

setErrorCallback Source #

Arguments

:: Ptr Ctx 
-> FunPtr (CString -> Ptr a -> IO ())

message, data

-> Ptr a

data

-> IO () 

ecPubKeyParse Source #

Arguments

:: Ptr Ctx 
-> Ptr PubKey64 
-> Ptr CUChar

encoded public key array

-> CSize

size of encoded public key array

-> IO Ret 

ecPubKeySerialize Source #

Arguments

:: Ptr Ctx 
-> Ptr CUChar

array for encoded public key, must be large enough

-> Ptr CSize

size of encoded public key, will be updated

-> Ptr PubKey64 
-> SerFlags 
-> IO Ret 

ecdsaSignatureParseDer Source #

Arguments

:: Ptr Ctx 
-> Ptr Sig64 
-> Ptr CUChar

encoded DER signature

-> CSize

size of encoded signature

-> IO Ret 

ecdsaSignatureSerializeDer Source #

Arguments

:: Ptr Ctx 
-> Ptr CUChar

array for encoded signature, must be large enough

-> Ptr CSize

size of encoded signature, will be updated

-> Ptr Sig64 
-> IO Ret 

ecdsaSignatureNormalize Source #

Arguments

:: Ptr Ctx 
-> Ptr Sig64

output

-> Ptr Sig64

input

-> IO Ret 

ecdsaSign Source #

Arguments

:: Ptr Ctx 
-> Ptr Sig64 
-> Ptr Msg32 
-> Ptr SecKey32 
-> FunPtr (NonceFunction a) 
-> Ptr a

nonce data

-> IO Ret 

ecPubKeyCombine Source #

Arguments

:: Ptr Ctx 
-> Ptr PubKey64

pointer to public key storage

-> Ptr (Ptr PubKey64)

pointer to array of public keys

-> CInt

number of public keys

-> IO Ret 

ecdsaSignRecoverable Source #

Arguments

:: Ptr Ctx 
-> Ptr RecSig65 
-> Ptr Msg32 
-> Ptr SecKey32 
-> FunPtr (NonceFunction a) 
-> Ptr a

nonce data

-> IO Ret