haskoin-core-0.8.2: Bitcoin & Bitcoin Cash library for Haskell

CopyrightNo rights reserved
LicenseUNLICENSE
Maintainerxenog@protonmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Network.Haskoin.Keys

Contents

Description

ECDSA private and public keys, extended keys (BIP-32) and mnemonic sentences (BIP-39).

Synopsis

Mnemonic Sentences

type Entropy = ByteString Source #

Random data used to create a mnemonic sentence. Use a good entropy source. You will get your coins stolen if you don't. You have been warned.

type Mnemonic = Text Source #

Human-readable mnemonic sentence.

type Passphrase = ByteString Source #

Optional passphrase for mnemnoic sentence.

type Seed = ByteString Source #

Seed for a private key from a mnemonic sentence.

toMnemonic :: Entropy -> Either String Mnemonic Source #

Provide intial Entropy as a ByteString of length multiple of 4 bytes. Output a Mnemonic sentence.

fromMnemonic :: Mnemonic -> Either String Entropy Source #

Revert toMnemonic. Do not use this to generate a Seed. Instead use mnemonicToSeed. This outputs the original Entropy used to generate a Mnemonic sentence.

mnemonicToSeed :: Passphrase -> Mnemonic -> Either String Seed Source #

Get a 512-bit Seed from a Mnemonic sentence. Will validate checksum. Passphrase can be used to protect the Mnemonic. Use an empty string as Passphrase if none is required.

Extended Keys

data XPubKey Source #

Data type representing an extended BIP32 public key.

Constructors

XPubKey 

Fields

Instances
Eq XPubKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Methods

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

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

Read XPubKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Show XPubKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Generic XPubKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Associated Types

type Rep XPubKey :: * -> * #

Methods

from :: XPubKey -> Rep XPubKey x #

to :: Rep XPubKey x -> XPubKey #

type Rep XPubKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

data XPrvKey Source #

Data type representing an extended BIP32 private key. An extended key is a node in a tree of key derivations. It has a depth in the tree, a parent node and an index to differentiate it from other siblings.

Constructors

XPrvKey 

Fields

Instances
Eq XPrvKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Methods

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

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

Read XPrvKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Show XPrvKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Generic XPrvKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Associated Types

type Rep XPrvKey :: * -> * #

Methods

from :: XPrvKey -> Rep XPrvKey x #

to :: Rep XPrvKey x -> XPrvKey #

type Rep XPrvKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

type ChainCode = Hash256 Source #

Chain code as specified in BIP-32.

type KeyIndex = Word32 Source #

Index of key as specified in BIP-32.

type Fingerprint = Word32 Source #

Fingerprint of parent

makeXPrvKey :: ByteString -> XPrvKey Source #

Build a BIP32 compatible extended private key from a bytestring. This will produce a root node (depth=0 and parent=0).

deriveXPubKey :: XPrvKey -> XPubKey Source #

Derive an extended public key from an extended private key. This function will preserve the depth, parent, index and chaincode fields of the extended private keys.

prvSubKey Source #

Arguments

:: XPrvKey

extended parent private key

-> KeyIndex

child derivation index

-> XPrvKey

extended child private key

Compute a private, soft child key derivation. A private soft derivation will allow the equivalent extended public key to derive the public key for this child. Given a parent key m and a derivation index i, this function will compute m/i.

Soft derivations allow for more flexibility such as read-only wallets. However, care must be taken not the leak both the parent extended public key and one of the extended child private keys as this would compromise the extended parent private key.

pubSubKey Source #

Arguments

:: XPubKey

extended parent public key

-> KeyIndex

child derivation index

-> XPubKey

extended child public key

Compute a public, soft child key derivation. Given a parent key M and a derivation index i, this function will compute M/i.

hardSubKey Source #

Arguments

:: XPrvKey

extended parent private key

-> KeyIndex

child derivation index

-> XPrvKey

extended child private key

Compute a hard child key derivation. Hard derivations can only be computed for private keys. Hard derivations do not allow the parent public key to derive the child public keys. However, they are safer as a breach of the parent public key and child private keys does not lead to a breach of the parent private key. Given a parent key m and a derivation index i, this function will compute m/i'.

xPrvIsHard :: XPrvKey -> Bool Source #

Returns true if the extended private key was derived through a hard derivation.

xPubIsHard :: XPubKey -> Bool Source #

Returns true if the extended public key was derived through a hard derivation.

xPrvChild :: XPrvKey -> KeyIndex Source #

Returns the derivation index of this extended private key without the hard bit set.

xPubChild :: XPubKey -> KeyIndex Source #

Returns the derivation index of this extended public key without the hard bit set.

xPubID :: XPubKey -> Hash160 Source #

Computes the key identifier of an extended public key.

xPrvID :: XPrvKey -> Hash160 Source #

Computes the key identifier of an extended private key.

xPubFP :: XPubKey -> Fingerprint Source #

