| 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.Shelley
Description
Synopsis
- data Shelley (depth :: Depth) key
- data Role
- = UTxOExternal
- | UTxOInternal
- | Stake
- | DRep
- | CCCold
- | CCHot
- data family Credential (purpose :: Depth)
- genMasterKeyFromXPrv :: XPrv -> Shelley 'RootK XPrv
- genMasterKeyFromMnemonic :: SomeMnemonic -> ScrubbedBytes -> Shelley 'RootK XPrv
- deriveAccountPrivateKey :: Shelley 'RootK XPrv -> Index 'Hardened 'AccountK -> Shelley 'AccountK XPrv
- deriveAddressPrivateKey :: Shelley 'AccountK XPrv -> Role -> Index 'Soft 'PaymentK -> Shelley 'PaymentK XPrv
- deriveDelegationPrivateKey :: Shelley 'AccountK XPrv -> Shelley 'DelegationK XPrv
- deriveDRepPrivateKey :: Shelley 'AccountK XPrv -> Shelley 'DRepK XPrv
- deriveCCColdPrivateKey :: Shelley 'AccountK XPrv -> Shelley 'CCColdK XPrv
- deriveCCHotPrivateKey :: Shelley 'AccountK XPrv -> Shelley 'CCHotK XPrv
- deriveAddressPublicKey :: Shelley 'AccountK XPub -> Role -> Index 'Soft 'PaymentK -> Shelley 'PaymentK XPub
- derivePolicyPrivateKey :: Shelley 'RootK XPrv -> Index 'Hardened 'PolicyK -> Shelley 'PolicyK XPrv
- data InspectAddress
- data AddressInfo = AddressInfo {}
- data ReferenceInfo
- eitherInspectAddress :: Maybe XPub -> Address -> Either ErrInspectAddress InspectAddress
- inspectAddress :: MonadThrow m => Maybe XPub -> Address -> m Value
- inspectShelleyAddress :: MonadThrow m => Maybe XPub -> Address -> m Value
- paymentAddress :: NetworkDiscriminant Shelley -> Credential 'PaymentK -> Address
- delegationAddress :: NetworkDiscriminant Shelley -> Credential 'PaymentK -> Credential 'DelegationK -> Address
- pointerAddress :: NetworkDiscriminant Shelley -> Credential 'PaymentK -> ChainPointer -> Address
- stakeAddress :: NetworkDiscriminant Shelley -> Credential 'DelegationK -> Either ErrInvalidStakeAddress Address
- extendAddress :: Address -> Credential 'DelegationK -> Either ErrExtendAddress Address
- data ErrExtendAddress
- data ErrInspectAddressOnlyShelley
- data ErrInspectAddress
- prettyErrInspectAddressOnlyShelley :: ErrInspectAddressOnlyShelley -> String
- prettyErrInspectAddress :: ErrInspectAddress -> String
- newtype MkNetworkDiscriminantError = ErrWrongNetworkTag Integer
- mkNetworkDiscriminant :: Integer -> Either MkNetworkDiscriminantError (NetworkDiscriminant Shelley)
- inspectNetworkDiscriminant :: Address -> Maybe (NetworkDiscriminant Shelley)
- shelleyMainnet :: NetworkDiscriminant Shelley
- shelleyTestnet :: NetworkDiscriminant Shelley
- liftXPrv :: forall (depth :: Depth). XPrv -> Shelley depth XPrv
- liftXPub :: forall (depth :: Depth). XPub -> Shelley depth XPub
- liftPub :: forall (depth :: Depth). Pub -> Shelley depth Pub
Documentation
This module provides an implementation of:
GenMasterKey: for generating Shelley master keys from mnemonic sentencesHardDerivation: for hierarchical hard derivation of parent to child keysSoftDerivation: for hierarchical soft derivation of parent to child keyspaymentAddress: for constructing payment addresses from a address public key or a scriptdelegationAddress: 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 pointerstakeAddress: 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
Describe what the keys within an account are used for.
Since: 3.0.0
Constructors
| 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. |
| DRep | Used for DRep key derivation. |
| CCCold | Used for constitutional committee cold key derivation |
| CCHot | Used for constitutional committee hot key derivation |
Instances
| Bounded Role Source # | |||||
| Generic Role Source # | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
| Show Role Source # | |||||
| NFData Role Source # | |||||
Defined in Cardano.Address.Style.Shelley | |||||
| Eq Role Source # | |||||
| Ord Role Source # | |||||
| type Rep Role Source # | |||||
Defined in Cardano.Address.Style.Shelley type Rep Role = D1 ('MetaData "Role" "Cardano.Address.Style.Shelley" "cardano-addresses-4.0.1-12OTt85pRZ623XqhieiIYs" '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))) :+: (C1 ('MetaCons "DRep" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CCCold" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CCHot" '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
Instances
| Show (Credential 'DelegationK) Source # | |
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> Credential 'DelegationK -> ShowS # show :: Credential 'DelegationK -> String # showList :: [Credential 'DelegationK] -> ShowS # | |
| Show (Credential 'PaymentK) Source # | |
Defined in Cardano.Address.Style.Shelley | |
| data Credential 'DelegationK Source # | |
Defined in Cardano.Address.Style.Shelley data Credential 'DelegationK where
| |
| data Credential 'PaymentK Source # | |
Defined in Cardano.Address.Style.Shelley data Credential 'PaymentK where
| |
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 |
| -> 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
deriveDRepPrivateKey :: Shelley 'AccountK XPrv -> Shelley 'DRepK XPrv Source #
Derive a DRep 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 DRep keys for something else than the initial account is not recommended and can lead to incompatibility with existing wallet softwares (Daedalus, Yoroi, Adalite...).
deriveCCColdPrivateKey :: Shelley 'AccountK XPrv -> Shelley 'CCColdK XPrv Source #
Derive a CCCold 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 CCCold keys for something else than the initial account is not recommended and can lead to incompatibility with existing wallet softwares (Daedalus, Yoroi, Adalite...).
deriveCCHotPrivateKey :: Shelley 'AccountK XPrv -> Shelley 'CCHotK XPrv Source #
Derive a CCHot 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 CCHot keys for something else than the initial account is not recommended and can lead to incompatibility with existing wallet softwares (Daedalus, Yoroi, Adalite...).
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 = PaymentFromExtendedKey $ (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 infoSpendingScriptHash@(ScriptHash bytes) = toScriptHash script >>> decodeUtf8 (encode EBase16 bytes) "a015ae61075e25c3d9250bdcbc35c6557272127927ecf2a2d716e29f" >>> bech32 $ paymentAddress tag (PaymentFromScriptHash infoSpendingScriptHash) "addr1wxspttnpqa0zts7ey59ae0p4ce2hyusj0yn7eu4z6utw98c9uxm83"
Generating a DelegationAddress
>>> let (Right tag) = mkNetworkDiscriminant 1 >>> let paymentCredential = PaymentFromExtendedKey $ (toXPub $ addrK) >>> let delegationCredential = DelegationFromExtendedKey $ (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 = PaymentFromExtendedKey $ (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 (PaymentFromScriptHash infoSpendingScriptHash) (DelegationFromScript infoSpendingScriptHash) "addr1xxspttnpqa0zts7ey59ae0p4ce2hyusj0yn7eu4z6utw98aqzkhxzp67yhpajfgtmj7rt3j4wfepy7f8ane294cku20swucnrl"
data InspectAddress Source #
The result of eitherInspectAddress.
Since: 3.4.0
Constructors
| InspectAddressShelley AddressInfo | |
| InspectAddressIcarus AddressInfo | |
| InspectAddressByron AddressInfo |
Instances
| ToJSON InspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods toJSON :: InspectAddress -> Value # toEncoding :: InspectAddress -> Encoding # toJSONList :: [InspectAddress] -> Value # toEncodingList :: [InspectAddress] -> Encoding # omitField :: InspectAddress -> Bool # | |||||
| Generic InspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
Methods from :: InspectAddress -> Rep InspectAddress x # to :: Rep InspectAddress x -> InspectAddress # | |||||
| Show InspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> InspectAddress -> ShowS # show :: InspectAddress -> String # showList :: [InspectAddress] -> ShowS # | |||||
| Eq InspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods (==) :: InspectAddress -> InspectAddress -> Bool # (/=) :: InspectAddress -> InspectAddress -> Bool # | |||||
| type Rep InspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley type Rep InspectAddress = D1 ('MetaData "InspectAddress" "Cardano.Address.Style.Shelley" "cardano-addresses-4.0.1-12OTt85pRZ623XqhieiIYs" 'False) (C1 ('MetaCons "InspectAddressShelley" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AddressInfo)) :+: (C1 ('MetaCons "InspectAddressIcarus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AddressInfo)) :+: C1 ('MetaCons "InspectAddressByron" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AddressInfo)))) | |||||
data AddressInfo Source #
An inspected Shelley address.
Since: 3.4.0
Constructors
| AddressInfo | |
Fields
| |
Instances
| ToJSON AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods toJSON :: AddressInfo -> Value # toEncoding :: AddressInfo -> Encoding # toJSONList :: [AddressInfo] -> Value # toEncodingList :: [AddressInfo] -> Encoding # omitField :: AddressInfo -> Bool # | |||||
| Generic AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
| Show AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> AddressInfo -> ShowS # show :: AddressInfo -> String # showList :: [AddressInfo] -> ShowS # | |||||
| Eq AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley | |||||
| type Rep AddressInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley type Rep AddressInfo = D1 ('MetaData "AddressInfo" "Cardano.Address.Style.Shelley" "cardano-addresses-4.0.1-12OTt85pRZ623XqhieiIYs" 'False) (C1 ('MetaCons "AddressInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "infoStakeReference") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ReferenceInfo)) :*: (S1 ('MetaSel ('Just "infoSpendingKeyHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)) :*: S1 ('MetaSel ('Just "infoStakeKeyHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)))) :*: ((S1 ('MetaSel ('Just "infoSpendingScriptHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString)) :*: S1 ('MetaSel ('Just "infoStakeScriptHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe ByteString))) :*: (S1 ('MetaSel ('Just "infoNetworkTag") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetworkTag) :*: S1 ('MetaSel ('Just "infoAddressType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8))))) | |||||
data ReferenceInfo Source #
Info from Address about how delegation keys are located.
Since: 3.6.1
Constructors
| ByValue | |
| ByPointer ChainPointer |
Instances
| Generic ReferenceInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
| Show ReferenceInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> ReferenceInfo -> ShowS # show :: ReferenceInfo -> String # showList :: [ReferenceInfo] -> ShowS # | |||||
| Eq ReferenceInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods (==) :: ReferenceInfo -> ReferenceInfo -> Bool # (/=) :: ReferenceInfo -> ReferenceInfo -> Bool # | |||||
| type Rep ReferenceInfo Source # | |||||
Defined in Cardano.Address.Style.Shelley type Rep ReferenceInfo = D1 ('MetaData "ReferenceInfo" "Cardano.Address.Style.Shelley" "cardano-addresses-4.0.1-12OTt85pRZ623XqhieiIYs" 'False) (C1 ('MetaCons "ByValue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ByPointer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainPointer))) | |||||
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 :: 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
inspectShelleyAddress :: MonadThrow m => Maybe XPub -> Address -> m Value Source #
Deprecated: use qualified inspectAddress instead.
Determines whether an Address a Shelley address.
Throws AddrError if it's not a valid Shelley address, or a ready-to-print
string giving details about the Address.
Since: 2.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 ErrExtendAddress Source #
Captures error occuring when trying to extend an invalid address.
Since: 2.0.0
Instances
| Show ErrExtendAddress Source # | |
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> ErrExtendAddress -> ShowS # show :: ErrExtendAddress -> String # showList :: [ErrExtendAddress] -> ShowS # | |
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
| ToJSON ErrInspectAddressOnlyShelley Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods toJSON :: ErrInspectAddressOnlyShelley -> Value # toEncoding :: ErrInspectAddressOnlyShelley -> Encoding # toJSONList :: [ErrInspectAddressOnlyShelley] -> Value # toEncodingList :: [ErrInspectAddressOnlyShelley] -> Encoding # | |||||
| Exception ErrInspectAddressOnlyShelley Source # | |||||
| Generic ErrInspectAddressOnlyShelley Source # | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
| |||||
| Show ErrInspectAddressOnlyShelley Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> ErrInspectAddressOnlyShelley -> ShowS # show :: ErrInspectAddressOnlyShelley -> String # showList :: [ErrInspectAddressOnlyShelley] -> ShowS # | |||||
| Eq ErrInspectAddressOnlyShelley Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods (==) :: ErrInspectAddressOnlyShelley -> ErrInspectAddressOnlyShelley -> Bool # (/=) :: ErrInspectAddressOnlyShelley -> ErrInspectAddressOnlyShelley -> Bool # | |||||
| type Rep ErrInspectAddressOnlyShelley Source # | |||||
Defined in Cardano.Address.Style.Shelley type Rep ErrInspectAddressOnlyShelley = D1 ('MetaData "ErrInspectAddressOnlyShelley" "Cardano.Address.Style.Shelley" "cardano-addresses-4.0.1-12OTt85pRZ623XqhieiIYs" 'False) (C1 ('MetaCons "PtrRetrieveError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "UnknownType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))) | |||||
data ErrInspectAddress Source #
Possible errors from inspecting a Shelley, Icarus, or Byron address.
Since: 3.4.0
Constructors
| WrongInputSize Int | Unexpected size |
| ErrShelley ErrInspectAddressOnlyShelley | |
| ErrIcarus ErrInspectAddress | |
| ErrByron ErrInspectAddress |
Instances
| ToJSON ErrInspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods toJSON :: ErrInspectAddress -> Value # toEncoding :: ErrInspectAddress -> Encoding # toJSONList :: [ErrInspectAddress] -> Value # toEncodingList :: [ErrInspectAddress] -> Encoding # omitField :: ErrInspectAddress -> Bool # | |||||
| Exception ErrInspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods toException :: ErrInspectAddress -> SomeException # | |||||
| Generic ErrInspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Associated Types
Methods from :: ErrInspectAddress -> Rep ErrInspectAddress x # to :: Rep ErrInspectAddress x -> ErrInspectAddress # | |||||
| Show ErrInspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> ErrInspectAddress -> ShowS # show :: ErrInspectAddress -> String # showList :: [ErrInspectAddress] -> ShowS # | |||||
| Eq ErrInspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley Methods (==) :: ErrInspectAddress -> ErrInspectAddress -> Bool # (/=) :: ErrInspectAddress -> ErrInspectAddress -> Bool # | |||||
| type Rep ErrInspectAddress Source # | |||||
Defined in Cardano.Address.Style.Shelley type Rep ErrInspectAddress = D1 ('MetaData "ErrInspectAddress" "Cardano.Address.Style.Shelley" "cardano-addresses-4.0.1-12OTt85pRZ623XqhieiIYs" 'False) ((C1 ('MetaCons "WrongInputSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "ErrShelley" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ErrInspectAddressOnlyShelley))) :+: (C1 ('MetaCons "ErrIcarus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ErrInspectAddress)) :+: C1 ('MetaCons "ErrByron" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ErrInspectAddress)))) | |||||
prettyErrInspectAddressOnlyShelley :: ErrInspectAddressOnlyShelley -> String Source #
Pretty-print an ErrInspectAddressOnlyShelley
Since: 3.4.0
prettyErrInspectAddress :: ErrInspectAddress -> String Source #
Pretty-print an ErrInspectAddress
Since: 3.0.0
Network Discrimination
newtype MkNetworkDiscriminantError Source #
Error reported from trying to create a network discriminant from number
Since: 2.0.0
Constructors
| ErrWrongNetworkTag Integer | Wrong network tag. |
Instances
| Show MkNetworkDiscriminantError Source # | |
Defined in Cardano.Address.Style.Shelley Methods showsPrec :: Int -> MkNetworkDiscriminantError -> ShowS # show :: MkNetworkDiscriminantError -> String # showList :: [MkNetworkDiscriminantError] -> ShowS # | |
| Buildable MkNetworkDiscriminantError Source # | |
Defined in Cardano.Address.Style.Shelley Methods | |
| Eq MkNetworkDiscriminantError Source # | |
Defined in Cardano.Address.Style.Shelley Methods (==) :: MkNetworkDiscriminantError -> MkNetworkDiscriminantError -> Bool # (/=) :: MkNetworkDiscriminantError -> MkNetworkDiscriminantError -> Bool # | |
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
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 :: forall (depth :: Depth). 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 :: forall (depth :: Depth). 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
liftPub :: forall (depth :: Depth). Pub -> Shelley depth Pub Source #
Unsafe backdoor for constructing an Shelley key from a raw Pub. 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: 3.0.0