cardano-addresses-3.12.0: Library utilities for mnemonic generation and address derivation.
Safe HaskellNone
LanguageHaskell2010

Cardano.Address.Derivation

Synopsis

Overview

These abstractions allow generating root private key, also called Master Key and then basing on it enable address derivation

Key Derivation

Types

data Index (derivationType :: DerivationType) (depth :: Depth) Source #

A derivation index, with phantom-types to disambiguate derivation type.

let accountIx = Index 'Hardened 'AccountK
let addressIx = Index 'Soft 'PaymentK

Since: 1.0.0

Instances

Instances details
Bounded (Index 'Hardened depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

minBound :: Index 'Hardened depth #

maxBound :: Index 'Hardened depth #

Bounded (Index 'Soft depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

minBound :: Index 'Soft depth #

maxBound :: Index 'Soft depth #

Bounded (Index 'WholeDomain depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Eq (Index derivationType depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

(==) :: Index derivationType depth -> Index derivationType depth -> Bool #

(/=) :: Index derivationType depth -> Index derivationType depth -> Bool #

Ord (Index derivationType depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

compare :: Index derivationType depth -> Index derivationType depth -> Ordering #

(<) :: Index derivationType depth -> Index derivationType depth -> Bool #

(<=) :: Index derivationType depth -> Index derivationType depth -> Bool #

(>) :: Index derivationType depth -> Index derivationType depth -> Bool #

(>=) :: Index derivationType depth -> Index derivationType depth -> Bool #

max :: Index derivationType depth -> Index derivationType depth -> Index derivationType depth #

min :: Index derivationType depth -> Index derivationType depth -> Index derivationType depth #

Show (Index derivationType depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

showsPrec :: Int -> Index derivationType depth -> ShowS #

show :: Index derivationType depth -> String #

showList :: [Index derivationType depth] -> ShowS #

Generic (Index derivationType depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Associated Types

type Rep (Index derivationType depth) :: Type -> Type #

Methods

from :: Index derivationType depth -> Rep (Index derivationType depth) x #

to :: Rep (Index derivationType depth) x -> Index derivationType depth #

NFData (Index derivationType depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

rnf :: Index derivationType depth -> () #

Buildable (Index derivationType depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

build :: Index derivationType depth -> Builder

type Rep (Index derivationType depth) Source # 
Instance details

Defined in Cardano.Address.Derivation

type Rep (Index derivationType depth) = D1 ('MetaData "Index" "Cardano.Address.Derivation" "cardano-addresses-3.12.0-CXdZXYlvM2IBJZenPvTIY5" 'True) (C1 ('MetaCons "Index" 'PrefixI 'True) (S1 ('MetaSel ('Just "indexToWord32") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

indexToWord32 :: Index derivationType depth -> Word32 Source #

Get the index as a Word32 @since 3.3.0

indexFromWord32 :: forall ix derivationType depth. (ix ~ Index derivationType depth, Bounded ix) => Word32 -> Maybe ix Source #

Construct derivation path indices from raw Word32 values.

wholeDomainIndex :: Word32 -> Index 'WholeDomain depth Source #

Constructs a full domain Index. This can't fail, unlike fromWord32.

Since: 3.3.0

coerceWholeDomainIndex :: Index ty depth0 -> Index 'WholeDomain depth1 Source #

Upcasts an Index to one with the full Word32 domain.

Since: 3.3.0

nextIndex :: forall ix derivationType depth. (ix ~ Index derivationType depth, Bounded ix) => ix -> Maybe ix Source #

Increment an index, if possible.

Since: 3.3.0

data Depth Source #

Key Depth in the derivation path, according to BIP-0039 / BIP-0044

root | purpose' | cointype' | account' | role | address@
0th      1st         2nd        3rd       4th     5th

We do not manipulate purpose, cointype and change paths directly, so there are no constructors for these.

Since: 1.0.0

data DerivationType Source #

Type of derivation that should be used with the given indexes.

In theory, we should only consider two derivation types: soft and hard.

However, historically, addresses in Cardano used to be generated across both the soft and the hard domain. We therefore introduce a WholeDomain derivation type that is the exact union of Hardened and Soft.

Since: 1.0.0

Constructors

Hardened 
Soft 
WholeDomain 

Abstractions

class GenMasterKey (key :: Depth -> Type -> Type) where Source #

Abstract interface for constructing a Master Key.

Since: 1.0.0

Associated Types

type SecondFactor key :: Type Source #

Methods

genMasterKeyFromMnemonic :: SomeMnemonic -> SecondFactor key -> key 'RootK XPrv Source #

Generate a root key from a corresponding mnemonic.

Since: 1.0.0

genMasterKeyFromXPrv :: XPrv -> key 'RootK XPrv Source #

Generate a root key from a corresponding root XPrv

Since: 1.0.0

class HardDerivation (key :: Depth -> Type -> Type) where Source #

An interface for doing hard derivations from the root private key, Master Key

Since: 1.0.0

Methods

deriveAccountPrivateKey :: key 'RootK XPrv -> Index (AccountIndexDerivationType key) 'AccountK -> key 'AccountK XPrv Source #

Derives account private key from the given root private key, using derivation scheme 2 (see cardano-crypto package for more details).

Since: 1.0.0

deriveAddressPrivateKey :: key 'AccountK XPrv -> WithRole key -> Index (AddressIndexDerivationType key) 'PaymentK -> key 'PaymentK XPrv Source #

Derives address private key from the given account private key, using derivation scheme 2 (see cardano-crypto package for more details).

Since: 1.0.0

Instances

Instances details
HardDerivation Byron Source # 
Instance details

Defined in Cardano.Address.Style.Byron

HardDerivation Icarus Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

HardDerivation Shelley Source # 
Instance details

Defined in Cardano.Address.Style.Shelley

HardDerivation Shared Source # 
Instance details

Defined in Cardano.Address.Style.Shared

class HardDerivation key => SoftDerivation (key :: Depth -> Type -> Type) where Source #

An interface for doing soft derivations from an account public key

Methods

deriveAddressPublicKey :: key 'AccountK XPub -> WithRole key -> Index 'Soft 'PaymentK -> key 'PaymentK XPub Source #

Derives address public key from the given account public key, using derivation scheme 2 (see cardano-crypto package for more details).

This is the preferred way of deriving new sequential address public keys.

Since: 1.0.0

Low-Level Cryptography Primitives

XPrv

type XPrv = XPrv Source #

An opaque type representing an extended private key.

Properties:

Roundtripping
forall xprv. xprvFromBytes (xprvToBytes xprv) == Just xprv
Chain Code Invariance
forall xprv. xprvChainCode xprv == xpubChainCode (toXPub xprv)
Public Key Signature
forall xprv msg. verify (toXPub xprv) msg (sign xprv msg) == True

Since: 1.0.0

xprvFromBytes :: ByteString -> Maybe XPrv Source #

Construct an XPrv from raw ByteString (96 bytes).

Since: 1.0.0

xprvToBytes :: XPrv -> ByteString Source #

Convert an XPrv to a raw ByteString (96 bytes).

Since: 1.0.0

xprvPrivateKey :: XPrv -> ByteString Source #

Extract the private key from an XPrv as a raw ByteString (64 bytes).

Since: 2.0.0

xprvChainCode :: XPrv -> ByteString Source #

Extract the chain code from an XPrv as a raw ByteString (32 bytes).

Since: 2.0.0

toXPub :: HasCallStack => XPrv -> XPub Source #

Derive the XPub associated with an XPrv.

Since: 1.0.0

XPub

type XPub = XPub Source #

An opaque type representing an extended public key.

Properties:

Roundtripping
forall xpub. xpubFromBytes (xpubToBytes xpub) == Just xpub

Since: 1.0.0

xpubFromBytes :: ByteString -> Maybe XPub Source #

Construct an XPub from raw ByteString (64 bytes).

Since: 1.0.0

xpubToBytes :: XPub -> ByteString Source #

Convert an XPub to a raw ByteString (64 bytes).

Since: 1.0.0

xpubPublicKey :: XPub -> ByteString Source #

Extract the public key from an XPub as a raw ByteString (32 bytes).

Since: 2.0.0

xpubChainCode :: XPub -> ByteString Source #

Extract the chain code from an XPub as a raw ByteString (32 bytes).

Since: 2.0.0

Pub

data Pub Source #

An opaque type representing a non-extended public key.

Properties:

Roundtripping
forall pub. pubFromBytes (pubToBytes pub) == Just pub

Since: 3.12.0

Instances

Instances details
Eq Pub Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

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

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

Show Pub Source # 
Instance details

Defined in Cardano.Address.Derivation

Methods

showsPrec :: Int -> Pub -> ShowS #

show :: Pub -> String #

showList :: [Pub] -> ShowS #

pubFromBytes :: ByteString -> Maybe Pub Source #

Construct a Pub from raw ByteString (32 bytes).

Since: 3.12.0

pubToBytes :: Pub -> ByteString Source #

Convert an Pub to a raw ByteString (32 bytes).

Since: 3.12.0

xpubToPub :: XPub -> Pub Source #

Extract the public key from an XPub as a Pub (32 bytes).

Since: 3.12.0

XSignature

type XSignature = XSignature Source #

An opaque type representing a signature made from an XPrv.

Since: 1.0.0

sign :: ByteArrayAccess msg => XPrv -> msg -> XSignature Source #

Produce a signature of the given msg from an XPrv.

Since: 1.0.0

verify :: ByteArrayAccess msg => XPub -> msg -> XSignature -> Bool Source #

Verify the XSignature of a msg with the XPub associated with the XPrv used for signing.

Since: 1.0.0