cardano-addresses-3.11.0: Library utilities for mnemonic generation and address derivation.
Copyright © 2018-2021 IOHK
License Apache-2.0
Safe Haskell None
Language Haskell2010

Cardano.Address.Style.Shelley

Description

Synopsis

Documentation

This module provides an implementation of:

  • GenMasterKey : for generating Shelley master keys from mnemonic sentences
  • HardDerivation : for hierarchical hard derivation of parent to child keys
  • SoftDerivation : for hierarchical soft derivation of parent to child keys
  • paymentAddress : for constructing payment addresses from a address public key or a script
  • delegationAddress : for constructing delegation addresses from payment credential (public key or script) and stake credential (public key or script)
  • pointerAddress : for constructing delegation addresses from payment credential (public key or script) and chain pointer
  • stakeAddress : for constructing reward accounts from stake credential (public key or script)

Shelley

data Shelley (depth :: Depth ) key Source #

A cryptographic key for sequential-scheme address derivation, with phantom-types to disambiguate key types.

let rootPrivateKey = Shelley 'RootK XPrv
let accountPubKey  = Shelley 'AccountK XPub
let addressPubKey  = Shelley 'PaymentK XPub

Since: 2.0.0

Instances

Instances details
GenMasterKey Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

SoftDerivation Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

HardDerivation Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

HasNetworkDiscriminant Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Functor ( Shelley depth) Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Methods

fmap :: (a -> b) -> Shelley depth a -> Shelley depth b Source #

(<$) :: a -> Shelley depth b -> Shelley depth a Source #

Eq key => Eq ( Shelley depth key) Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Methods

(==) :: Shelley depth key -> Shelley depth key -> Bool Source #

(/=) :: Shelley depth key -> Shelley depth key -> Bool Source #

Show key => Show ( Shelley depth key) Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Generic ( Shelley depth key) Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Associated Types

type Rep ( Shelley depth key) :: Type -> Type Source #

Methods

from :: Shelley depth key -> Rep ( Shelley depth key) x Source #

to :: Rep ( Shelley depth key) x -> Shelley depth key Source #

NFData key => NFData ( Shelley depth key) Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Methods

rnf :: Shelley depth key -> () Source #

