Copyright | © 2018-2020 IOHK |
---|---|
License | Apache-2.0 |
Safe Haskell | None |
Language | Haskell2010 |
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
- data Depth
- newtype Index (derivationType :: DerivationType ) (level :: Depth ) = Index { }
- data Role
- roleVal :: forall (c :: Role ). Typeable c => Role
- utxoExternal :: Index ' Soft ' RoleK
- utxoInternal :: Index ' Soft ' RoleK
- mutableAccount :: Index ' Soft ' RoleK
- zeroAccount :: Index ' Soft ' AddressK
- stakeDerivationPath :: DerivationPrefix -> NonEmpty DerivationIndex
-
data
DerivationType
- = Hardened
- | Soft
- | WholeDomain
-
class
HardDerivation
(key ::
Depth
->
Type
->
Type
)
where
- type AddressIndexDerivationType key :: DerivationType
- deriveAccountPrivateKey :: Passphrase "encryption" -> key ' RootK XPrv -> Index ' Hardened ' AccountK -> key ' AccountK XPrv
- deriveAddressPrivateKey :: Passphrase "encryption" -> key ' AccountK XPrv -> Role -> Index ( AddressIndexDerivationType key) ' AddressK -> key ' AddressK XPrv
- class HardDerivation key => SoftDerivation (key :: Depth -> Type -> Type ) where
- newtype DerivationPrefix = DerivationPrefix ( Index ' Hardened ' PurposeK , Index ' Hardened ' CoinTypeK , Index ' Hardened ' AccountK )
- newtype DerivationIndex = DerivationIndex { }
- liftIndex :: LiftIndex derivation => Index derivation level -> Index ' WholeDomain level
- hashVerificationKey :: WalletKey key => KeyRole -> key depth XPub -> KeyHash
- newtype RewardAccount = RewardAccount { }
-
class
ToRewardAccount
k
where
- toRewardAccount :: k ' AddressK XPub -> RewardAccount
- someRewardAccount :: SomeMnemonic -> ( XPrv , RewardAccount , NonEmpty DerivationIndex )
- deriveRewardAccount :: ( HardDerivation k, Bounded ( Index ( AddressIndexDerivationType k) ' AddressK )) => Passphrase "encryption" -> k ' RootK XPrv -> k ' AddressK XPrv
- hex :: ByteArrayAccess bin => bin -> ByteString
- fromHex :: ByteArray bout => ByteString -> Either String bout
- data NetworkDiscriminant
- class NetworkDiscriminantVal (n :: NetworkDiscriminant )
- networkDiscriminantVal :: NetworkDiscriminantVal n => Text
-
class
MkKeyFingerprint
key
Address
=>
PaymentAddress
(network ::
NetworkDiscriminant
) key
where
- paymentAddress :: key ' AddressK XPub -> Address
- liftPaymentAddress :: KeyFingerprint "payment" key -> Address
-
class
PaymentAddress
network key =>
DelegationAddress
(network ::
NetworkDiscriminant
) key
where
- delegationAddress :: key ' AddressK XPub -> key ' AddressK XPub -> Address
- liftDelegationAddress :: KeyFingerprint "payment" key -> key ' AddressK XPub -> Address
-
class
BoundedAddressLength
key
where
- maxLengthAddressFor :: Proxy key -> Address
-
class
WalletKey
(key ::
Depth
->
Type
->
Type
)
where
- changePassphrase :: ( PassphraseScheme , Passphrase "user") -> ( PassphraseScheme , Passphrase "user") -> key depth XPrv -> key depth XPrv
- publicKey :: key depth XPrv -> key depth XPub
- digest :: HashAlgorithm a => key depth XPub -> Digest a
- keyTypeDescriptor :: Proxy key -> String
- getRawKey :: key depth raw -> raw
- liftRawKey :: raw -> key depth raw
-
class
PersistPrivateKey
(key ::
Type
->
Type
)
where
- serializeXPrv :: (key XPrv , PassphraseHash ) -> ( ByteString , ByteString )
- unsafeDeserializeXPrv :: ( ByteString , ByteString ) -> (key XPrv , PassphraseHash )
-
class
PersistPublicKey
(key ::
Type
->
Type
)
where
- serializeXPub :: key XPub -> ByteString
- unsafeDeserializeXPub :: ByteString -> key XPub
-
class
Show
from =>
MkKeyFingerprint
(key ::
Depth
->
Type
->
Type
) from
where
- paymentKeyFingerprint :: from -> Either ( ErrMkKeyFingerprint key from) ( KeyFingerprint "payment" key)
- data ErrMkKeyFingerprint key from = ErrInvalidAddress from ( Proxy key)
- newtype KeyFingerprint (s :: Symbol ) key = KeyFingerprint ByteString
HD Derivation
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
Instances
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
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)
stakeDerivationPath :: DerivationPrefix -> NonEmpty DerivationIndex Source #
Full path to the stake key. There's only one.
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
type AddressIndexDerivationType key :: DerivationType Source #
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
class HardDerivation key => SoftDerivation (key :: Depth -> Type -> Type ) where Source #
An interface for doing soft derivations from an account public key
deriveAddressPublicKey :: key ' AccountK XPub -> Role -> Index ' Soft ' AddressK -> key ' AddressK 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.
Instances
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
.
DerivationPrefix ( Index ' Hardened ' PurposeK , Index ' Hardened ' CoinTypeK , Index ' Hardened ' AccountK ) |
Instances
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:
-
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. - 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
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
class ToRewardAccount k where Source #
Derivation of a reward account, as a type-class because different between key types (in particular, Jörmungandr vs Shelley).
toRewardAccount :: k ' AddressK XPub -> RewardAccount Source #
someRewardAccount :: SomeMnemonic -> ( XPrv , RewardAccount , NonEmpty DerivationIndex ) Source #
Instances
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
hex :: ByteArrayAccess bin => bin -> ByteString Source #
Encode a
ByteString
in base16
fromHex :: ByteArray bout => ByteString -> Either String bout Source #
Decode a
ByteString
from base16
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
class NetworkDiscriminantVal (n :: NetworkDiscriminant ) Source #
Instances
NetworkDiscriminantVal ' Mainnet Source # | |
KnownNat pm => NetworkDiscriminantVal (' Testnet pm) Source # | |
KnownNat pm => NetworkDiscriminantVal (' Staging pm) Source # | |
Backends Interoperability
class MkKeyFingerprint key Address => PaymentAddress (network :: NetworkDiscriminant ) key where Source #
Encoding of addresses for certain key types and backend targets.
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.
:: KeyFingerprint "payment" key |
Payment fingerprint |
-> Address |
Lift a payment fingerprint back into a payment address.
Instances
class PaymentAddress network key => DelegationAddress (network :: NetworkDiscriminant ) key where Source #
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 #
:: KeyFingerprint "payment" key |
Payment fingerprint |
-> key ' AddressK XPub |
Staking key / Reward account |
-> Address |
Lift a payment fingerprint back into a delegation address.
Instances
DelegationAddress ' Mainnet ShelleyKey Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley delegationAddress :: ShelleyKey ' AddressK XPub -> ShelleyKey ' AddressK XPub -> Address Source # liftDelegationAddress :: KeyFingerprint "payment" ShelleyKey -> ShelleyKey ' AddressK XPub -> Address Source # |
|
DelegationAddress (' Testnet pm) ShelleyKey Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley delegationAddress :: ShelleyKey ' AddressK XPub -> ShelleyKey ' AddressK XPub -> Address Source # liftDelegationAddress :: KeyFingerprint "payment" ShelleyKey -> ShelleyKey ' AddressK XPub -> Address Source # |
|
DelegationAddress ' Mainnet k => DelegationAddress (' Staging pm) k Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation delegationAddress :: k ' AddressK XPub -> k ' AddressK XPub -> Address Source # liftDelegationAddress :: KeyFingerprint "payment" k -> k ' AddressK XPub -> Address Source # |
class BoundedAddressLength key where Source #
The class of keys for which addresses are bounded in length.
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 #
:: ( 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 #
liftRawKey :: raw -> key depth raw Source #
Instances
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.
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.
Instances
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.
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.
Instances
PersistPublicKey ( SharedKey depth) Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation.Shared serializeXPub :: SharedKey depth XPub -> ByteString Source # unsafeDeserializeXPub :: ByteString -> SharedKey depth XPub Source # |
|
PersistPublicKey ( ShelleyKey depth) Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation.Shelley serializeXPub :: ShelleyKey depth XPub -> ByteString Source # unsafeDeserializeXPub :: ByteString -> ShelleyKey depth XPub Source # |
|
PersistPublicKey ( IcarusKey depth) Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation.Icarus serializeXPub :: IcarusKey depth XPub -> ByteString Source # unsafeDeserializeXPub :: ByteString -> IcarusKey depth XPub Source # |
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:
-
For
ByronKey
, it can only be the address itself! -
For
ShelleyKey
, then the "payment" fingerprint refers to the payment key within a single or grouped address.
paymentKeyFingerprint :: from -> Either ( ErrMkKeyFingerprint key from) ( KeyFingerprint "payment" key) Source #
Instances
data ErrMkKeyFingerprint key from Source #
ErrInvalidAddress from ( Proxy key) |
Instances
Eq from => Eq ( ErrMkKeyFingerprint key from) Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation (==) :: ErrMkKeyFingerprint key from -> ErrMkKeyFingerprint key from -> Bool Source # (/=) :: ErrMkKeyFingerprint key from -> ErrMkKeyFingerprint key from -> Bool Source # |
|
Show from => Show ( ErrMkKeyFingerprint key from) Source # | |
Defined in Cardano.Wallet.Primitive.AddressDerivation |
newtype KeyFingerprint (s :: Symbol ) key Source #
Something that uniquely identifies a public key. Typically, a hash of that key or the key itself.