slip32-0.1: SLIP-0032: Extended serialization format for BIP-32 wallets

Safe HaskellNone
LanguageHaskell2010

SLIP32

Contents

Description

SLIP-0032 is an extended serialization format for BIP-0032 wallets

Implementation based on the draft SLIP-0032 spec.

Synopsis

Parsing

parse :: ByteString -> Maybe (Either XPub XPrv) Source #

Parse either an XPub or an XPrv from its SLIP-0032 representation.

parseXPub :: ByteString -> Maybe XPub Source #

Parse an XPub from its SLIP-0032 representation.

parseXPrv :: ByteString -> Maybe XPrv Source #

Parse an XPrv from its SLIP-0032 representation.

Text

parseText :: Text -> Maybe (Either XPub XPrv) Source #

Parse either an XPub or an XPrv from its SLIP-0032 representation.

Like parse, but takes Text.

parseXPubText :: Text -> Maybe XPub Source #

Parse an XPub from its SLIP-0032 representation.

Like parseXPub, but takes Text.

parseXPrvText :: Text -> Maybe XPrv Source #

Parse an XPrv from its SLIP-0032 representation.

Like parseXPrv, but takes Text.

Rendering

renderXPub :: XPub -> ByteString Source #

Render an XPub using the SLIP-0032 encoding.

renderXPrv :: XPrv -> ByteString Source #

Render an XPub using the SLIP-0032 encoding.

Text

renderXPubText :: XPub -> Text Source #

Render an XPub using the SLIP-0032 encoding.

The rendered Text is ASCII compatible.

renderXPrvText :: XPrv -> Text Source #

Render an XPub using the SLIP-0032 encoding.

The rendered Text is ASCII compatible.

Public key

data XPub Source #

Extended public key.

Constructors

XPub !Path !Chain !Pub 
Instances
Eq XPub Source # 
Instance details

Defined in SLIP32

Methods

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

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

Show XPub Source # 
Instance details

Defined in SLIP32

Methods

showsPrec :: Int -> XPub -> ShowS #

show :: XPub -> String #

showList :: [XPub] -> ShowS #

data Pub Source #

Public key.

Construct with pub.

Instances
Eq Pub Source # 
Instance details

Defined in SLIP32

Methods

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

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

Show Pub Source # 
Instance details

Defined in SLIP32

Methods

showsPrec :: Int -> Pub -> ShowS #

show :: Pub -> String #

showList :: [Pub] -> ShowS #

pub :: ByteString -> Maybe Pub Source #

Construct a Pub key from its raw bytes.

  • 33 bytes in total, containing \(ser_{P}(P)\).
  • The leftmost byte is either 0x02 or 0x03, depending on the parity of the omitted y coordinate.
  • The remaining 32 bytes are \(ser_{256}(x)\).

See Bitcoin's BIP-0032 for details.

Nothing if something is not satisfied.

unPub :: Pub -> ByteString Source #

Obtain the 33 raw bytes inside a Pub. See pub.

Private key

data XPrv Source #

Extended private key.

Constructors

XPrv !Path !Chain !Prv 
Instances
Eq XPrv Source # 
Instance details

Defined in SLIP32

Methods

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

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

Show XPrv Source # 
Instance details

Defined in SLIP32

Methods

showsPrec :: Int -> XPrv -> ShowS #

show :: XPrv -> String #

showList :: [XPrv] -> ShowS #

data Prv Source #

Private key.

Construct with prv.

Instances
Eq Prv Source # 
Instance details

Defined in SLIP32

Methods

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

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

Show Prv Source # 
Instance details

Defined in SLIP32

Methods

showsPrec :: Int -> Prv -> ShowS #

show :: Prv -> String #

showList :: [Prv] -> ShowS #

prv :: ByteString -> Maybe Prv Source #

Construct a Prv key from its raw bytes.

  • 33 bytes in total.
  • The leftmost byte is 0x00.
  • The remaining 32 bytes are \(ser_{256}(k)\).

See Bitcoin's BIP-0032 for details.

Nothing if something is not satisfied.

unPrv :: Prv -> ByteString Source #

Obtain the 33 raw bytes inside a Prv. See prv.

Path

data Path Source #

Derivation path.

Construct with path.

Instances
Eq Path Source # 
Instance details

Defined in SLIP32

Methods

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

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

Show Path Source # 
Instance details

Defined in SLIP32

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

path :: [Word32] -> Maybe Path Source #

Construct a derivation Path.

Hardened keys start from \(2^{31}\).

m           = path []
m/0         = path [0]
m/0'        = path [0 + 2^31]
m/1         = path [1]
m/1'        = path [1 + 2^31]
m/0'/1/2'/2 = path [0 + 2^31, 1, 2 + 2^31, 2]

See Bitcoin's BIP-0032 for details.

Returns Nothing if the list length is more than 255.

unPath :: Path -> [Word32] Source #

Obtains the derivation path as a list of up to 255 elements.

Chain

data Chain Source #

Chain code.

Construct with chain.

Instances
Eq Chain Source # 
Instance details

Defined in SLIP32

Methods

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

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

Show Chain Source # 
Instance details

Defined in SLIP32

Methods

showsPrec :: Int -> Chain -> ShowS #

show :: Chain -> String #

showList :: [Chain] -> ShowS #

chain :: ByteString -> Maybe Chain Source #

Construct a Chain code.

See Bitcoin's BIP-0032 for details.

Nothing if the ByteString length is not 32.

unChain :: Chain -> ByteString Source #

Obtain the 32 raw bytes inside a Chain.