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

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

Crypto.Secp256k1

Contents

Description

Crytpographic functions from Bitcoin’s secp256k1 library.

Synopsis

Messages

data Msg Source #

Instances
Eq Msg Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

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

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

Read Msg Source # 
Instance details

Defined in Crypto.Secp256k1

Show Msg Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

showsPrec :: Int -> Msg -> ShowS #

show :: Msg -> String #

showList :: [Msg] -> ShowS #

IsString Msg Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

fromString :: String -> Msg #

Arbitrary Msg Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

arbitrary :: Gen Msg #

shrink :: Msg -> [Msg] #

msg :: ByteString -> Maybe Msg Source #

Import 32-byte ByteString as Msg.

getMsg :: Msg -> ByteString Source #

Get 32-byte message.

Secret Keys

data SecKey Source #

Instances
Eq SecKey Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

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

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

Read SecKey Source # 
Instance details

Defined in Crypto.Secp256k1

Show SecKey Source # 
Instance details

Defined in Crypto.Secp256k1

IsString SecKey Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

fromString :: String -> SecKey #

Arbitrary SecKey Source # 
Instance details

Defined in Crypto.Secp256k1

getSecKey :: SecKey -> ByteString Source #

Get 32-byte secret key.

Public Keys

data PubKey Source #

Instances
Eq PubKey Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

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

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

Read PubKey Source # 
Instance details

Defined in Crypto.Secp256k1

Show PubKey Source # 
Instance details

Defined in Crypto.Secp256k1

IsString PubKey Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

fromString :: String -> PubKey #

Arbitrary PubKey Source # 
Instance details

Defined in Crypto.Secp256k1

importPubKey :: ByteString -> Maybe PubKey Source #

Import DER-encoded public key.

exportPubKey :: Bool -> PubKey -> ByteString Source #

Encode public key as DER. First argument True for compressed output.

Signatures

data Sig Source #

Instances
Eq Sig Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

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

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

Read Sig Source # 
Instance details

Defined in Crypto.Secp256k1

Show Sig Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

showsPrec :: Int -> Sig -> ShowS #

show :: Sig -> String #

showList :: [Sig] -> ShowS #

IsString Sig Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

fromString :: String -> Sig #

verifySig :: PubKey -> Sig -> Msg -> Bool Source #

Verify message signature. True means that the signature is correct.

normalizeSig :: Sig -> (Sig, Bool) Source #

Convert signature to a normalized lower-S form. Boolean value True indicates that the signature changed, False indicates that it was already normal.

DER

importSig :: ByteString -> Maybe Sig Source #

Import DER-encoded signature.

exportSig :: Sig -> ByteString Source #

Encode signature as strict DER.

Compact

Recoverable

data RecSig Source #

Instances
Eq RecSig Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

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

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

Read RecSig Source # 
Instance details

Defined in Crypto.Secp256k1

Show RecSig Source # 
Instance details

Defined in Crypto.Secp256k1

IsString RecSig Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

fromString :: String -> RecSig #

data CompactRecSig Source #

importCompactRecSig :: CompactRecSig -> Maybe RecSig Source #

Parse a compact ECDSA signature (64 bytes + recovery id).

exportCompactRecSig :: RecSig -> CompactRecSig Source #

Serialize an ECDSA signature in compact format (64 bytes + recovery id).

convertRecSig :: RecSig -> Sig Source #

Convert a recoverable signature into a normal signature.

signRecMsg :: SecKey -> Msg -> RecSig Source #

Create a recoverable ECDSA signature.

recover :: RecSig -> Msg -> Maybe PubKey Source #

Recover an ECDSA public key from a signature.

Addition & Multiplication

data Tweak Source #

Instances
Eq Tweak Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

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

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

Read Tweak Source # 
Instance details

Defined in Crypto.Secp256k1

Show Tweak Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

showsPrec :: Int -> Tweak -> ShowS #

show :: Tweak -> String #

showList :: [Tweak] -> ShowS #

IsString Tweak Source # 
Instance details

Defined in Crypto.Secp256k1

Methods

fromString :: String -> Tweak #

getTweak :: Tweak -> ByteString Source #

Get 32-byte tweak.

tweakAddSecKey :: SecKey -> Tweak -> Maybe SecKey Source #

Add tweak to secret key.

tweakMulSecKey :: SecKey -> Tweak -> Maybe SecKey Source #

Multiply secret key by tweak.

tweakAddPubKey :: PubKey -> Tweak -> Maybe PubKey Source #

Add tweak to public key. Tweak is multiplied first by G to obtain a point.

tweakMulPubKey :: PubKey -> Tweak -> Maybe PubKey Source #

Multiply public key by tweak. Tweak is multiplied first by G to obtain a point.

combinePubKeys :: [PubKey] -> Maybe PubKey Source #

Add multiple public keys together.