| Copyright | 2020 Input Output (Hong Kong) Ltd. 2021-2022 Input Output Global Inc. (IOG) 2023-2025 Intersect |
|---|---|
| License | Apache-2.0 |
| Safe Haskell | None |
| Language | Haskell2010 |
Cardano.Address.Derivation
Description
Synopsis
- data Index (derivationType :: DerivationType) (depth :: Depth)
- indexToWord32 :: Index derivationType depth -> Word32
- indexFromWord32 :: forall ix (derivationType :: DerivationType) (depth :: Depth). (ix ~ Index derivationType depth, Bounded ix) => Word32 -> Maybe ix
- wholeDomainIndex :: forall (depth :: Depth). Word32 -> Index 'WholeDomain depth
- coerceWholeDomainIndex :: forall (ty :: DerivationType) (depth0 :: Depth) (depth1 :: Depth). Index ty depth0 -> Index 'WholeDomain depth1
- nextIndex :: forall ix (derivationType :: DerivationType) (depth :: Depth). (ix ~ Index derivationType depth, Bounded ix) => ix -> Maybe ix
- data Depth
- data DerivationType
- = Hardened
- | Soft
- | WholeDomain
- class GenMasterKey (key :: Depth -> Type -> Type) where
- type SecondFactor (key :: Depth -> Type -> Type)
- genMasterKeyFromMnemonic :: SomeMnemonic -> SecondFactor key -> key 'RootK XPrv
- genMasterKeyFromXPrv :: XPrv -> key 'RootK XPrv
- class HardDerivation (key :: Depth -> Type -> Type) where
- type AccountIndexDerivationType (key :: Depth -> Type -> Type) :: DerivationType
- type AddressIndexDerivationType (key :: Depth -> Type -> Type) :: DerivationType
- type WithRole (key :: Depth -> Type -> Type)
- deriveAccountPrivateKey :: key 'RootK XPrv -> Index (AccountIndexDerivationType key) 'AccountK -> key 'AccountK XPrv
- deriveAddressPrivateKey :: key 'AccountK XPrv -> WithRole key -> Index (AddressIndexDerivationType key) 'PaymentK -> key 'PaymentK XPrv
- class HardDerivation key => SoftDerivation (key :: Depth -> Type -> Type) where
- type XPrv = XPrv
- xprvFromBytes :: ByteString -> Maybe XPrv
- xprvToBytes :: XPrv -> ByteString
- xprvPrivateKey :: XPrv -> ByteString
- xprvChainCode :: XPrv -> ByteString
- toXPub :: HasCallStack => XPrv -> XPub
- type XPub = XPub
- xpubFromBytes :: ByteString -> Maybe XPub
- xpubToBytes :: XPub -> ByteString
- xpubPublicKey :: XPub -> ByteString
- xpubChainCode :: XPub -> ByteString
- data Pub
- pubFromBytes :: ByteString -> Maybe Pub
- pubToBytes :: Pub -> ByteString
- xpubToPub :: XPub -> Pub
- type XSignature = XSignature
- sign :: ByteArrayAccess msg => XPrv -> msg -> XSignature
- verify :: ByteArrayAccess msg => XPub -> msg -> XSignature -> Bool
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
| Bounded (Index 'Hardened depth) Source # | |||||
| Bounded (Index 'Soft depth) Source # | |||||
| Bounded (Index 'WholeDomain depth) Source # | |||||
Defined in Cardano.Address.Derivation | |||||
| Generic (Index derivationType depth) Source # | |||||
Defined in Cardano.Address.Derivation Associated Types
| |||||
| Show (Index derivationType depth) Source # | |||||
| NFData (Index derivationType depth) Source # | |||||
Defined in Cardano.Address.Derivation | |||||
| Buildable (Index derivationType depth) Source # | |||||
Defined in Cardano.Address.Derivation | |||||
| Eq (Index derivationType depth) Source # | |||||
| Ord (Index derivationType depth) Source # | |||||
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 # | |||||
| type Rep (Index derivationType depth) Source # | |||||
Defined in Cardano.Address.Derivation | |||||
indexToWord32 :: Index derivationType depth -> Word32 Source #
Get the index as a Word32
@since 3.3.0
indexFromWord32 :: forall ix (derivationType :: DerivationType) (depth :: Depth). (ix ~ Index derivationType depth, Bounded ix) => Word32 -> Maybe ix Source #
Construct derivation path indices from raw Word32 values.
wholeDomainIndex :: forall (depth :: Depth). Word32 -> Index 'WholeDomain depth Source #
Constructs a full domain Index. This can't fail, unlike fromWord32.
Since: 3.3.0
coerceWholeDomainIndex :: forall (ty :: DerivationType) (depth0 :: Depth) (depth1 :: Depth). Index ty depth0 -> Index 'WholeDomain depth1 Source #
nextIndex :: forall ix (derivationType :: DerivationType) (depth :: Depth). (ix ~ Index derivationType depth, Bounded ix) => ix -> Maybe ix Source #
Increment an index, if possible.
Since: 3.3.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
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
Instances
| GenMasterKey Byron Source # | Key Derivation Example: Generating a root key from | ||||
Defined in Cardano.Address.Style.Byron Associated Types
Methods genMasterKeyFromMnemonic :: SomeMnemonic -> SecondFactor Byron -> Byron 'RootK XPrv Source # | |||||
| GenMasterKey Icarus Source # | |||||
Defined in Cardano.Address.Style.Icarus Associated Types
Methods genMasterKeyFromMnemonic :: SomeMnemonic -> SecondFactor Icarus -> Icarus 'RootK XPrv Source # | |||||
| GenMasterKey Shared Source # | |||||
Defined in Cardano.Address.Style.Shared Associated Types
Methods genMasterKeyFromMnemonic :: SomeMnemonic -> SecondFactor Shared -> Shared 'RootK XPrv Source # | |||||
| GenMasterKey Shelley Source # | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
Methods genMasterKeyFromMnemonic :: SomeMnemonic -> SecondFactor Shelley -> Shelley 'RootK XPrv Source # genMasterKeyFromXPrv :: XPrv -> Shelley 'RootK XPrv Source # | |||||
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
Associated Types
type AccountIndexDerivationType (key :: Depth -> Type -> Type) :: DerivationType Source #
type AddressIndexDerivationType (key :: Depth -> Type -> Type) :: DerivationType Source #
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
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
Instances
Low-Level Cryptography Primitives
XPrv
An opaque type representing an extended private key.
Properties:
Roundtripping
forall xprv.xprvFromBytes(xprvToBytesxprv) ==Justxprv
Chain Code Invariance
forall xprv.xprvChainCodexprv ==xpubChainCode(toXPubxprv)
Public Key Signature
forall xprv msg.verify(toXPubxprv) msg (signxprv 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
XPub
An opaque type representing an extended public key.
Properties:
Roundtripping
forall xpub.xpubFromBytes(xpubToBytesxpub) ==Justxpub
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
An opaque type representing a non-extended public key.
Properties:
Roundtripping
forall pub.pubFromBytes(pubToBytespub) ==Justpub
Since: 3.12.0
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
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