cardano-wallet-core-2022.7.1: The Wallet Backend for a Cardano node.
Copyright © 2018-2020 IOHK
License Apache-2.0
Safe Haskell None
Language Haskell2010

Cardano.Wallet.Primitive.AddressDerivation

Description

Primitives for performing address derivation for some given schemes. This is where most of the crypto happens in the wallet and, it is quite important to ensure that the implementations match with other Cardano wallets (like cardano-sl, Yoroi/Icarus, or cardano-cli)

The actual implementations are in the following modules:

Synopsis

HD Derivation

data Depth Source #

Typically used as a phantom type parameter, a witness to the type of the key being used.

For example, key 'RootK XPrv , represents the private key at the root of the HD hierarchy.

According to BIP-0044 / CIP-1852, we have the following keys in our HD hierarchy:

m | purpose' | cointype' | account' | role | address

Plus, we also have script keys (which are used in shared wallets) and policy keys (which are used in minting and burning).

newtype Index (derivationType :: DerivationType ) (level :: Depth ) Source #

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

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

Constructors

Index

Instances

Instances details
Enum ( Index derivation level) => ToJSON ( ApiT ( Index derivation level)) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

( Enum ( Index derivation level), Bounded ( Index derivation level)) => FromJSON ( ApiT ( Index derivation level)) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

