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

Haskoin.Keys.Extended

Description

BIP-32 extended keys.

Synopsis

Extended Keys

data XPubKey Source #

Data type representing an extended BIP32 public key.

Constructors

XPubKey 

Fields

Instances

Instances details
Eq XPubKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

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

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

Read XPubKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show XPubKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic XPubKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep XPubKey :: Type -> Type #

Methods

from :: XPubKey -> Rep XPubKey x #

to :: Rep XPubKey x -> XPubKey #

Hashable XPubKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

hashWithSalt :: Int -> XPubKey -> Int #

hash :: XPubKey -> Int #

Serialize XPubKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData XPubKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: XPubKey -> () #

type Rep XPubKey Source # 
Instance details

Defined in 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

Instances details
Eq XPrvKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

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

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

Read XPrvKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show XPrvKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic XPrvKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep XPrvKey :: Type -> Type #

Methods

from :: XPrvKey -> Rep XPrvKey x #

to :: Rep XPrvKey x -> XPrvKey #

Hashable XPrvKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

hashWithSalt :: Int -> XPrvKey -> Int #

hash :: XPrvKey -> Int #

Serialize XPrvKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData XPrvKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: XPrvKey -> () #

type Rep XPrvKey Source # 
Instance details

Defined in 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

newtype DerivationException Source #

A derivation exception is thrown in the very unlikely event that a derivation is invalid.

Instances

Instances details
Eq DerivationException Source # 
Instance details

Defined in Haskoin.Keys.Extended

Read DerivationException Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show DerivationException Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic DerivationException Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep DerivationException :: Type -> Type #

Exception DerivationException Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData DerivationException Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: DerivationException -> () #