type SecondFactor Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type AccountIndexDerivationType Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type AddressIndexDerivationType Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type WithRole Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type NetworkDiscriminant Shelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep ( Shelley depth key) Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep ( Shelley depth key) = D1 (' MetaData "Shelley" "Cardano.Address.Style.Shelley" "cardano-addresses-3.11.0-D40zGSHo3QMFNy9OpWafYI" ' True ) ( C1 (' MetaCons "Shelley" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "getKey") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 key)))

$sel:getKey:Shelley :: Shelley depth key -> key Source #

Extract the raw XPrv or XPub wrapped by this type.

Since: 1.0.0

data Role Source #

Describe what the keys within an account are used for.

  • UTxOExternal: used for public addresses sent to other parties for receiving money.
  • UTxOInternal: generated by wallet software to send change back to the wallet.
  • Stake: used for stake key(s) and delegation.

Since: 3.0.0

Instances

Instances details
Bounded Role Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Eq Role Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Ord Role Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Show Role Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Generic Role Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Associated Types

type Rep Role :: Type -> Type Source #

NFData Role Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep Role Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep Role = D1 (' MetaData "Role" "Cardano.Address.Style.Shelley" "cardano-addresses-3.11.0-D40zGSHo3QMFNy9OpWafYI" ' False ) ( C1 (' MetaCons "UTxOExternal" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: ( C1 (' MetaCons "UTxOInternal" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "Stake" ' PrefixI ' False ) ( U1 :: Type -> Type )))

data family Credential (purpose :: Depth ) Source #

Shelley offers several ways to identify ownership of entities on chain.

This data-family has two instances, depending on whether the key is used for payment or for delegation.

Since: 3.0.0

Key Derivation

Generating a root key from SomeMnemonic

:set -XOverloadedStrings
:set -XTypeApplications
:set -XDataKinds
import Cardano.Mnemonic ( mkSomeMnemonic )

let (Right mw) = mkSomeMnemonic @'[15] ["network","empty","cause","mean","expire","private","finger","accident","session","problem","absurd","banner","stage","void","what"]
let sndFactor = mempty -- Or alternatively, a second factor mnemonic transformed to bytes via someMnemonicToBytes
let rootK = genMasterKeyFromMnemonic mw sndFactor :: Shelley 'RootK XPrv

Deriving child keys

Let's consider the following 3rd, 4th and 5th derivation paths 0'/0/14

let Just accIx = indexFromWord32 0x80000000
let acctK = deriveAccountPrivateKey rootK accIx

let Just addIx = indexFromWord32 0x00000014
let addrK = deriveAddressPrivateKey acctK UTxOExternal addIx
let stakeK = deriveDelegationPrivateKey acctK

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

Generate a root key from a corresponding root XPrv

Since: 2.0.0

genMasterKeyFromMnemonic Source #

Arguments

:: SomeMnemonic

Some valid mnemonic sentence.

-> ScrubbedBytes

An optional second-factor passphrase (or mempty )

-> Shelley ' RootK XPrv

Generate a root key from a corresponding mnemonic.

Since: 2.0.0

deriveAccountPrivateKey :: Shelley ' RootK XPrv -> Index ' Hardened ' AccountK -> Shelley ' AccountK XPrv Source #

Derives an account private key from the given root private key.

Since: 2.0.0

deriveAddressPrivateKey :: Shelley ' AccountK XPrv -> Role -> Index ' Soft ' PaymentK -> Shelley ' PaymentK XPrv Source #

Derives an address private key from the given account private key.

Since: 2.0.0

deriveDelegationPrivateKey :: Shelley ' AccountK XPrv -> Shelley ' DelegationK XPrv Source #

Derive a delegation key for a corresponding AccountK . Note that wallet software are by convention only using one delegation key per account, and always the first account (with index 0').

Deriving delegation keys for something else than the initial account is not recommended and can lead to incompatibility with existing wallet softwares (Daedalus, Yoroi, Adalite...).

Since: 2.0.0

deriveAddressPublicKey :: Shelley ' AccountK XPub -> Role -> Index ' Soft ' PaymentK -> Shelley ' PaymentK XPub Source #

Derives an address public key from the given account public key.

Since: 2.0.0

derivePolicyPrivateKey :: Shelley ' RootK XPrv -> Index ' Hardened ' PolicyK -> Shelley ' PolicyK XPrv Source #

Derives a policy private key from the given root private key.

Since: 3.9.0

Addresses

Generating a PaymentAddress from public key credential

import Cardano.Address ( bech32 )
import Cardano.Address.Derivation ( toXPub )

let (Right tag) = mkNetworkDiscriminant 1
let paymentCredential = PaymentFromKey $ (toXPub <$> addrK)
bech32 $ paymentAddress tag paymentCredential
"addr1vxpfffuj3zkp5g7ct6h4va89caxx9ayq2gvkyfvww48sdncxsce5t"

Generating a PaymentAddress from script credential

import Cardano.Address.Script.Parser ( scriptFromString )
import Cardano.Address.Script ( toScriptHash )
import Codec.Binary.Encoding ( encode )
import Data.Text.Encoding ( decodeUtf8 )

let (Right tag) = mkNetworkDiscriminant 1
let verKey1 = "script_vkh18srsxr3khll7vl3w9mqfu55n6wzxxlxj7qzr2mhnyreluzt36ms"
let verKey2 = "script_vkh18srsxr3khll7vl3w9mqfu55n6wzxxlxj7qzr2mhnyrenxv223vj"
let scriptStr = "all [" ++ verKey1 ++ ", " ++ verKey2 ++ "]"
let (Right script) = scriptFromString scriptStr
let infoScriptHash@(ScriptHash bytes) = toScriptHash script
decodeUtf8 (encode EBase16 bytes)
"a015ae61075e25c3d9250bdcbc35c6557272127927ecf2a2d716e29f"
bech32 $ paymentAddress tag (PaymentFromScript infoScriptHash)
"addr1wxspttnpqa0zts7ey59ae0p4ce2hyusj0yn7eu4z6utw98c9uxm83"

Generating a DelegationAddress

let (Right tag) = mkNetworkDiscriminant 1
let paymentCredential = PaymentFromKey $ (toXPub <$> addrK)
let delegationCredential = DelegationFromKey $ (toXPub <$> stakeK)
bech32 $ delegationAddress tag paymentCredential delegationCredential
"addr1qxpfffuj3zkp5g7ct6h4va89caxx9ayq2gvkyfvww48sdn7nudck0fzve4346yytz3wpwv9yhlxt7jwuc7ytwx2vfkyqmkc5xa"

Generating a PointerAddress

import Cardano.Address ( ChainPointer (..) )

let (Right tag) = mkNetworkDiscriminant 1
let ptr = ChainPointer 123 1 2
let paymentCredential = PaymentFromKey $ (toXPub <$> addrK)
bech32 $ pointerAddress tag paymentCredential ptr
"addr1gxpfffuj3zkp5g7ct6h4va89caxx9ayq2gvkyfvww48sdnmmqypqfcp5um"

Generating a DelegationAddress from using the same script credential in both payment and delegation

bech32 $ delegationAddress tag (PaymentFromScript infoScriptHash) (DelegationFromScript infoScriptHash)
"addr1xxspttnpqa0zts7ey59ae0p4ce2hyusj0yn7eu4z6utw98aqzkhxzp67yhpajfgtmj7rt3j4wfepy7f8ane294cku20swucnrl"

data InspectAddress Source #

The result of eitherInspectAddress .

Since: 3.4.0

Instances

Instances details
Eq InspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Show InspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Generic InspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

ToJSON InspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep InspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

data AddressInfo Source #

An inspected Shelley address.

Since: 3.4.0

Instances

Instances details
Eq AddressInfo Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Show AddressInfo Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Generic AddressInfo Source #
Instance details

Defined in Cardano.Address.Style.Shelley

ToJSON AddressInfo Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep AddressInfo Source #
Instance details

Defined in Cardano.Address.Style.Shelley

eitherInspectAddress :: Maybe XPub -> Address -> Either ErrInspectAddress InspectAddress Source #

Determines whether an Address is a valid address for the Cardano Shelley era. Shelley format addresses, as well as old-style Byron and Icarus addresses can be parsed by this function.

Returns either details about the Address , or ErrInspectAddress if it's not a valid address.

Since: 3.4.0

inspectAddress :: ( Alternative m, MonadThrow m) => Maybe XPub -> Address -> m Value Source #

Analyze an Address to know whether it's a valid address for the Cardano Shelley era. Shelley format addresses, as well as old-style Byron and Icarus addresses can be parsed by this function.

Returns a JSON value containing details about the Address , or throws ErrInspectAddress if it's not a valid address.

Since: 3.0.0

paymentAddress :: NetworkDiscriminant Shelley -> Credential ' PaymentK -> Address Source #

Convert a payment credential (key or script) to a payment Address valid for the given network discrimination.

Since: 2.0.0

delegationAddress :: NetworkDiscriminant Shelley -> Credential ' PaymentK -> Credential ' DelegationK -> Address Source #

Convert a payment credential (key or script) and a delegation credential (key or script) 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.

Since: 2.0.0

pointerAddress :: NetworkDiscriminant Shelley -> Credential ' PaymentK -> ChainPointer -> Address Source #

Convert a payment credential (key or script) and pointer to delegation certificate in blockchain to a pointer Address valid for the given network discrimination.

Since: 3.0.0

stakeAddress :: NetworkDiscriminant Shelley -> Credential ' DelegationK -> Either ErrInvalidStakeAddress Address Source #

Convert a delegation credential (key or script) to a stake Address (aka reward account address) for the given network discrimination.

Since: 3.0.0

extendAddress :: Address -> Credential ' DelegationK -> Either ErrExtendAddress Address Source #

Extend an existing payment Address to make it a delegation address.

Since: 2.0.0

data ErrInspectAddressOnlyShelley Source #

Possible errors from inspecting a Shelley address

Since: 3.4.0

Constructors

PtrRetrieveError String

Human readable error of underlying operation

UnknownType Word8

Unknown value in address type field

Instances

Instances details
Eq ErrInspectAddressOnlyShelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Show ErrInspectAddressOnlyShelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Generic ErrInspectAddressOnlyShelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

ToJSON ErrInspectAddressOnlyShelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Exception ErrInspectAddressOnlyShelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep ErrInspectAddressOnlyShelley Source #
Instance details

Defined in Cardano.Address.Style.Shelley

data ErrInspectAddress Source #

Possible errors from inspecting a Shelley, Icarus, or Byron address.

Since: 3.4.0

Instances

Instances details
Eq ErrInspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Show ErrInspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Generic ErrInspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

ToJSON ErrInspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Exception ErrInspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

type Rep ErrInspectAddress Source #
Instance details

Defined in Cardano.Address.Style.Shelley

Network Discrimination

mkNetworkDiscriminant :: Integer -> Either MkNetworkDiscriminantError ( NetworkDiscriminant Shelley ) Source #

Construct NetworkDiscriminant for Cardano Shelley from a number. If the number is invalid, ie., not between 0 and 15, then MkNetworkDiscriminantError is thrown.

Since: 2.0.0

inspectNetworkDiscriminant :: Address -> Maybe ( NetworkDiscriminant Shelley ) Source #

Retrieve the network discriminant of a given Address . If the Address is malformed or, not a shelley address, returns Nothing.

Since: 2.0.0

shelleyMainnet :: NetworkDiscriminant Shelley Source #

NetworkDicriminant for Cardano MainNet & Shelley

Since: 2.0.0

shelleyTestnet :: NetworkDiscriminant Shelley Source #

NetworkDicriminant for Cardano Testnet & Shelley

Since: 2.0.0

Unsafe

liftXPrv :: XPrv -> Shelley depth XPrv Source #

Unsafe backdoor for constructing an Shelley key from a raw XPrv . this is unsafe because it lets the caller choose the actually derivation depth .

This can be useful however when serializing / deserializing such a type, or to speed up test code (and avoid having to do needless derivations from a master key down to an address key for instance).

Since: 2.0.0

liftXPub :: XPub -> Shelley depth XPub Source #

Unsafe backdoor for constructing an Shelley key from a raw XPub . this is unsafe because it lets the caller choose the actually derivation depth .

This can be useful however when serializing / deserializing such a type, or to speed up test code (and avoid having to do needless derivations from a master key down to an address key for instance).

Since: 2.0.0