Bounded ( Index ' Hardened level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Bounded ( Index ' Soft level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Bounded ( Index ' WholeDomain level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Enum ( Index ' Hardened level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Enum ( Index ' Soft level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Enum ( Index ' WholeDomain level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Eq ( Index derivationType level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Methods

(==) :: Index derivationType level -> Index derivationType level -> Bool Source #

(/=) :: Index derivationType level -> Index derivationType level -> Bool Source #

Ord ( Index derivationType level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Methods

compare :: Index derivationType level -> Index derivationType level -> Ordering Source #

(<) :: Index derivationType level -> Index derivationType level -> Bool Source #

(<=) :: Index derivationType level -> Index derivationType level -> Bool Source #

(>) :: Index derivationType level -> Index derivationType level -> Bool Source #

(>=) :: Index derivationType level -> Index derivationType level -> Bool Source #

max :: Index derivationType level -> Index derivationType level -> Index derivationType level Source #

min :: Index derivationType level -> Index derivationType level -> Index derivationType level Source #

Show ( Index derivationType level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Methods

showsPrec :: Int -> Index derivationType level -> ShowS Source #

show :: Index derivationType level -> String Source #

showList :: [ Index derivationType level] -> ShowS Source #

Generic ( Index derivationType level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Associated Types

type Rep ( Index derivationType level) :: Type -> Type Source #

Methods

from :: Index derivationType level -> Rep ( Index derivationType level) x Source #

to :: Rep ( Index derivationType level) x -> Index derivationType level Source #

NFData ( Index derivationType level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Methods

rnf :: Index derivationType level -> () Source #

Buildable ( Index derivationType level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Methods

build :: Index derivationType level -> Builder Source #

( Enum ( Index derivation level), Bounded ( Index derivation level)) => FromText ( Index derivation level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

type Rep ( Index derivationType level) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

type Rep ( Index derivationType level) = D1 (' MetaData "Index" "Cardano.Wallet.Primitive.AddressDerivation" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" ' True ) ( C1 (' MetaCons "Index" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "getIndex") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Word32 )))

data Role Source #

Marker for addresses type engaged. We want to handle four cases here. The first two are pertinent to UTxO accounting, next handles rewards from participation in staking the last one is used for getting verification keys used in scripts. (a) external chain is used for addresses that are part of the advertised targets of a given transaction (b) internal change is for addresses used to handle the change of a the transaction within a given wallet (c) the addresses for a reward account (d) used for keys used inside scripts

Instances

Instances details
Bounded Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Enum Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Eq Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Ord Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Show Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Generic Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Associated Types

type Rep Role :: Type -> Type Source #

NFData Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

PersistFieldSql Role Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

PersistField Role Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

ToText Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

FromText Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

SymbolToField "seqStateAddressRole" SeqStateAddress Role Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Schema

type Rep Role Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

type Rep Role = D1 (' MetaData "Role" "Cardano.Wallet.Primitive.AddressDerivation" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" ' False ) ( C1 (' MetaCons "UtxoExternal" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: ( C1 (' MetaCons "UtxoInternal" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "MutableAccount" ' PrefixI ' False ) ( U1 :: Type -> Type )))

roleVal :: forall (c :: Role ). Typeable c => Role Source #

Bring a Role type back to the term-level. This requires a type application and either a scoped type variable, or an explicit passing of a Role .

>>> roleVal @'UtxoExternal
UtxoExternal
>>> roleVal @chain
...

utxoExternal :: Index ' Soft ' RoleK Source #

smart-constructor for getting a derivation index that refers to external utxo.

utxoInternal :: Index ' Soft ' RoleK Source #

smart-constructor for getting a derivation index that refers to internal utxo.

mutableAccount :: Index ' Soft ' RoleK Source #

smart-constructor for getting a derivation index that refers to stake key level (a.k.a mutable account)

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 the both soft and hard domain. We therefore introduce a WholeDomain derivation type that is the exact union of Hardened and Soft .

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

An interface for doing hard derivations from the root private key

Methods

deriveAccountPrivateKey :: Passphrase "encryption" -> key ' RootK XPrv -> Index ' Hardened ' 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).

NOTE: The caller is expected to provide the corresponding passphrase (and to have checked that the passphrase is valid). Providing a wrong passphrase will not make the function fail but will instead, yield an incorrect new key that doesn't belong to the wallet.

deriveAddressPrivateKey :: Passphrase "encryption" -> key ' AccountK XPrv -> Role -> Index ( AddressIndexDerivationType key) ' AddressK -> key ' AddressK XPrv Source #

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

It is preferred to use deriveAddressPublicKey whenever possible to avoid having to manipulate passphrases and private keys.

NOTE: The caller is expected to provide the corresponding passphrase (and to have checked that the passphrase is valid). Providing a wrong passphrase will not make the function fail but will instead, yield an incorrect new key that doesn't belong to the wallet.

Instances

Instances details
HardDerivation SharedKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shared

HardDerivation ByronKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Byron

HardDerivation ShelleyKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

HardDerivation IcarusKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

newtype DerivationPrefix Source #

Each SeqState is like a bucket of addresses associated with an account . An account corresponds to a subset of an HD tree as defined in BIP-0039.

cardano-wallet implements two similar HD schemes on top of BIP-0039 that are:

  • BIP-0044 (for so-called Icarus wallets)
  • CIP-1815 (for so-called Shelley and Jormungandr wallets)

Both scheme works by considering 5 levels of derivation from an initial root key (see also Depth from Cardano.Wallet.Primitive.AddressDerivation). A SeqState keeps track of indexes from the two last levels of a derivation branch. The DerivationPrefix defines the first three indexes chosen for this particular SeqState .

Instances

Instances details
Eq DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Ord DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Show DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Generic DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

NFData DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

PersistFieldSql DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

PersistField DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

ToText DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

FromText DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

SymbolToField "seqStateDerivationPrefix" SeqState DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Schema

SymbolToField "sharedStateDerivationPrefix" SharedState DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Schema

type Rep DerivationPrefix Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

type Rep DerivationPrefix = D1 (' MetaData "DerivationPrefix" "Cardano.Wallet.Primitive.AddressDerivation" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" ' True ) ( C1 (' MetaCons "DerivationPrefix" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Index ' Hardened ' PurposeK , Index ' Hardened ' CoinTypeK , Index ' Hardened ' AccountK ))))

newtype DerivationIndex Source #

A thin wrapper around derivation indexes. This can be used to represent derivation path as homogeneous lists of DerivationIndex . This is slightly more convenient than having to carry heterogeneous lists of 'Index depth type' and works fine because:

  1. The depth matters not because what the depth captures is actually the position of the index in that list. It makes sense to carry at the type level when manipulating standalone indexes to avoid mistakes, but when treating them as a part of a list it is redundant.
  2. The derivationType is captured by representing indexes as plain Word32. The Soft / Hardened notation is for easing human-readability but in the end, a soft index is simply a value < 2^31, whereas a "hardened" index is simply a value >= 2^31. Therefore, instead of representing indexes as derivationType + relative index within 0 and 2^31, we can represent them as just an index between 0 and 2^32, which is what DerivationIndex does.

Instances

Instances details
Eq DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Ord DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Show DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Generic DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

NFData DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

ToText DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

FromText DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

ToJSON ( ApiT DerivationIndex ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

FromJSON ( ApiT DerivationIndex ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type Rep DerivationIndex Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

type Rep DerivationIndex = D1 (' MetaData "DerivationIndex" "Cardano.Wallet.Primitive.AddressDerivation" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" ' True ) ( C1 (' MetaCons "DerivationIndex" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "getDerivationIndex") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Word32 )))

liftIndex :: LiftIndex derivation => Index derivation level -> Index ' WholeDomain level Source #

Delegation

newtype RewardAccount Source #

A reward account is used in group-type addresses for delegation.

It is the public key of the account address.

Instances

Instances details
Eq RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

Ord RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

Read RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

Show RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

Generic RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

NFData RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

ToJSON RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

FromJSON RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

Buildable RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

ToHttpApiData RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

FromHttpApiData RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

PathPiece RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

PersistFieldSql RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

PersistField RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Types

ToText RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

FromText RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

SymbolToField "txWithdrawalAccount" TxWithdrawal RewardAccount Source #
Instance details

Defined in Cardano.Wallet.DB.Sqlite.Schema

IsOurs ( RndState n) RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDiscovery.Random

EncodeStakeAddress n => ToJSON ( ApiT RewardAccount , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

DecodeStakeAddress n => FromJSON ( ApiT RewardAccount , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

IsOurs ( RndAnyState n p) RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDiscovery.Random

IsOurs ( SeqState n ShelleyKey ) RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

IsOurs ( SeqState n IcarusKey ) RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

IsOurs ( SharedState n k) RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDiscovery.Shared

IsOurs ( SeqAnyState n k p) RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDiscovery.Sequential

type Rep RewardAccount Source #
Instance details

Defined in Cardano.Wallet.Primitive.Types.RewardAccount

type Rep RewardAccount = D1 (' MetaData "RewardAccount" "Cardano.Wallet.Primitive.Types.RewardAccount" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" ' True ) ( C1 (' MetaCons "RewardAccount" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "unRewardAccount") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ByteString )))

deriveRewardAccount :: ( HardDerivation k, Bounded ( Index ( AddressIndexDerivationType k) ' AddressK )) => Passphrase "encryption" -> k ' RootK XPrv -> k ' AddressK XPrv Source #

Derive a reward account from a root private key. It is agreed by standard that every HD wallet will use only a single reward account. This account is located into a special derivation path and uses the first index of that path.

Helpers

Network Discrimination

data NetworkDiscriminant Source #

Available network options.

  • Mainnet : is a shortcut for quickly pointing to mainnet. On Byron and Shelley, it assumes no discrimination. It has a known magic and known genesis parameters.
  • Testnet : can be used to identify any network that has a custom genesis and, that requires _explicit_ network discrimination in addresses. Genesis file needs to be passed explicitly when starting the application.
  • Staging : very much like testnet, but like mainnet, assumes to no address discrimination. Genesis file needs to be passed explicitly when starting the application.

Instances

Instances details
MkKeyFingerprint SharedKey ( Proxy n, SharedKey ' AddressK XPub ) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shared

MkKeyFingerprint ShelleyKey ( Proxy n, ShelleyKey ' AddressK XPub ) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

PaymentAddress n IcarusKey => MkKeyFingerprint IcarusKey ( Proxy n, IcarusKey ' AddressK XPub ) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

EncodeAddress n => ToJSON ( ApiT Address , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

EncodeStakeAddress n => ToJSON ( ApiT RewardAccount , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

EncodeStakeAddress n => ToJSON ( ApiCoinSelectionWithdrawal n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

EncodeStakeAddress n => ToJSON ( ApiWithdrawal n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

DecodeAddress n => FromJSON ( ApiT Address , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

DecodeStakeAddress n => FromJSON ( ApiT RewardAccount , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

DecodeStakeAddress n => FromJSON ( ApiCoinSelectionWithdrawal n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

DecodeStakeAddress n => FromJSON ( ApiWithdrawal n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

EncodeAddress n => ToHttpApiData ( ApiT Address , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

DecodeAddress n => FromHttpApiData ( ApiT Address , Proxy n) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiDecodedTransactionT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiBalanceTransactionPostDataT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiPutAddressesDataT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiWalletMigrationPlanPostDataT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type PostTransactionFeeOldDataT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type PostTransactionOldDataT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiConstructTransactionDataT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiConstructTransactionT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiTransactionT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiSelectCoinsDataT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiCoinSelectionT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiAddressIdT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiStakeKeysT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiAddressT (n :: NetworkDiscriminant ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

type ApiWalletMigrationPostDataT (n :: NetworkDiscriminant ) (s :: Symbol ) Source #
Instance details

Defined in Cardano.Wallet.Api.Types

Backends Interoperability

class MkKeyFingerprint key Address => PaymentAddress (network :: NetworkDiscriminant ) key where Source #

Encoding of addresses for certain key types and backend targets.

Methods

paymentAddress :: key ' AddressK XPub -> Address Source #

Convert a public key to a payment Address valid for the given network discrimination.

Note that paymentAddress is ambiguous and requires therefore a type application.

liftPaymentAddress Source #

Arguments

:: KeyFingerprint "payment" key

Payment fingerprint

-> Address

Lift a payment fingerprint back into a payment address.

Instances

Instances details
PaymentAddress ' Mainnet ByronKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Byron

PaymentAddress ' Mainnet ShelleyKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

PaymentAddress ' Mainnet IcarusKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

KnownNat pm => PaymentAddress (' Testnet pm) ByronKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Byron

PaymentAddress (' Testnet pm) ShelleyKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

KnownNat pm => PaymentAddress (' Testnet pm) IcarusKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

PaymentAddress ' Mainnet k => PaymentAddress (' Staging pm) k Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

class PaymentAddress network key => DelegationAddress (network :: NetworkDiscriminant ) key where Source #

Methods

delegationAddress Source #

Arguments

:: key ' AddressK XPub

Payment key

-> key ' AddressK XPub

Staking key / Reward account

-> Address

Convert a public key and a staking key to a delegation Address valid for the given network discrimination. Funds sent to this address will be delegated according to the delegation settings attached to the delegation key.

Note that delegationAddress is ambiguous and requires therefore a type application.

liftDelegationAddress Source #

Arguments

:: KeyFingerprint "payment" key

Payment fingerprint

-> key ' AddressK XPub

Staking key / Reward account

-> Address

Lift a payment fingerprint back into a delegation address.

class BoundedAddressLength key where Source #

The class of keys for which addresses are bounded in length.

Methods

maxLengthAddressFor :: Proxy key -> Address Source #

Returns the longest address that the wallet can generate for a given key.

This is useful in situations where we want to compute some function of an output under construction (such as a minimum UTxO value), but don't yet have convenient access to a real address.

Please note that this address should:

  • never be used for anything besides its length and validity properties.
  • never be used as a payment target within a real transaction.

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

Methods

changePassphrase Source #

Arguments

:: ( PassphraseScheme , Passphrase "user")

Old passphrase

-> ( PassphraseScheme , Passphrase "user")

New passphrase

-> key depth XPrv
-> key depth XPrv

Re-encrypt a private key using a different passphrase.

  • *Important**: This function doesn't check that the old passphrase is correct! Caller is expected to have already checked that. Using an incorrect passphrase here will lead to very bad thing.

publicKey :: key depth XPrv -> key depth XPub Source #

Extract the public key part of a private key.

digest :: HashAlgorithm a => key depth XPub -> Digest a Source #

Hash a public key to some other representation.

keyTypeDescriptor :: Proxy key -> String Source #

Get a short, human-readable string descriptor that uniquely identifies the specified key type.

getRawKey :: key depth raw -> raw Source #

Unwrap the WalletKey to use the XPrv or XPub .

liftRawKey :: raw -> key depth raw Source #

Instances

Instances details
WalletKey SharedKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shared

WalletKey ByronKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Byron

WalletKey ShelleyKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

WalletKey IcarusKey Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

class PersistPrivateKey (key :: Type -> Type ) where Source #

Operations for saving a private key into a database, and restoring it from a database. The keys should be encoded in hexadecimal strings.

Methods

serializeXPrv :: (key XPrv , PassphraseHash ) -> ( ByteString , ByteString ) Source #

Convert a private key and its password hash into hexadecimal strings suitable for storing in a text file or database column.

unsafeDeserializeXPrv :: ( ByteString , ByteString ) -> (key XPrv , PassphraseHash ) Source #

The reverse of serializeXPrv . This may fail if the inputs are not valid hexadecimal strings, or if the key is of the wrong length.

class PersistPublicKey (key :: Type -> Type ) where Source #

Operations for saving a public key into a database, and restoring it from a database. The keys should be encoded in hexadecimal strings.

Methods

serializeXPub :: key XPub -> ByteString Source #

Convert a private key and its password hash into hexadecimal strings suitable for storing in a text file or database column.

unsafeDeserializeXPub :: ByteString -> key XPub Source #

Convert a public key into hexadecimal strings suitable for storing in a text file or database column.

class Show from => MkKeyFingerprint (key :: Depth -> Type -> Type ) from where Source #

Produce KeyFingerprint for existing types. A fingerprint here uniquely identifies part of an address. It can refer to either the payment key or, if any, the delegation key of an address.

The fingerprint obeys the following rules:

  • If two addresses are the same, then they have the same fingerprints
  • It is possible to lift the fingerprint back into an address

This second rule pretty much fixes what can be chosen as a fingerprint for various key types:

  1. For ByronKey , it can only be the address itself!
  2. For ShelleyKey , then the "payment" fingerprint refers to the payment key within a single or grouped address.

Instances

Instances details
MkKeyFingerprint SharedKey Address Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shared

MkKeyFingerprint ByronKey Address Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Byron

MkKeyFingerprint ShelleyKey Address Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

MkKeyFingerprint IcarusKey Address Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

MkKeyFingerprint SharedKey ( Proxy n, SharedKey ' AddressK XPub ) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shared

MkKeyFingerprint ShelleyKey ( Proxy n, ShelleyKey ' AddressK XPub ) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley

PaymentAddress n IcarusKey => MkKeyFingerprint IcarusKey ( Proxy n, IcarusKey ' AddressK XPub ) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus

newtype KeyFingerprint (s :: Symbol ) key Source #

Something that uniquely identifies a public key. Typically, a hash of that key or the key itself.

Instances

Instances details
Eq ( KeyFingerprint s key) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Ord ( KeyFingerprint s key) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Show ( KeyFingerprint s key) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Generic ( KeyFingerprint s key) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

Associated Types

type Rep ( KeyFingerprint s key) :: Type -> Type Source #

NFData ( KeyFingerprint s key) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

type Rep ( KeyFingerprint s key) Source #
Instance details

Defined in Cardano.Wallet.Primitive.AddressDerivation

type Rep ( KeyFingerprint s key) = D1 (' MetaData "KeyFingerprint" "Cardano.Wallet.Primitive.AddressDerivation" "cardano-wallet-core-2022.7.1-AGKhlyz9liLKN3QqZD1gj" ' True ) ( C1 (' MetaCons "KeyFingerprint" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ByteString )))