Computes the key fingerprint of an extended public key.

xPrvFP :: XPrvKey -> Fingerprint Source #

Computes the key fingerprint of an extended private key.

xPubAddr :: XPubKey -> Address Source #

Computer the Address of an extended public key.

xPubExport :: Network -> XPubKey -> Base58 Source #

Exports an extended public key to the BIP32 key export format (Base58).

xPubFromJSON :: Network -> Value -> Parser XPubKey Source #

Decode an extended public key from a JSON string

xPrvExport :: Network -> XPrvKey -> Base58 Source #

Exports an extended private key to the BIP32 key export format (Base58).

xPrvFromJSON :: Network -> Value -> Parser XPrvKey Source #

Decode an extended private key from a JSON string

xPubImport :: Network -> Base58 -> Maybe XPubKey Source #

Decodes a BIP32 encoded extended public key. This function will fail if invalid base 58 characters are detected or if the checksum fails.

xPrvImport :: Network -> Base58 -> Maybe XPrvKey Source #

Decodes a BIP32 encoded extended private key. This function will fail if invalid base 58 characters are detected or if the checksum fails.

xPrvWif :: Network -> XPrvKey -> Base58 Source #

Export an extended private key to WIF (Wallet Import Format).

putXPrvKey :: Network -> Putter XPrvKey Source #

Serialize an extended private key.

putXPubKey :: Network -> Putter XPubKey Source #

Serialize an extended public key.

getXPrvKey :: Network -> Get XPrvKey Source #

Parse a binary extended private key.

getXPubKey :: Network -> Get XPubKey Source #

Parse a binary extended public key.

Helper Functions

prvSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)] Source #

Cyclic list of all private soft child key derivations of a parent key starting from an offset index.

pubSubKeys :: XPubKey -> KeyIndex -> [(XPubKey, KeyIndex)] Source #

Cyclic list of all public soft child key derivations of a parent key starting from an offset index.

hardSubKeys :: XPrvKey -> KeyIndex -> [(XPrvKey, KeyIndex)] Source #

Cyclic list of all hard child key derivations of a parent key starting from an offset index.

deriveAddr :: XPubKey -> KeyIndex -> (Address, PubKey) Source #

Derive an address from a public key and an index. The derivation type is a public, soft derivation.

deriveAddrs :: XPubKey -> KeyIndex -> [(Address, PubKey, KeyIndex)] Source #

Cyclic list of all addresses derived from a public key starting from an offset index. The derivation types are public, soft derivations.

deriveMSAddr :: [XPubKey] -> Int -> KeyIndex -> (Address, RedeemScript) Source #

Derive a multisig address from a list of public keys, the number of required signatures m and a derivation index. The derivation type is a public, soft derivation.

deriveMSAddrs :: [XPubKey] -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)] Source #

Cyclic list of all multisig addresses derived from a list of public keys, a number of required signatures m and starting from an offset index. The derivation type is a public, soft derivation.

cycleIndex :: KeyIndex -> [KeyIndex] Source #

Helper function to go through derivation indices.

Derivation Paths

data DerivPathI t where Source #

Data type representing a derivation path. Two constructors are provided for specifying soft or hard derivations. The path /0/1'/2 for example can be expressed as Deriv :/ 0 :| 1 :/ 2. The HardOrAny and AnyOrSoft type classes are used to constrain the valid values for the phantom type t. If you mix hard '(:|)' and soft '(:/)' paths, the only valid type for t is AnyDeriv. Otherwise, t can be HardDeriv if you only have hard derivation or SoftDeriv if you only have soft derivations.

Using this type is as easy as writing the required derivation like in these example:

Deriv :/ 0 :/ 1 :/ 2 :: SoftPath
Deriv :| 0 :| 1 :| 2 :: HardPath
Deriv :| 0 :/ 1 :/ 2 :: DerivPath

Constructors

(:|) :: HardOrAny t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t 
(:/) :: AnyOrSoft t => !(DerivPathI t) -> !KeyIndex -> DerivPathI t 
Deriv :: DerivPathI t 
Instances
Read SoftPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Read DerivPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Read HardPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Show SoftPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Show DerivPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Show HardPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

IsString SoftPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

IsString DerivPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

IsString HardPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

FromJSON SoftPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

FromJSON DerivPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

FromJSON HardPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Serialize DerivPath Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Eq (DerivPathI t) Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Methods

(==) :: DerivPathI t -> DerivPathI t -> Bool #

(/=) :: DerivPathI t -> DerivPathI t -> Bool #

ToJSON (DerivPathI t) Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

data AnyDeriv Source #

Phantom type signaling no knowledge about derivation path: can be hardened or not.

data HardDeriv Source #

Phantom type signaling a hardened derivation path that can only be computed from private extended key.

data SoftDeriv Source #

Phantom type signaling derivation path including only non-hardened paths that can be computed from an extended public key.

class HardOrAny a Source #

