| License | UNLICENSE |
|---|---|
| Maintainer | Keagan McClelland <keagan.mcclelland@gmail.com> |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Crypto.Secp256k1
Description
Crytpographic functions from Bitcoin’s secp256k1 library.
Synopsis
- data SecKey
- data PubKeyXY
- data PubKeyXO
- data KeyPair
- data Signature
- data RecoverableSignature
- data SchnorrSignature
- data Tweak
- importSecKey :: ByteString -> Maybe SecKey
- exportSecKey :: SecKey -> ByteString
- importPubKeyXY :: ByteString -> Maybe PubKeyXY
- exportPubKeyXY :: Bool -> PubKeyXY -> ByteString
- importPubKeyXO :: ByteString -> Maybe PubKeyXO
- exportPubKeyXO :: PubKeyXO -> ByteString
- importSignatureCompact :: ByteString -> Maybe Signature
- importSignatureDer :: ByteString -> Maybe Signature
- exportSignatureCompact :: Signature -> ByteString
- exportSignatureDer :: Signature -> ByteString
- importRecoverableSignature :: ByteString -> Maybe RecoverableSignature
- exportRecoverableSignature :: RecoverableSignature -> ByteString
- importSchnorrSignature :: ByteString -> Maybe SchnorrSignature
- exportSchnorrSignature :: SchnorrSignature -> ByteString
- importTweak :: ByteString -> Maybe Tweak
- ecdsaVerify :: ByteString -> PubKeyXY -> Signature -> Bool
- ecdsaSign :: SecKey -> ByteString -> Maybe Signature
- ecdsaSignRecoverable :: SecKey -> ByteString -> Maybe RecoverableSignature
- ecdsaRecover :: RecoverableSignature -> ByteString -> Maybe PubKeyXY
- ecdsaNormalizeSignature :: Signature -> Signature
- recSigToSig :: RecoverableSignature -> Signature
- derivePubKey :: SecKey -> PubKeyXY
- keyPairCreate :: SecKey -> KeyPair
- keyPairSecKey :: KeyPair -> SecKey
- keyPairPubKeyXY :: KeyPair -> PubKeyXY
- keyPairPubKeyXO :: KeyPair -> (PubKeyXO, Bool)
- xyToXO :: PubKeyXY -> (PubKeyXO, Bool)
- secKeyTweakAdd :: SecKey -> Tweak -> Maybe SecKey
- secKeyTweakMul :: SecKey -> Tweak -> Maybe SecKey
- keyPairPubKeyXOTweakAdd :: KeyPair -> Tweak -> Maybe KeyPair
- pubKeyCombine :: [PubKeyXY] -> Maybe PubKeyXY
- pubKeyNegate :: PubKeyXY -> PubKeyXY
- secKeyNegate :: SecKey -> SecKey
- tweakNegate :: Tweak -> Tweak
- pubKeyTweakAdd :: PubKeyXY -> Tweak -> Maybe PubKeyXY
- pubKeyTweakMul :: PubKeyXY -> Tweak -> Maybe PubKeyXY
- pubKeyXOTweakAdd :: PubKeyXO -> Tweak -> Maybe PubKeyXY
- pubKeyXOTweakAddCheck :: PubKeyXO -> Bool -> PubKeyXO -> Tweak -> Bool
- schnorrSign :: Maybe StdGen -> KeyPair -> ByteString -> Maybe SchnorrSignature
- schnorrSignDeterministic :: KeyPair -> ByteString -> Maybe SchnorrSignature
- schnorrSignNondeterministic :: KeyPair -> ByteString -> IO (Maybe SchnorrSignature)
- schnorrVerify :: PubKeyXO -> ByteString -> SchnorrSignature -> Bool
- taggedSha256 :: ByteString -> ByteString -> SizedByteArray 32 ByteString
- ecdh :: SecKey -> PubKeyXY -> SizedByteArray 32 ByteString
Core Types
Secret Key
Public Key with both X and Y coordinates
Public Key with only an X coordinate.
Structure containing Signature (R,S) data.
data RecoverableSignature Source #
Structure containing Signature AND recovery ID
Instances
| Read RecoverableSignature Source # | |
Defined in Crypto.Secp256k1 Methods readsPrec :: Int -> ReadS RecoverableSignature # readList :: ReadS [RecoverableSignature] # | |
| Show RecoverableSignature Source # | |
Defined in Crypto.Secp256k1 Methods showsPrec :: Int -> RecoverableSignature -> ShowS # show :: RecoverableSignature -> String # showList :: [RecoverableSignature] -> ShowS # | |
| NFData RecoverableSignature Source # | |
Defined in Crypto.Secp256k1 Methods rnf :: RecoverableSignature -> () # | |
| Eq RecoverableSignature Source # | |
Defined in Crypto.Secp256k1 Methods (==) :: RecoverableSignature -> RecoverableSignature -> Bool # (/=) :: RecoverableSignature -> RecoverableSignature -> Bool # | |
data SchnorrSignature Source #
Structure containing Schnorr Signature
Instances
| Read SchnorrSignature Source # | |
Defined in Crypto.Secp256k1 Methods readsPrec :: Int -> ReadS SchnorrSignature # readList :: ReadS [SchnorrSignature] # | |
| Show SchnorrSignature Source # | |
Defined in Crypto.Secp256k1 Methods showsPrec :: Int -> SchnorrSignature -> ShowS # show :: SchnorrSignature -> String # showList :: [SchnorrSignature] -> ShowS # | |
| NFData SchnorrSignature Source # | |
Defined in Crypto.Secp256k1 Methods rnf :: SchnorrSignature -> () # | |
| Eq SchnorrSignature Source # | |
Defined in Crypto.Secp256k1 Methods (==) :: SchnorrSignature -> SchnorrSignature -> Bool # (/=) :: SchnorrSignature -> SchnorrSignature -> Bool # | |
Isomorphic to SecKey but specifically used for tweaking (EC Group operations) other keys
Parsing and Serialization
importSecKey :: ByteString -> Maybe SecKey Source #
Parses SecKey, will be Nothing if the ByteString corresponds to 0{32} or is not 32 bytes in length
exportSecKey :: SecKey -> ByteString Source #
importPubKeyXY :: ByteString -> Maybe PubKeyXY Source #
Parses a 33 or 65 byte PubKeyXY, all other lengths will result in Nothing
exportPubKeyXY :: Bool -> PubKeyXY -> ByteString Source #
Serialize PubKeyXY. First argument True for compressed output (33 bytes), False for uncompressed (65 bytes).
importPubKeyXO :: ByteString -> Maybe PubKeyXO Source #
Parses PubKeyXO from ByteString, will be Nothing if the pubkey corresponds to the Point at Infinity or the
the ByteString is not 32 bytes long
exportPubKeyXO :: PubKeyXO -> ByteString Source #
Serializes PubKeyXO to 32 byte ByteString
importSignatureCompact :: ByteString -> Maybe Signature Source #
Parses Signature from Compact (64 bytes) representation.
importSignatureDer :: ByteString -> Maybe Signature Source #
Parses Signature from DER representation.
exportSignatureCompact :: Signature -> ByteString Source #
Serializes Signature to Compact (64 byte) representation
exportSignatureDer :: Signature -> ByteString Source #
Serializes Signature to DER (71 | 72 bytes) representation
importRecoverableSignature :: ByteString -> Maybe RecoverableSignature Source #
Parses RecoverableSignature from Compact (65 byte) representation
exportRecoverableSignature :: RecoverableSignature -> ByteString Source #
Serializes RecoverableSignature to Compact (65 byte) representation
importSchnorrSignature :: ByteString -> Maybe SchnorrSignature Source #
Parses SchnorrSignature from Schnorr (64 byte) representation
exportSchnorrSignature :: SchnorrSignature -> ByteString Source #
Serializes SchnorrSignature to Schnorr (64 byte) representation
importTweak :: ByteString -> Maybe Tweak Source #
ECDSA Operations
ecdsaVerify :: ByteString -> PubKeyXY -> Signature -> Bool Source #
Verify message signature. True means that the signature is correct.
ecdsaSign :: SecKey -> ByteString -> Maybe Signature Source #
Signs ByteString with SecKey only if ByteString is 32 bytes.
ecdsaSignRecoverable :: SecKey -> ByteString -> Maybe RecoverableSignature Source #
Signs ByteString with SecKey only if ByteString is 32 bytes. Retains ability to compute PubKeyXY from the
RecoverableSignature and the original message (ByteString)
ecdsaRecover :: RecoverableSignature -> ByteString -> Maybe PubKeyXY Source #
Computes PubKeyXY from RecoverableSignature and the original message that was signed (must be 32 bytes).
Conversions
recSigToSig :: RecoverableSignature -> Signature Source #
Forgets the recovery id of a signature
keyPairPubKeyXO :: KeyPair -> (PubKeyXO, Bool) Source #
Project PubKeyXO from KeyPair as well as parity bit. True indicates that the public key is the same as it
would be if you had serialized the PubKeyXO and it was prefixed with flagsTagPubkeyOdd. False indicates
it would be prefixed by flagsTagPubkeyEven
xyToXO :: PubKeyXY -> (PubKeyXO, Bool) Source #
Convert PubKeyXY to PubKeyXO. See keyPairPubKeyXO for more information on how to interpret the parity bit.
Tweaks
pubKeyXOTweakAddCheck :: PubKeyXO -> Bool -> PubKeyXO -> Tweak -> Bool Source #
Check that a PubKeyXO is the result of the specified tweak operation. True means it was.
Schnorr Operations
schnorrSign :: Maybe StdGen -> KeyPair -> ByteString -> Maybe SchnorrSignature Source #
schnorrSignDeterministic :: KeyPair -> ByteString -> Maybe SchnorrSignature Source #
Compute a deterministic schnorr signature using a KeyPair.
schnorrSignNondeterministic :: KeyPair -> ByteString -> IO (Maybe SchnorrSignature) Source #
Compute a non-deterministic schnorr signature using a KeyPair.
schnorrVerify :: PubKeyXO -> ByteString -> SchnorrSignature -> Bool Source #
Verify the authenticity of a schnorr signature. True means the Signature is correct.
Other
taggedSha256 :: ByteString -> ByteString -> SizedByteArray 32 ByteString Source #
Generate a tagged sha256 digest as specified in BIP340
ecdh :: SecKey -> PubKeyXY -> SizedByteArray 32 ByteString Source #