| 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.Style.Byron
Description
Synopsis
- data Byron (depth :: Depth) key
- type family DerivationPath (depth :: Depth) where ...
- payloadPassphrase :: Byron depth key -> ScrubbedBytes
- derivationPath :: Byron depth key -> DerivationPath depth
- getKey :: Byron depth key -> key
- genMasterKeyFromXPrv :: XPrv -> Byron 'RootK XPrv
- genMasterKeyFromMnemonic :: SomeMnemonic -> Byron 'RootK XPrv
- deriveAccountPrivateKey :: Byron 'RootK XPrv -> Index 'WholeDomain 'AccountK -> Byron 'AccountK XPrv
- deriveAddressPrivateKey :: Byron 'AccountK XPrv -> Index 'WholeDomain 'PaymentK -> Byron 'PaymentK XPrv
- data AddressInfo = AddressInfo {
- infoAddressRoot :: !ByteString
- infoPayload :: !PayloadInfo
- infoNetworkTag :: !(Maybe NetworkTag)
- eitherInspectAddress :: Maybe XPub -> Address -> Either ErrInspectAddress AddressInfo
- inspectAddress :: MonadThrow m => Maybe XPub -> Address -> m Value
- inspectByronAddress :: MonadThrow m => Maybe XPub -> Address -> m Value
- paymentAddress :: NetworkDiscriminant Byron -> Byron 'PaymentK XPub -> Address
- data ErrInspectAddress
- prettyErrInspectAddress :: ErrInspectAddress -> String
- byronMainnet :: NetworkDiscriminant Byron
- byronStaging :: NetworkDiscriminant Byron
- byronTestnet :: NetworkDiscriminant Byron
- byronPreprod :: NetworkDiscriminant Byron
- byronPreview :: NetworkDiscriminant Byron
- liftXPrv :: forall (depth :: Depth). XPub -> DerivationPath depth -> XPrv -> Byron depth XPrv
- liftXPub :: forall (depth :: Depth). XPub -> DerivationPath depth -> XPub -> Byron depth XPub
Documentation
This module provides an implementation of:
GenMasterKey: for generating Byron master keys from mnemonic sentencesHardDerivation: for hierarchical derivation of parent to child keysPaymentAddress: for constructing addresses from a public key
We call Byron addresses the old address type used by Daedalus in the early
days of Cardano. Using this type of addresses and underlying key scheme is
now considered deprecated because of some security implications.
The internals of the Byron does not matter for the reader, but basically
contains what is necessary to perform key derivation and generate addresses
from a Byron type.
Byron uses WholeDomain (meaning Soft+Hardened) for account key and payment key derivation. It should use Hardened for account and Soft for payment as design, but due to the error made prior 2019 in cardano-sl implementation WholeDomain was adopted to handle all the keys. Nevertheless, it was recommended and enforced to use Hardened for account derivation and Soft for payment key derivation from 2019 onwards. To sum up both account index and payment index can assume values from 0 to 4294967295 (ie. 0xFFFFFFFF)
Deprecation Notice
Unless you have good reason to do so (like writing backward-compatible code
with an existing piece), any new implementation should use the
Icarus style for key and addresses.
Byron
data Byron (depth :: Depth) key Source #
Deprecated: see Icarus
Material for deriving HD random scheme keys, which can be used for making addresses.
Since: 1.0.0
Instances
| HasNetworkDiscriminant Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron Associated Types
| |||||||||||||
| PaymentAddress Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron Methods paymentAddress :: NetworkDiscriminant Byron -> Byron 'PaymentK XPub -> Address Source # | |||||||||||||
| 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 # | |||||||||||||
| HardDerivation Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron Associated Types
| |||||||||||||
| Functor (Byron depth) Source # | |||||||||||||
| Generic (Byron depth key) Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron Associated Types
| |||||||||||||
| (Show key, Show (DerivationPath depth)) => Show (Byron depth key) Source # | |||||||||||||
| (NFData key, NFData (DerivationPath depth)) => NFData (Byron depth key) Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron | |||||||||||||
| (Eq key, Eq (DerivationPath depth)) => Eq (Byron depth key) Source # | |||||||||||||
| type NetworkDiscriminant Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron | |||||||||||||
| type AccountIndexDerivationType Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron | |||||||||||||
| type AddressIndexDerivationType Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron | |||||||||||||
| type SecondFactor Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron | |||||||||||||
| type WithRole Byron Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron | |||||||||||||
| type Rep (Byron depth key) Source # | |||||||||||||
Defined in Cardano.Address.Style.Byron type Rep (Byron depth key) = D1 ('MetaData "Byron" "Cardano.Address.Style.Byron" "cardano-addresses-4.0.1-12OTt85pRZ623XqhieiIYs" 'False) (C1 ('MetaCons "Byron" 'PrefixI 'True) (S1 ('MetaSel ('Just "getKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 key) :*: (S1 ('MetaSel ('Just "derivationPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DerivationPath depth)) :*: S1 ('MetaSel ('Just "payloadPassphrase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScrubbedBytes)))) | |||||||||||||
type family DerivationPath (depth :: Depth) where ... Source #
Equations
| DerivationPath 'RootK = () | |
| DerivationPath 'AccountK = Index 'WholeDomain 'AccountK | |
| DerivationPath 'PaymentK = (Index 'WholeDomain 'AccountK, Index 'WholeDomain 'PaymentK) |
payloadPassphrase :: Byron depth key -> ScrubbedBytes Source #
Deprecated: see Icarus
Used for encryption of the derivation path payload within an address.
Since: 1.0.0
derivationPath :: Byron depth key -> DerivationPath depth Source #
Key Derivation
genMasterKeyFromMnemonic Source #
Arguments
| :: SomeMnemonic | Some valid mnemonic sentence. |
| -> Byron 'RootK XPrv |
deriveAccountPrivateKey :: Byron 'RootK XPrv -> Index 'WholeDomain 'AccountK -> Byron 'AccountK XPrv Source #
deriveAddressPrivateKey :: Byron 'AccountK XPrv -> Index 'WholeDomain 'PaymentK -> Byron 'PaymentK XPrv Source #
Deprecated: see Icarus
Derives an address private key from the given account private key.
Since: 1.0.0
Addresses
data AddressInfo Source #
The result of eitherInspectAddress for Byron addresses.
Since: 3.4.0
Constructors
| AddressInfo | |
Fields
| |
Instances
| ToJSON AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Byron Methods toJSON :: AddressInfo -> Value # toEncoding :: AddressInfo -> Encoding # toJSONList :: [AddressInfo] -> Value # toEncodingList :: [AddressInfo] -> Encoding # omitField :: AddressInfo -> Bool # | |||||
| Generic AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Byron Associated Types
| |||||
| Show AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Byron Methods showsPrec :: Int -> AddressInfo -> ShowS # show :: AddressInfo -> String # showList :: [AddressInfo] -> ShowS # | |||||
| Eq AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Byron | |||||
| type Rep AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Byron | |||||
eitherInspectAddress :: Maybe XPub -> Address -> Either ErrInspectAddress AddressInfo Source #
Determines whether an Address is a Byron address.
Returns either details about the Address, or ErrInspectAddress if it's
not a valid address.
Since: 3.4.0
inspectAddress :: MonadThrow m => Maybe XPub -> Address -> m Value Source #
Determines whether an Address is a Byron address.
Returns a JSON object with information about the address, or throws
ErrInspectAddress if the address isn't a byron address.
Since: 3.0.0
inspectByronAddress :: MonadThrow m => Maybe XPub -> Address -> m Value Source #
Deprecated: use qualified inspectAddress instead.
Determines whether an Address is a Byron address.
Returns a JSON object with information about the address, or throws
ErrInspectAddress if the address isn't a byron address.
Since: 2.0.0
paymentAddress :: NetworkDiscriminant Byron -> Byron 'PaymentK XPub -> Address Source #
Convert a public key to a payment Address valid for the given
network discrimination.
Since: 1.0.0
data ErrInspectAddress Source #
Possible errors from inspecting a Byron address
Since: 3.0.0
Instances
prettyErrInspectAddress :: ErrInspectAddress -> String Source #
Pretty-print an ErrInspectAddress
Since: 3.0.0
Network Discrimination
byronMainnet :: NetworkDiscriminant Byron Source #
NetworkDiscriminant for Cardano MainNet & Byron
Since: 2.0.0
byronStaging :: NetworkDiscriminant Byron Source #
NetworkDiscriminant for Cardano Staging & Byron
Since: 2.0.0
byronTestnet :: NetworkDiscriminant Byron Source #
NetworkDiscriminant for Cardano Testnet & Byron
Since: 2.0.0
byronPreprod :: NetworkDiscriminant Byron Source #
NetworkDiscriminant for Cardano Preprod & Byron
Since: 3.13.0
byronPreview :: NetworkDiscriminant Byron Source #
NetworkDiscriminant for Cardano Preview & Byron
Since: 3.13.0
Unsafe
Arguments
| :: forall (depth :: Depth). XPub | A root public key |
| -> DerivationPath depth | |
| -> XPrv | |
| -> Byron depth XPrv |
Deprecated: see Icarus
Backdoor for generating a new key from a raw XPrv.
Note that the depth is left open so that the caller gets to decide what type
of key this is. This is mostly for testing, in practice, seeds are used to
represent root keys, and one should genMasterKeyFromXPrv
The first argument is a type-family DerivationPath and its type depends on
the depth of the key.
examples:
>>>liftXPrv rootPrv () prv_ :: Byron RootK XPrv
>>>liftXPrv rootPrv minBound prv_ :: Byron AccountK XPrv
>>>liftXPrv rootPrv (minBound, minBound) prv_ :: Byron PaymentK XPrv
Since: 2.0.0
Arguments
| :: forall (depth :: Depth). XPub | A root public key |
| -> DerivationPath depth | |
| -> XPub | |
| -> Byron depth XPub |
Deprecated: see Icarus
Backdoor for generating a new key from a raw XPub.
Note that the depth is left open so that the caller gets to decide what type
of key this is. This is mostly for testing, in practice, seeds are used to
represent root keys, and one should genMasterKeyFromXPrv
see also liftXPrv
Since: 2.0.0