License | UNLICENSE |
---|---|
Maintainer | Keagan McClelland <keagan.mcclelland@gmail.com> |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Crytpographic functions from Bitcoin’s secp256k1 library.
Synopsis
- data SecKey
- data PubKeyXY
- data PubKeyXO
- data KeyPair
- data Signature
- data RecoverableSignature
- data Tweak
- importSecKey :: ByteString -> Maybe SecKey
- importPubKeyXY :: ByteString -> Maybe PubKeyXY
- exportPubKeyXY :: Bool -> PubKeyXY -> ByteString
- importPubKeyXO :: ByteString -> Maybe PubKeyXO
- exportPubKeyXO :: PubKeyXO -> ByteString
- importSignature :: ByteString -> Maybe Signature
- exportSignatureCompact :: Signature -> ByteString
- exportSignatureDer :: Signature -> ByteString
- importRecoverableSignature :: ByteString -> Maybe RecoverableSignature
- exportRecoverableSignature :: RecoverableSignature -> 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
- recSigToSig :: RecoverableSignature -> Signature
- derivePubKey :: SecKey -> PubKeyXY
- keyPairCreate :: SecKey -> KeyPair
- keyPairPubKeyXY :: KeyPair -> PubKeyXY
- keyPairPubKeyXO :: KeyPair -> (PubKeyXO, Bool)
- xyToXO :: PubKeyXY -> (PubKeyXO, Bool)
- ecSecKeyTweakAdd :: SecKey -> Tweak -> Maybe SecKey
- ecSecKeyTweakMul :: SecKey -> Tweak -> Maybe SecKey
- keyPairPubKeyXOTweakAdd :: KeyPair -> Tweak -> Maybe KeyPair
- pubKeyCombine :: [PubKeyXY] -> Maybe PubKeyXY
- pubKeyNegate :: PubKeyXY -> PubKeyXY
- secKeyNegate :: SecKey -> SecKey
- pubKeyTweakAdd :: PubKeyXY -> Tweak -> Maybe PubKeyXY
- pubKeyTweakMul :: PubKeyXY -> Tweak -> Maybe PubKeyXY
- pubKeyXOTweakAdd :: PubKeyXO -> Tweak -> Maybe PubKeyXY
- pubKeyXOTweakAddCheck :: PubKeyXO -> Bool -> PubKeyXO -> Tweak -> Bool
- schnorrSign :: KeyPair -> ByteString -> Maybe Signature
- data SchnorrExtra a = Storable a => SchnorrExtra {
- schnorrExtraNonceFunHardened :: ByteString -> SecKey -> PubKeyXO -> ByteString -> a -> Maybe (SizedByteArray 32 ByteString)
- schnorrExtraData :: a
- schnorrSignCustom :: forall a. KeyPair -> ByteString -> SchnorrExtra a -> Maybe Signature
- schnorrVerify :: PubKeyXO -> ByteString -> Signature -> Bool
- taggedSha256 :: ByteString -> ByteString -> Digest SHA256
- ecdh :: SecKey -> PubKeyXY -> Digest SHA256
Core Types
data RecoverableSignature Source #
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
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
importSignature :: ByteString -> Maybe Signature Source #
Parses Signature
from DER (71 | 72 | 73 bytes) or Compact (64 bytes) representations.
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
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 :: KeyPair -> ByteString -> Maybe Signature Source #
Compute a schnorr signature using a KeyPair
. The ByteString
must be 32 bytes long to get a Just
out of this
function
data SchnorrExtra a Source #
Extra parameters object for alternative nonce generation
Storable a => SchnorrExtra | |
|
schnorrSignCustom :: forall a. KeyPair -> ByteString -> SchnorrExtra a -> Maybe Signature Source #
Compute a schnorr signature with an alternative scheme for generating nonces, it is not recommended you use this
unless you know what you are doing. Instead, favor the usage of schnorrSign
schnorrVerify :: PubKeyXO -> ByteString -> Signature -> Bool Source #
Verify the authenticity of a schnorr signature. True
means the Signature
is correct.
Other
taggedSha256 :: ByteString -> ByteString -> Digest SHA256 Source #
Generate a tagged sha256 digest as specified in BIP340