cardano-addresses-4.0.0: Utils for constructing a command-line on top of cardano-addresses.
Copyright2020 Input Output (Hong Kong) Ltd. 2021-2022 Input Output Global Inc. (IOG) 2023-2025 Intersect
LicenseApache-2.0
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Address.Style.Icarus

Description

 
Synopsis

Documentation

This module provides an implementation of:

  • GenMasterKey: for generating Icarus 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 addresses from a public key

We call Icarus addresses the new format of Cardano addresses which came after Byron. This is the format initially used in Yoroi and now also used by Daedalus.

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

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

Since: 1.0.0

Icarus

getKey :: Icarus depth key -> key Source #

Extract the raw XPrv or XPub wrapped by this type.

Since: 1.0.0

data Role Source #

Role the key assumes

Since: 1.0.0

Constructors

UTxOExternal 
UTxOInternal 

Instances

Instances details
Bounded Role Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Generic Role Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Show Role Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

NFData Role Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Methods

rnf :: Role -> () #

Eq Role Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Methods

(==) :: Role -> Role -> Bool #

(/=) :: Role -> Role -> Bool #

Ord Role Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

(>=) :: Role -> Role -> Bool #

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

type Rep Role Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

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

Key Derivation

Example:

Generating a root key from SomeMnemonic

>>> :set -XOverloadedStrings
>>> :set -XTypeApplications
>>> :set -XDataKinds
>>> :set -XFlexibleContexts
>>> import Cardano.Mnemonic ( mkSomeMnemonic )
>>> import Cardano.Address ( base58 )
>>> import Cardano.Address.Derivation ( toXPub )
>>> import qualified Cardano.Address.Style.Icarus as Icarus
>>>
>>> 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 = Icarus.genMasterKeyFromMnemonic mw sndFactor :: Icarus 'RootK XPrv

Deriving child keys

Let's consider the following 3rd, 4th and 5th derivation paths 0'/0/14 accIx assumes values from 2147483648 (ie. 0x80000000) to 4294967295 (ie. 0xFFFFFFFF) addIx assume values from 0 to 2147483647 (ie. 7FFFFFFF)

>>> let Just accIx = indexFromWord32 0x80000000
// this is the same as
>>> let accIx = minBound @(Index 'Hardened 'AccountK)
>>> let acctK = Icarus.deriveAccountPrivateKey rootK accIx
>>> let Just addIx = indexFromWord32 0x00000014
>>> let addrK = Icarus.deriveAddressPrivateKey acctK Icarus.UTxOExternal addIx
>>> base58 $ Icarus.paymentAddress Icarus.icarusMainnet (toXPub $ addrK)
>>>Ae2tdPwUPEZ8XpsjgQPH2cJdtohkYrxJ3i5y6mVsrkZZkdpdn6mnr4Rt6wG

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

Generate a root key from a corresponding root XPrv

Since: 1.0.0

genMasterKeyFromMnemonic Source #

Arguments

:: SomeMnemonic

Some valid mnemonic sentence.

-> ScrubbedBytes

An optional second-factor passphrase (or mempty)

-> Icarus 'RootK XPrv 

Generate a root key from a corresponding mnemonic.

Since: 1.0.0

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

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

Since: 1.0.0

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

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

Since: 1.0.0

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

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

Since: 1.0.0

Addresses

 

data AddressInfo Source #

The result of eitherInspectAddress for Icarus addresses.

Since: 3.4.0

Instances

Instances details
Generic AddressInfo Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Associated Types

type Rep AddressInfo :: Type -> Type #

Show AddressInfo Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Eq AddressInfo Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

ToJSON AddressInfo Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

type Rep AddressInfo Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

