| License | UNLICENSE |
|---|---|
| Maintainer | Jean-Pierre Rupp <jprupp@protonmail.ch> |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Crypto.Secp256k1.Internal.Base
Description
Crytpographic functions from Bitcoin’s secp256k1 library.
The API for this module may change at any time. This is an internal module only exposed for hacking and experimentation.
Synopsis
- newtype PubKey = PubKey {
- get :: ByteString
- newtype Msg = Msg {
- get :: ByteString
- newtype Sig = Sig {
- get :: ByteString
- newtype SecKey = SecKey {
- get :: ByteString
- newtype Tweak = Tweak {
- get :: ByteString
- newtype CompactSig = CompactSig {
- get :: ByteString
- sig :: ByteString -> Maybe Sig
- pubKey :: ByteString -> Maybe PubKey
- msg :: ByteString -> Maybe Msg
- secKey :: ByteString -> Maybe SecKey
- compactSig :: ByteString -> Maybe CompactSig
- normalizeSig :: Ctx -> Sig -> Maybe Sig
- tweak :: ByteString -> Maybe Tweak
- importPubKey :: Ctx -> ByteString -> Maybe PubKey
- exportPubKey :: Ctx -> Bool -> PubKey -> ByteString
- exportCompactSig :: Ctx -> Sig -> CompactSig
- importCompactSig :: Ctx -> CompactSig -> Maybe Sig
- importSig :: Ctx -> ByteString -> Maybe Sig
- exportSig :: Ctx -> Sig -> ByteString
- verifySig :: Ctx -> PubKey -> Sig -> Msg -> Bool
- signMsg :: Ctx -> SecKey -> Msg -> Sig
- derivePubKey :: Ctx -> SecKey -> PubKey
- tweakAddSecKey :: Ctx -> SecKey -> Tweak -> Maybe SecKey
- tweakMulSecKey :: Ctx -> SecKey -> Tweak -> Maybe SecKey
- tweakAddPubKey :: Ctx -> PubKey -> Tweak -> Maybe PubKey
- tweakMulPubKey :: Ctx -> PubKey -> Tweak -> Maybe PubKey
- combinePubKeys :: Ctx -> [PubKey] -> Maybe PubKey
- tweakNegate :: Ctx -> Tweak -> Maybe Tweak
Documentation
Constructors
| PubKey | |
Fields
| |
Instances
| IsString PubKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base Methods fromString :: String -> PubKey # | |
| Generic PubKey Source # | |
| Read PubKey Source # | |
| Show PubKey Source # | |
| NFData PubKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| Eq PubKey Source # | |
| Hashable PubKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| type Rep PubKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base type Rep PubKey = D1 ('MetaData "PubKey" "Crypto.Secp256k1.Internal.Base" "secp256k1-haskell-1.2.0-5hhTrFzbY7H83oJyj7uSnR" 'True) (C1 ('MetaCons "PubKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "get") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
Constructors
| Msg | |
Fields
| |
Instances
| Arbitrary Msg Source # | |
| IsString Msg Source # | |
Defined in Crypto.Secp256k1.Internal.Base Methods fromString :: String -> Msg # | |
| Generic Msg Source # | |
| Read Msg Source # | |
| Show Msg Source # | |
| NFData Msg Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| Eq Msg Source # | |
| Hashable Msg Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| type Rep Msg Source # | |
Defined in Crypto.Secp256k1.Internal.Base type Rep Msg = D1 ('MetaData "Msg" "Crypto.Secp256k1.Internal.Base" "secp256k1-haskell-1.2.0-5hhTrFzbY7H83oJyj7uSnR" 'True) (C1 ('MetaCons "Msg" 'PrefixI 'True) (S1 ('MetaSel ('Just "get") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
Constructors
| Sig | |
Fields
| |
Instances
| IsString Sig Source # | |
Defined in Crypto.Secp256k1.Internal.Base Methods fromString :: String -> Sig # | |
| Generic Sig Source # | |
| Read Sig Source # | |
| Show Sig Source # | |
| NFData Sig Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| Eq Sig Source # | |
| Hashable Sig Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| type Rep Sig Source # | |
Defined in Crypto.Secp256k1.Internal.Base type Rep Sig = D1 ('MetaData "Sig" "Crypto.Secp256k1.Internal.Base" "secp256k1-haskell-1.2.0-5hhTrFzbY7H83oJyj7uSnR" 'True) (C1 ('MetaCons "Sig" 'PrefixI 'True) (S1 ('MetaSel ('Just "get") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
Constructors
| SecKey | |
Fields
| |
Instances
| Arbitrary SecKey Source # | |
| IsString SecKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base Methods fromString :: String -> SecKey # | |
| Generic SecKey Source # | |
| Read SecKey Source # | |
| Show SecKey Source # | |
| NFData SecKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| Eq SecKey Source # | |
| Hashable SecKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| type Rep SecKey Source # | |
Defined in Crypto.Secp256k1.Internal.Base type Rep SecKey = D1 ('MetaData "SecKey" "Crypto.Secp256k1.Internal.Base" "secp256k1-haskell-1.2.0-5hhTrFzbY7H83oJyj7uSnR" 'True) (C1 ('MetaCons "SecKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "get") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
Constructors
| Tweak | |
Fields
| |
Instances
| IsString Tweak Source # | |
Defined in Crypto.Secp256k1.Internal.Base Methods fromString :: String -> Tweak # | |
| Generic Tweak Source # | |
| Read Tweak Source # | |
| Show Tweak Source # | |
| NFData Tweak Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| Eq Tweak Source # | |
| Hashable Tweak Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| type Rep Tweak Source # | |
Defined in Crypto.Secp256k1.Internal.Base type Rep Tweak = D1 ('MetaData "Tweak" "Crypto.Secp256k1.Internal.Base" "secp256k1-haskell-1.2.0-5hhTrFzbY7H83oJyj7uSnR" 'True) (C1 ('MetaCons "Tweak" 'PrefixI 'True) (S1 ('MetaSel ('Just "get") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
newtype CompactSig Source #
Constructors
| CompactSig | |
Fields
| |
Instances
| Generic CompactSig Source # | |
Defined in Crypto.Secp256k1.Internal.Base Associated Types type Rep CompactSig :: Type -> Type # | |
| NFData CompactSig Source # | |
Defined in Crypto.Secp256k1.Internal.Base Methods rnf :: CompactSig -> () # | |
| Eq CompactSig Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| Hashable CompactSig Source # | |
Defined in Crypto.Secp256k1.Internal.Base | |
| type Rep CompactSig Source # | |
Defined in Crypto.Secp256k1.Internal.Base type Rep CompactSig = D1 ('MetaData "CompactSig" "Crypto.Secp256k1.Internal.Base" "secp256k1-haskell-1.2.0-5hhTrFzbY7H83oJyj7uSnR" 'True) (C1 ('MetaCons "CompactSig" 'PrefixI 'True) (S1 ('MetaSel ('Just "get") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) | |
sig :: ByteString -> Maybe Sig Source #
Import 64-byte ByteString as Sig.
pubKey :: ByteString -> Maybe PubKey Source #
Import 64-byte ByteString as PubKey.
msg :: ByteString -> Maybe Msg Source #
Import 32-byte ByteString as Msg.
secKey :: ByteString -> Maybe SecKey Source #
Import 32-byte ByteString as SecKey.
compactSig :: ByteString -> Maybe CompactSig Source #
normalizeSig :: Ctx -> Sig -> Maybe Sig Source #
Convert signature to a normalized lower-S form. Nothing indicates that it
was already normal.
tweak :: ByteString -> Maybe Tweak Source #
32-Byte ByteString as Tweak.
importPubKey :: Ctx -> ByteString -> Maybe PubKey Source #
Import DER-encoded public key.
exportPubKey :: Ctx -> Bool -> PubKey -> ByteString Source #
Encode public key as DER. First argument True for compressed output.
exportCompactSig :: Ctx -> Sig -> CompactSig Source #
importCompactSig :: Ctx -> CompactSig -> Maybe Sig Source #
verifySig :: Ctx -> PubKey -> Sig -> Msg -> Bool Source #
Verify message signature. True means that the signature is correct.
tweakAddPubKey :: Ctx -> PubKey -> Tweak -> Maybe PubKey Source #
Add tweak to public key. Tweak is multiplied first by G to obtain a point.