type Rep DerivationException Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep DerivationException = D1 ('MetaData "DerivationException" "Haskoin.Keys.Extended" "haskoin-core-0.19.0-inplace" 'True) (C1 ('MetaCons "DerivationException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

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 #

Compute a standard P2PKH address for an extended public key.

xPubWitnessAddr :: XPubKey -> Address Source #

Compute a SegWit P2WPKH address for an extended public key.

xPubCompatWitnessAddr :: XPubKey -> Address Source #

Compute a backwards-compatible SegWit P2SH-P2WPKH address for 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 a standard address from an extended public key and an index.

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

Derive a SegWit P2WPKH address from an extended public key and an index.

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

Derive a backwards-compatible SegWit P2SH-P2WPKH address from an extended public key and an index.

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

Cyclic list of all addresses derived from a public key starting from an offset index.

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

Cyclic list of all SegWit P2WPKH addresses derived from a public key starting from an offset index.

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

Cyclic list of all backwards-compatible SegWit P2SH-P2WPKH addresses derived from a public key starting from an offset index.

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

Instances details
Read SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Read DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Read HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

IsString SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

IsString DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

IsString HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

FromJSON SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

FromJSON DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

FromJSON HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Serialize SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Serialize DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Serialize HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Eq (DerivPathI t) Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

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

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

Ord (DerivPathI t) Source # 
Instance details

Defined in Haskoin.Keys.Extended

ToJSON (DerivPathI t) Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData (DerivPathI t) Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: DerivPathI t -> () #

data AnyDeriv Source #

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

Instances

Instances details
Read DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

IsString DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic AnyDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep AnyDeriv :: Type -> Type #

Methods

from :: AnyDeriv -> Rep AnyDeriv x #

to :: Rep AnyDeriv x -> AnyDeriv #

FromJSON DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Serialize DerivPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData AnyDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: AnyDeriv -> () #

AnyOrSoft AnyDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

HardOrAny AnyDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep AnyDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep AnyDeriv = D1 ('MetaData "AnyDeriv" "Haskoin.Keys.Extended" "haskoin-core-0.19.0-inplace" 'False) (V1 :: Type -> Type)

data HardDeriv Source #

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

Instances

Instances details
Read HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

IsString HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic HardDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep HardDeriv :: Type -> Type #

FromJSON HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Serialize HardPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData HardDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: HardDeriv -> () #

HardOrAny HardDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep HardDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep HardDeriv = D1 ('MetaData "HardDeriv" "Haskoin.Keys.Extended" "haskoin-core-0.19.0-inplace" 'False) (V1 :: Type -> Type)

data SoftDeriv Source #

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

Instances

Instances details
Read SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

IsString SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic SoftDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep SoftDeriv :: Type -> Type #

FromJSON SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Serialize SoftPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData SoftDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: SoftDeriv -> () #

AnyOrSoft SoftDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep SoftDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep SoftDeriv = D1 ('MetaData "SoftDeriv" "Haskoin.Keys.Extended" "haskoin-core-0.19.0-inplace" 'False) (V1 :: Type -> Type)

class HardOrAny a Source #

Helper class to perform validations on a hardened derivation path.

Instances

Instances details
HardOrAny AnyDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

HardOrAny HardDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

class AnyOrSoft a Source #

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

Instances

Instances details
AnyOrSoft SoftDeriv Source # 
Instance details

Defined in Haskoin.Keys.Extended

AnyOrSoft AnyDeriv Source # 
Instance details

Defined in 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.

data Bip32PathIndex Source #

Type for BIP32 path index element.

Instances

Instances details
Eq Bip32PathIndex Source # 
Instance details

Defined in Haskoin.Keys.Extended

Read Bip32PathIndex Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show Bip32PathIndex Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic Bip32PathIndex Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep Bip32PathIndex :: Type -> Type #

NFData Bip32PathIndex Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: Bip32PathIndex -> () #

type Rep Bip32PathIndex Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep Bip32PathIndex = D1 ('MetaData "Bip32PathIndex" "Haskoin.Keys.Extended" "haskoin-core-0.19.0-inplace" 'False) (C1 ('MetaCons "Bip32HardIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeyIndex)) :+: C1 ('MetaCons "Bip32SoftIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeyIndex)))

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 derivation 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

Instances details
Eq XKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

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

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

Show XKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

showsPrec :: Int -> XKey -> ShowS #

show :: XKey -> String #

showList :: [XKey] -> ShowS #

Generic XKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep XKey :: Type -> Type #

Methods

from :: XKey -> Rep XKey x #

to :: Rep XKey x -> XKey #

NFData XKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: XKey -> () #

type Rep XKey Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep XKey = D1 ('MetaData "XKey" "Haskoin.Keys.Extended" "haskoin-core-0.19.0-inplace" 'False) (C1 ('MetaCons "XPrv" 'PrefixI 'True) (S1 ('MetaSel ('Just "getXKeyPrv") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 XPrvKey) :*: S1 ('MetaSel ('Just "getXKeyNet") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Network)) :+: C1 ('MetaCons "XPub" 'PrefixI 'True) (S1 ('MetaSel ('Just "getXKeyPub") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 XPubKey) :*: S1 ('MetaSel ('Just "getXKeyNet") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Network)))

data ParsedPath Source #

Type for parsing derivation paths of the form m/1/2'/3 or M/1/2'/3.

Instances

Instances details
Eq ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Read ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Show ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

IsString ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Generic ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Associated Types

type Rep ParsedPath :: Type -> Type #

ToJSON ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

FromJSON ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

NFData ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

Methods

rnf :: ParsedPath -> () #

type Rep ParsedPath Source # 
Instance details

Defined in Haskoin.Keys.Extended

type Rep ParsedPath = D1 ('MetaData "ParsedPath" "Haskoin.Keys.Extended" "haskoin-core-0.19.0-inplace" 'False) (C1 ('MetaCons "ParsedPrv" 'PrefixI 'True) (S1 ('MetaSel ('Just "getParsedPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DerivPath)) :+: (C1 ('MetaCons "ParsedPub" 'PrefixI 'True) (S1 ('MetaSel ('Just "getParsedPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DerivPath)) :+: C1 ('MetaCons "ParsedEmpty" 'PrefixI 'True) (S1 ('MetaSel ('Just "getParsedPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DerivPath))))

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.