type Rep AddressInfo = D1 ('MetaData "AddressInfo" "Cardano.Address.Style.Icarus" "cardano-addresses-4.0.0-inplace" 'False) (C1 ('MetaCons "AddressInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "infoAddressRoot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "infoNetworkTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe NetworkTag))))

eitherInspectAddress :: Address -> Either ErrInspectAddress AddressInfo Source #

Determines whether an Address is an Icarus address.

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

Since: 3.4.0

inspectAddress :: MonadThrow m => Address -> m Value Source #

How to go from address root and the payment address

Example:

>>> :set -XOverloadedStrings
>>> :set -XTypeApplications
>>> :set -XDataKinds
>>> :set -XFlexibleContexts
>>> import Cardano.Mnemonic ( mkSomeMnemonic )
>>> import qualified Cardano.Address.Style.Icarus as Icarus
>>> import Cardano.Address.Derivation ( toXPub )
>>> import Cardano.Address ( base58 )
>>> let (Right mw) = mkSomeMnemonic '[12] ["moon","fox","ostrich","quick","cactus","raven","wasp","intact","first","ring","crumble","error"]
>>> let sndFactor = mempty
>>> let rootK = Icarus.genMasterKeyFromMnemonic mw sndFactor :: Icarus 'RootK XPrv
>>> let Just accIx = indexFromWord32 0x80000000
>>> let acctK = Icarus.deriveAccountPrivateKey rootK accIx
>>> let Just addIx = indexFromWord32 0x00000014
>>> let addrK = Icarus.deriveAddressPrivateKey acctK Icarus.UTxOExternal addIx
>>> (toXPub $ addrK)
Icarus {getKey = XPub {xpubPublicKey = "223148230206187135253SO151216183210]}s:151134174q173207184202EM176170220216235&1243", xpubChaincode = ChainCode "\160196&8~208165241138SOH222ETX*150&214185196 153DC2167165243155136228255229~d253"}}
>>> base58 $ Icarus.paymentAddress icarusMainnet (toXPub $ addrK)
Ae2tdPwUPEYyzBcNXkFWKywMiZ9eSd96dQxhBQd371foiH16Y7gFgLBj9G5

>>> import Cardano.Codec.Cbor
>>> import Crypto.Hash.Algorithms (Blake2b_224, SHA3_256)
>>> import Crypto.Hash (hash)
>>> let blake2b224 = hash _ Blake2b_224
>>> let sha3256 = hash _ @SHA3_256
>>> import qualified Codec.CBOR.Encoding as CBOR
>>> let encodeXPub = CBOR.encodeBytes (xpubToBytes . Icarus.getKey $ icarusAddrKPub)
>>> let encodeSpendingData = CBOR.encodeListLen 2 <> CBOR.encodeWord8 0 <> encodeXPub
>>> let encodeAttrs = CBOR.encodeMapLen 0
>>> import qualified Data.ByteArray as BA
>>> let rootAddr = BA.convert $ blake2b224 $ sha3256 $ CBOR.toStrictByteString $ mempty <> CBOR.encodeListLen 3 <> CBOR.encodeWord8 0 <> encodeSpendingData <> encodeAttrs
>>> encode EBase16 rootAddr
"1fdde02c9e087474aa7ab0a46ae2f6d316a92cd0fa2d4e8b1c2eebdf"

Usage from the command-line:

 echo Ae2tdPwUPEYyzBcNXkFWKywMiZ9eSd96dQxhBQd371foiH16Y7gFgLBj9G5 | cardano-address address inspect
{
   "stake_reference": "none",
   "address_style": Icarus,
   "address_root": "1fdde02c9e087474aa7ab0a46ae2f6d316a92cd0fa2d4e8b1c2eebdf",
   "network_tag": null,
   "address_type": 8
}

Determines whether an Address is an Icarus address.

Returns a JSON object with information about the address, or throws ErrInspectAddress if the address isn't an icarus address. @since 2.0.0

inspectIcarusAddress :: MonadThrow m => Address -> m Value Source #

Deprecated: use qualified inspectAddress instead.

Determines whether an Address is an Icarus address.

Returns a JSON object with information about the address, or throws ErrInspectAddress if the address isn't an icarus address.

Since: 2.0.0

paymentAddress :: NetworkDiscriminant Icarus -> Icarus '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 Shelley address

Since: 3.0.0

Instances

Instances details
Exception ErrInspectAddress Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Generic ErrInspectAddress Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Associated Types

type Rep ErrInspectAddress :: Type -> Type #

Show ErrInspectAddress Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

Eq ErrInspectAddress Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

ToJSON ErrInspectAddress Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

type Rep ErrInspectAddress Source # 
Instance details

Defined in Cardano.Address.Style.Icarus

type Rep ErrInspectAddress = D1 ('MetaData "ErrInspectAddress" "Cardano.Address.Style.Icarus" "cardano-addresses-4.0.0-inplace" 'False) (C1 ('MetaCons "UnexpectedDerivationPath" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeserialiseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeserialiseFailure)))

Network Discrimination

Unsafe

liftXPrv :: XPrv -> Icarus depth XPrv Source #

Unsafe backdoor for constructing an Icarus 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: 1.0.0

liftXPub :: XPub -> Icarus depth XPub Source #

Unsafe backdoor for constructing an Icarus 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