haskoin-core-0.22.0: Bitcoin & Bitcoin Cash library for Haskell
CopyrightNo rights reserved
LicenseMIT
Maintainerjprupp@protonmail.ch
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Haskoin.Keys.Common

Description

ECDSA private and public key functions.

Synopsis

Public & Private Keys

data PubKeyI Source #

Elliptic curve public key type with expected serialized compression flag.

Constructors

PubKeyI 

Fields

Instances

Instances details
FromJSON PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

parseJSON :: Value -> Parser PubKeyI

parseJSONList :: Value -> Parser [PubKeyI]

omittedField :: Maybe PubKeyI

ToJSON PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

toJSON :: PubKeyI -> Value

toEncoding :: PubKeyI -> Encoding

toJSONList :: [PubKeyI] -> Value

toEncodingList :: [PubKeyI] -> Encoding

omitField :: PubKeyI -> Bool

IsString PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

fromString :: String -> PubKeyI #

Generic PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Associated Types

type Rep PubKeyI :: Type -> Type #

Methods

from :: PubKeyI -> Rep PubKeyI x #

to :: Rep PubKeyI x -> PubKeyI #

Read PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Show PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Binary PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

put :: PubKeyI -> Put #

get :: Get PubKeyI #

putList :: [PubKeyI] -> Put #

Serial PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

serialize :: MonadPut m => PubKeyI -> m ()

deserialize :: MonadGet m => m PubKeyI

Serialize PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

put :: Putter PubKeyI

get :: Get PubKeyI

NFData PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

rnf :: PubKeyI -> () #

Eq PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

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

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

Hashable PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

hashWithSalt :: Int -> PubKeyI -> Int

hash :: PubKeyI -> Int

type Rep PubKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

type Rep PubKeyI = D1 ('MetaData "PubKeyI" "Haskoin.Keys.Common" "haskoin-core-0.22.0-inplace" 'False) (C1 ('MetaCons "PubKeyI" 'PrefixI 'True) (S1 ('MetaSel ('Just "pubKeyPoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PubKey) :*: S1 ('MetaSel ('Just "pubKeyCompressed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))

data SecKeyI Source #

Elliptic curve private key type with expected public key compression information. Compression information is stored in private key WIF formats and needs to be preserved to generate the correct address from the corresponding public key.

Constructors

SecKeyI 

Fields

Instances

Instances details
Generic SecKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Associated Types

type Rep SecKeyI :: Type -> Type #

Methods

from :: SecKeyI -> Rep SecKeyI x #

to :: Rep SecKeyI x -> SecKeyI #

Read SecKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Show SecKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

NFData SecKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

rnf :: SecKeyI -> () #

Eq SecKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

Methods

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

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

type Rep SecKeyI Source # 
Instance details

Defined in Haskoin.Keys.Common

type Rep SecKeyI = D1 ('MetaData "SecKeyI" "Haskoin.Keys.Common" "haskoin-core-0.22.0-inplace" 'False) (C1 ('MetaCons "SecKeyI" 'PrefixI 'True) (S1 ('MetaSel ('Just "secKeyData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecKey) :*: S1 ('MetaSel ('Just "secKeyCompressed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))

exportPubKey :: Bool -> PubKey -> ByteString #

wrapPubKey :: Bool -> PubKey -> PubKeyI Source #

Wrap a public key from secp256k1 library adding information about compression.

derivePubKeyI :: SecKeyI -> PubKeyI Source #

Derives a public key from a private key. This function will preserve compression flag.

wrapSecKey :: Bool -> SecKey -> SecKeyI Source #

Wrap private key with corresponding public key compression flag.

fromMiniKey :: ByteString -> Maybe SecKeyI Source #

Decode Casascius mini private keys (22 or 30 characters).

tweakPubKey :: PubKey -> Hash256 -> Maybe PubKey Source #

Tweak a public key.

tweakSecKey :: SecKey -> Hash256 -> Maybe SecKey Source #

Tweak a private key.

getSecKey :: SecKey -> ByteString #

secKey :: ByteString -> Maybe SecKey #

Private Key Wallet Import Format (WIF)

fromWif :: Network -> Base58 -> Maybe SecKeyI Source #

Decode private key from WIF (wallet import format) string.

toWif :: Network -> SecKeyI -> Base58 Source #

Encode private key into a WIF string.