Helper class to perform validations on a hardened derivation path.

Instances
HardOrAny AnyDeriv Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

HardOrAny HardDeriv Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

class AnyOrSoft a Source #

Helper class to perform validations on a non-hardened derivation path.

Instances
AnyOrSoft SoftDeriv Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

AnyOrSoft AnyDeriv Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

type DerivPath = DerivPathI AnyDeriv Source #

Any derivation path.

type HardPath = DerivPathI HardDeriv Source #

Hardened derivation path. Can be computed from extended private key only.

type SoftPath = DerivPathI SoftDeriv Source #

Non-hardened derivation path can be computed from extended public key.

derivePath :: DerivPathI t -> XPrvKey -> XPrvKey Source #

Derive a private key from a derivation path

derivePubPath :: SoftPath -> XPubKey -> XPubKey Source #

Derive a public key from a soft derivation path

toHard :: DerivPathI t -> Maybe HardPath Source #

Turn a derivation path into a hard derivation path. Will fail if the path contains soft derivations.

toSoft :: DerivPathI t -> Maybe SoftPath Source #

Turn a derivatino path into a soft derivation path. Will fail if the path has hard derivations.

toGeneric :: DerivPathI t -> DerivPath Source #

Make a derivation path generic.

(++/) :: DerivPathI t1 -> DerivPathI t2 -> DerivPath Source #

Append two derivation paths together. The result will be a mixed derivation path.

pathToStr :: DerivPathI t -> String Source #

Convert a derivation path to a human-readable string.

listToPath :: [KeyIndex] -> DerivPath Source #

Convert a list of derivation indices to a derivation path.

pathToList :: DerivPathI t -> [KeyIndex] Source #

Get a list of derivation indices from a derivation path.

Derivation Path Parser

data XKey Source #

Data type representing a private or public key with its respective network.

Constructors

XPrv 
XPub 
Instances
Eq XKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Methods

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

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

Show XKey Source # 
Instance details

Defined in Network.Haskoin.Keys.Extended

Methods

showsPrec :: Int -> XKey -> ShowS #

show :: XKey -> String #

showList :: [XKey] -> ShowS #

parsePath :: String -> Maybe ParsedPath Source #

Parse derivation path string for extended key. Forms: m/0'/2, M/2/3/4.

parseHard :: String -> Maybe HardPath Source #

Helper function to parse a hard path.

parseSoft :: String -> Maybe SoftPath Source #

Helper function to parse a soft path.

applyPath :: ParsedPath -> XKey -> Either String XKey Source #

Apply a parsed path to an extended key to derive the new key defined in the path. If the path starts with m, a private key will be returned and if the path starts with M, a public key will be returned. Private derivations on a public key, and public derivations with a hard segment, return an error value.

derivePathAddr :: XPubKey -> SoftPath -> KeyIndex -> (Address, PubKey) Source #

Derive an address from a given parent path.

derivePathAddrs :: XPubKey -> SoftPath -> KeyIndex -> [(Address, PubKey, KeyIndex)] Source #

Cyclic list of all addresses derived from a given parent path and starting from the given offset index.

derivePathMSAddr :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> (Address, RedeemScript) Source #

Derive a multisig address from a given parent path. The number of required signatures (m in m of n) is also needed.

derivePathMSAddrs :: [XPubKey] -> SoftPath -> Int -> KeyIndex -> [(Address, RedeemScript, KeyIndex)] Source #

Cyclic list of all multisig addresses derived from a given parent path and starting from the given offset index. The number of required signatures (m in m of n) is also needed.

concatBip32Segments :: [Bip32PathIndex] -> DerivPath Source #

Concatenate derivation path indices into a derivation path.

Public & Private Keys

data PubKeyI Source #

Elliptic curve public key type with expected serialized compression flag.

Constructors

PubKeyI 
Instances
Eq PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

Methods

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

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

Read PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

Show PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

IsString PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

Methods

fromString :: String -> PubKeyI #

Generic PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

Associated Types

type Rep PubKeyI :: * -> * #

Methods

from :: PubKeyI -> Rep PubKeyI x #

to :: Rep PubKeyI x -> PubKeyI #

Hashable PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

Methods

hashWithSalt :: Int -> PubKeyI -> Int #

hash :: PubKeyI -> Int #

ToJSON PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

FromJSON PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

Serialize PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

type Rep PubKeyI Source # 
Instance details

Defined in Network.Haskoin.Keys.Common

type Rep PubKeyI = D1 (MetaData "PubKeyI" "Network.Haskoin.Keys.Common" "haskoin-core-0.8.2-DBbfowLuwQJDnYGV2ClFSV" 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 

exportPubKey :: Bool -> PubKey -> ByteString #

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

importPubKey :: ByteString -> Maybe PubKey #

Import DER-encoded public key.

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 #

Get 32-byte secret key.

secKey :: ByteString -> Maybe SecKey #

Import 32-byte ByteString as SecKey.