Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a library interface that is intended to be the complete API for Shelley covering everything, including exposing constructors for the lower level types.
Synopsis
- module Cardano.Api
-
data
ShelleyGenesis
era =
ShelleyGenesis
{
- sgSystemStart :: ! UTCTime
- sgNetworkMagic :: ! Word32
- sgNetworkId :: ! Network
- sgActiveSlotsCoeff :: ! PositiveUnitInterval
- sgSecurityParam :: ! Word64
- sgEpochLength :: ! EpochSize
- sgSlotsPerKESPeriod :: ! Word64
- sgMaxKESEvolutions :: ! Word64
- sgSlotLength :: ! NominalDiffTime
- sgUpdateQuorum :: ! Word64
- sgMaxLovelaceSupply :: ! Word64
- sgProtocolParams :: !( PParams era)
- sgGenDelegs :: !( Map ( KeyHash ' Genesis ( Crypto era)) ( GenDelegPair ( Crypto era)))
- sgInitialFunds :: !( Map ( Addr ( Crypto era)) Coin )
- sgStaking :: !( ShelleyGenesisStaking ( Crypto era))
- shelleyGenesisDefaults :: ShelleyGenesis crypto
-
class
(
Eq
(
VerificationKey
keyrole),
Show
(
VerificationKey
keyrole),
SerialiseAsRawBytes
(
Hash
keyrole),
HasTextEnvelope
(
VerificationKey
keyrole),
HasTextEnvelope
(
SigningKey
keyrole)) =>
Key
keyrole
where
- data VerificationKey keyrole :: Type
- data SigningKey keyrole :: Type
- getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole
- deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole
- deterministicSigningKeySeedSize :: AsType keyrole -> Word
- verificationKeyHash :: VerificationKey keyrole -> Hash keyrole
- data family Hash keyrole :: Type
- data Address addrtype where
- toShelleyAddr :: AddressInEra era -> Addr StandardCrypto
- fromShelleyAddr :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era
- fromShelleyAddrIsSbe :: IsShelleyBasedEra era => Addr StandardCrypto -> AddressInEra era
- fromShelleyAddrToAny :: Addr StandardCrypto -> AddressAny
- toShelleyStakeCredential :: StakeCredential -> StakeCredential StandardCrypto
- fromShelleyStakeCredential :: StakeCredential StandardCrypto -> StakeCredential
-
data
NetworkId
- = Mainnet
- | Testnet ! NetworkMagic
- data PaymentCredential
- data StakeAddress where
- data StakeAddressReference
- data StakeCredential
- toShelleyStakeAddr :: StakeAddress -> RewardAcnt StandardCrypto
- fromShelleyStakeAddr :: RewardAcnt StandardCrypto -> StakeAddress
- fromShelleyStakeReference :: StakeReference StandardCrypto -> StakeAddressReference
- fromShelleyPaymentCredential :: PaymentCredential StandardCrypto -> PaymentCredential
-
data
TxBody
era
where
- ShelleyTxBody :: ShelleyBasedEra era -> TxBody ( ShelleyLedgerEra era) -> [ Script ( ShelleyLedgerEra era)] -> TxBodyScriptData era -> Maybe ( AuxiliaryData ( ShelleyLedgerEra era)) -> TxScriptValidity era -> TxBody era
- newtype TxId = TxId ( Hash StandardCrypto EraIndependentTxBody )
- toShelleyTxId :: TxId -> TxId StandardCrypto
- fromShelleyTxId :: TxId StandardCrypto -> TxId
- getTxIdShelley :: Crypto ( ShelleyLedgerEra era) ~ StandardCrypto => UsesTxBody ( ShelleyLedgerEra era) => ShelleyBasedEra era -> TxBody ( ShelleyLedgerEra era) -> TxId
- data TxIn = TxIn TxId TxIx
- toShelleyTxIn :: TxIn -> TxIn StandardCrypto
- fromShelleyTxIn :: TxIn StandardCrypto -> TxIn
- data TxOut ctx era = TxOut ( AddressInEra era) ( TxOutValue era) ( TxOutDatum ctx era) ( ReferenceScript era)
- toShelleyTxOut :: forall era ledgerera. ShelleyLedgerEra era ~ ledgerera => ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera
- fromShelleyTxOut :: ShelleyLedgerEra era ~ ledgerera => ShelleyBasedEra era -> TxOut ledgerera -> TxOut ctx era
- newtype TxIx = TxIx Word
- newtype Lovelace = Lovelace Integer
- toShelleyLovelace :: Lovelace -> Coin
- fromShelleyLovelace :: Coin -> Lovelace
- toMaryValue :: Value -> Value StandardCrypto
- fromMaryValue :: Value StandardCrypto -> Value
- calcMinimumDeposit :: Value -> Lovelace -> Lovelace
-
data
Tx
era
where
- ShelleyTx :: ShelleyBasedEra era -> Tx ( ShelleyLedgerEra era) -> Tx era
-
data
KeyWitness
era
where
- ShelleyBootstrapWitness :: ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era
- ShelleyKeyWitness :: ShelleyBasedEra era -> WitVKey Witness StandardCrypto -> KeyWitness era
-
data
ShelleyWitnessSigningKey
- = WitnessPaymentKey ( SigningKey PaymentKey )
- | WitnessPaymentExtendedKey ( SigningKey PaymentExtendedKey )
- | WitnessStakeKey ( SigningKey StakeKey )
- | WitnessStakeExtendedKey ( SigningKey StakeExtendedKey )
- | WitnessStakePoolKey ( SigningKey StakePoolKey )
- | WitnessGenesisKey ( SigningKey GenesisKey )
- | WitnessGenesisExtendedKey ( SigningKey GenesisExtendedKey )
- | WitnessGenesisDelegateKey ( SigningKey GenesisDelegateKey )
- | WitnessGenesisDelegateExtendedKey ( SigningKey GenesisDelegateExtendedKey )
- data ShelleySigningKey
- getShelleyKeyWitnessVerificationKey :: ShelleySigningKey -> VKey Witness StandardCrypto
- getTxBodyAndWitnesses :: Tx era -> ( TxBody era, [ KeyWitness era])
- makeShelleySignature :: SignableRepresentation tosign => tosign -> ShelleySigningKey -> SignedDSIGN StandardCrypto tosign
- toShelleySigningKey :: ShelleyWitnessSigningKey -> ShelleySigningKey
- fromConsensusBlock :: ConsensusBlockForMode mode ~ block => LedgerSupportsProtocol ( ShelleyBlock ( TPraos StandardCrypto ) ( ShelleyEra StandardCrypto )) => ConsensusMode mode -> block -> BlockInMode mode
- toConsensusBlock :: ConsensusBlockForMode mode ~ block => LedgerSupportsProtocol ( ShelleyBlock ( TPraos StandardCrypto ) ( ShelleyEra StandardCrypto )) => BlockInMode mode -> block
- fromConsensusTip :: ConsensusBlockForMode mode ~ block => ConsensusMode mode -> Tip block -> ChainTip
- fromConsensusPointInMode :: ConsensusMode mode -> Point ( ConsensusBlockForMode mode) -> ChainPoint
- toConsensusPointInMode :: ConsensusMode mode -> ChainPoint -> Point ( ConsensusBlockForMode mode)
- toConsensusPointHF :: HeaderHash block ~ OneEraHash xs => ChainPoint -> Point block
- toShelleyMetadata :: Map Word64 TxMetadataValue -> Map Word64 Metadatum
- fromShelleyMetadata :: Map Word64 Metadatum -> Map Word64 TxMetadataValue
- toShelleyMetadatum :: TxMetadataValue -> Metadatum
- fromShelleyMetadatum :: Metadatum -> TxMetadataValue
-
data
ProtocolParameters
=
ProtocolParameters
{
- protocolParamProtocolVersion :: ( Natural , Natural )
- protocolParamDecentralization :: Maybe Rational
- protocolParamExtraPraosEntropy :: Maybe PraosNonce
- protocolParamMaxBlockHeaderSize :: Natural
- protocolParamMaxBlockBodySize :: Natural
- protocolParamMaxTxSize :: Natural
- protocolParamTxFeeFixed :: Natural
- protocolParamTxFeePerByte :: Natural
- protocolParamMinUTxOValue :: Maybe Lovelace
- protocolParamStakeAddressDeposit :: Lovelace
- protocolParamStakePoolDeposit :: Lovelace
- protocolParamMinPoolCost :: Lovelace
- protocolParamPoolRetireMaxEpoch :: EpochNo
- protocolParamStakePoolTargetNum :: Natural
- protocolParamPoolPledgeInfluence :: Rational
- protocolParamMonetaryExpansion :: Rational
- protocolParamTreasuryCut :: Rational
- protocolParamUTxOCostPerWord :: Maybe Lovelace
- protocolParamCostModels :: Map AnyPlutusScriptVersion CostModel
- protocolParamPrices :: Maybe ExecutionUnitPrices
- protocolParamMaxTxExUnits :: Maybe ExecutionUnits
- protocolParamMaxBlockExUnits :: Maybe ExecutionUnits
- protocolParamMaxValueSize :: Maybe Natural
- protocolParamCollateralPercent :: Maybe Natural
- protocolParamMaxCollateralInputs :: Maybe Natural
- protocolParamUTxOCostPerByte :: Maybe Lovelace
- checkProtocolParameters :: forall era. IsCardanoEra era => ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersError ()
- data ProtocolParametersError
- toShelleyScript :: ScriptInEra era -> Script ( ShelleyLedgerEra era)
- toShelleyMultiSig :: SimpleScript SimpleScriptV1 -> MultiSig StandardCrypto
- fromShelleyMultiSig :: MultiSig StandardCrypto -> SimpleScript lang
- toAllegraTimelock :: forall lang. SimpleScript lang -> Timelock StandardCrypto
- fromAllegraTimelock :: TimeLocksSupported lang -> Timelock StandardCrypto -> SimpleScript lang
- toShelleyScriptHash :: ScriptHash -> ScriptHash StandardCrypto
- fromShelleyScriptHash :: ScriptHash StandardCrypto -> ScriptHash
-
data
PlutusScript
lang
where
- PlutusScriptSerialised :: ShortByteString -> PlutusScript lang
-
data
PlutusScriptOrReferenceInput
lang
- = PScript ( PlutusScript lang)
- | PReferenceScript TxIn ( Maybe ScriptHash )
-
data
SimpleScriptOrReferenceInput
lang
- = SScript ( SimpleScript lang)
- | SReferenceScript TxIn ( Maybe ScriptHash )
- toPlutusData :: ScriptData -> Data
- fromPlutusData :: Data -> ScriptData
- toAlonzoData :: ScriptData -> Data ledgerera
- fromAlonzoData :: Data ledgerera -> ScriptData
- toAlonzoPrices :: ExecutionUnitPrices -> Maybe Prices
- fromAlonzoPrices :: Prices -> ExecutionUnitPrices
- toAlonzoExUnits :: ExecutionUnits -> ExUnits
- fromAlonzoExUnits :: ExUnits -> ExecutionUnits
- toAlonzoRdmrPtr :: ScriptWitnessIndex -> RdmrPtr
- fromAlonzoRdmrPtr :: RdmrPtr -> ScriptWitnessIndex
- scriptDataFromJsonDetailedSchema :: Value -> Either ScriptDataJsonSchemaError ScriptData
- scriptDataToJsonDetailedSchema :: ScriptData -> Value
- calculateExecutionUnitsLovelace :: ExecutionUnitPrices -> ExecutionUnits -> Maybe Lovelace
- data ReferenceScript era where
- data ReferenceTxInsScriptsInlineDatumsSupportedInEra era where
- refInsScriptsAndInlineDatsSupportedInEra :: CardanoEra era -> Maybe ( ReferenceTxInsScriptsInlineDatumsSupportedInEra era)
- refScriptToShelleyScript :: CardanoEra era -> ReferenceScript era -> StrictMaybe ( Script ( ShelleyLedgerEra era))
-
data
Certificate
- = StakeAddressRegistrationCertificate StakeCredential
- | StakeAddressDeregistrationCertificate StakeCredential
- | StakeAddressDelegationCertificate StakeCredential PoolId
- | StakePoolRegistrationCertificate StakePoolParameters
- | StakePoolRetirementCertificate PoolId EpochNo
- | GenesisKeyDelegationCertificate ( Hash GenesisKey ) ( Hash GenesisDelegateKey ) ( Hash VrfKey )
- | MIRCertificate MIRPot MIRTarget
- toShelleyCertificate :: Certificate -> DCert StandardCrypto
- fromShelleyCertificate :: DCert StandardCrypto -> Certificate
- data OperationalCertificate = OperationalCertificate !( OCert StandardCrypto ) !( VerificationKey StakePoolKey )
-
data
OperationalCertificateIssueCounter
=
OperationalCertificateIssueCounter
{
- opCertIssueCount :: ! Word64
- opCertIssueColdKey :: !( VerificationKey StakePoolKey )
- data OperationalCertIssueError = OperationalCertKeyMismatch ( VerificationKey StakePoolKey ) ( VerificationKey StakePoolKey )
- data StakePoolMetadata = StakePoolMetadata ! Text ! Text ! Text ! Text
- stakePoolName :: StakePoolMetadata -> Text
- stakePoolDescription :: StakePoolMetadata -> Text
- stakePoolTicker :: StakePoolMetadata -> Text
- stakePoolHomepage :: StakePoolMetadata -> Text
- data StakePoolMetadataReference = StakePoolMetadataReference Text ( Hash StakePoolMetadata )
- stakePoolMetadataURL :: StakePoolMetadataReference -> Text
- stakePoolMetadataHash :: StakePoolMetadataReference -> Hash StakePoolMetadata
- data StakePoolParameters = StakePoolParameters PoolId ( Hash VrfKey ) Lovelace Rational StakeAddress Lovelace [ Hash StakeKey ] [ StakePoolRelay ] ( Maybe StakePoolMetadataReference )
- stakePoolId :: StakePoolParameters -> PoolId
- stakePoolVRF :: StakePoolParameters -> Hash VrfKey
- stakePoolCost :: StakePoolParameters -> Lovelace
- stakePoolMargin :: StakePoolParameters -> Rational
- stakePoolRewardAccount :: StakePoolParameters -> StakeAddress
- stakePoolPledge :: StakePoolParameters -> Lovelace
- stakePoolOwners :: StakePoolParameters -> [ Hash StakeKey ]
- stakePoolRelays :: StakePoolParameters -> [ StakePoolRelay ]
- stakePoolMetadata :: StakePoolParameters -> Maybe StakePoolMetadataReference
-
data
StakePoolRelay
- = StakePoolRelayIp ( Maybe IPv4 ) ( Maybe IPv6 ) ( Maybe PortNumber )
- | StakePoolRelayDnsARecord ByteString ( Maybe PortNumber )
- | StakePoolRelayDnsSrvRecord ByteString
- newtype EpochNo = EpochNo { }
- data StakePoolKey
- type PoolId = Hash StakePoolKey
- data KesKey
-
newtype
KESPeriod
=
KESPeriod
{
- unKESPeriod :: Word
- data VrfKey
- data LocalNodeConnectInfo mode = LocalNodeConnectInfo ( ConsensusModeParams mode) NetworkId FilePath
- data ShelleyMode
- data ConsensusMode mode where
- data LocalNodeClientProtocols block point tip slot tx txid txerr query m = LocalNodeClientProtocols ( LocalChainSyncClient block point tip m) ( Maybe ( LocalTxSubmissionClient tx txerr m ())) ( Maybe ( LocalStateQueryClient block point query m ())) ( Maybe ( LocalTxMonitorClient txid tx slot m ()))
- type family ShelleyLedgerEra era where ...
-
data
DebugLedgerState
era
where
- DebugLedgerState :: ShelleyLedgerEra era ~ ledgerera => NewEpochState ledgerera -> DebugLedgerState era
- decodeDebugLedgerState :: forall era. FromCBOR ( DebugLedgerState era) => SerialisedDebugLedgerState era -> Either ByteString ( DebugLedgerState era)
- newtype ProtocolState era = ProtocolState ( Serialised ( ChainDepState ( ConsensusProtocol era)))
- decodeProtocolState :: FromCBOR ( ChainDepState ( ConsensusProtocol era)) => ProtocolState era -> Either ( ByteString , DecoderError ) ( ChainDepState ( ConsensusProtocol era))
- newtype SerialisedDebugLedgerState era = SerialisedDebugLedgerState ( Serialised ( NewEpochState ( ShelleyLedgerEra era)))
- newtype SerialisedCurrentEpochState era = SerialisedCurrentEpochState ( Serialised ( EpochState ( ShelleyLedgerEra era)))
- decodeCurrentEpochState :: forall era. Era ( ShelleyLedgerEra era) => Share ( TxOut ( ShelleyLedgerEra era)) ~ Interns ( Credential ' Staking ( Crypto ( ShelleyLedgerEra era))) => FromSharedCBOR ( TxOut ( ShelleyLedgerEra era)) => Share ( TxOut ( ShelleyLedgerEra era)) ~ Interns ( Credential ' Staking ( Crypto ( ShelleyLedgerEra era))) => FromCBOR ( PParams ( ShelleyLedgerEra era)) => FromCBOR ( Value ( ShelleyLedgerEra era)) => FromCBOR ( State ( EraRule "PPUP" ( ShelleyLedgerEra era))) => SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era)
- newtype UTxO era = UTxO { }
- data AcquiringFailure
- newtype SystemStart = SystemStart { }
-
data
LeadershipError
- = LeaderErrDecodeLedgerStateFailure
- | LeaderErrDecodeProtocolStateFailure ( ByteString , DecoderError )
- | LeaderErrDecodeProtocolEpochStateFailure DecoderError
- | LeaderErrGenesisSlot
- | LeaderErrStakePoolHasNoStake PoolId
- | LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo
- | LeaderErrSlotRangeCalculationFailure Text
- | LeaderErrCandidateNonceStillEvolving
- currentEpochEligibleLeadershipSlots :: forall era ledgerera. ShelleyLedgerEra era ~ ledgerera => Era ledgerera => PraosProtocolSupportsNode ( ConsensusProtocol era) => HasField "_d" ( PParams ledgerera) UnitInterval => Share ( TxOut ( ShelleyLedgerEra era)) ~ Interns ( Credential ' Staking ( Crypto ( ShelleyLedgerEra era))) => FromCBOR ( ChainDepState ( ConsensusProtocol era)) => ShelleyBasedEra era -> ShelleyGenesis StandardShelley -> EpochInfo ( Either Text ) -> ProtocolParameters -> ProtocolState era -> PoolId -> SigningKey VrfKey -> SerialisedCurrentEpochState era -> EpochNo -> Either LeadershipError ( Set SlotNo )
- nextEpochEligibleLeadershipSlots :: forall era. HasField "_d" ( PParams ( ShelleyLedgerEra era)) UnitInterval => Era ( ShelleyLedgerEra era) => Share ( TxOut ( ShelleyLedgerEra era)) ~ Interns ( Credential ' Staking ( Crypto ( ShelleyLedgerEra era))) => FromCBOR ( ChainDepState ( ConsensusProtocol era)) => PraosProtocolSupportsNode ( ConsensusProtocol era) => ShelleyBasedEra era -> ShelleyGenesis StandardShelley -> SerialisedCurrentEpochState era -> ProtocolState era -> PoolId -> SigningKey VrfKey -> ProtocolParameters -> EpochInfo ( Either Text ) -> ( ChainTip , EpochNo ) -> Either LeadershipError ( Set SlotNo )
- shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PubKeyHash
- toConsensusGenTx :: ConsensusBlockForMode mode ~ block => TxInMode mode -> GenTx block
- fromAlonzoCostModels :: CostModels -> Map AnyPlutusScriptVersion CostModel
- toShelleyNetwork :: NetworkId -> Network
- fromShelleyPParams :: PParams ledgerera -> ProtocolParameters
Documentation
module Cardano.Api
Genesis
data ShelleyGenesis era Source #
Shelley genesis information
Note that this is needed only for a pure Shelley network, hence it being defined here rather than in its own module. In mainnet, Shelley will transition naturally from Byron, and thus will never have its own genesis information.
ShelleyGenesis | |
|
Instances
shelleyGenesisDefaults :: ShelleyGenesis crypto Source #
Some reasonable starting defaults for constructing a
ShelleyGenesis
.
You must override at least the following fields for this to be useful:
-
sgSystemStart
the time of the first block -
sgNetworkMagic
to a suitable testnet or mainnet network magic number. -
sgGenDelegs
to have some initial nodes -
sgInitialFunds
to have any money in the system -
sgMaxLovelaceSupply
must be at least the sum of thesgInitialFunds
but more if you want to allow for rewards.
Cryptographic key interface
class ( Eq ( VerificationKey keyrole), Show ( VerificationKey keyrole), SerialiseAsRawBytes ( Hash keyrole), HasTextEnvelope ( VerificationKey keyrole), HasTextEnvelope ( SigningKey keyrole)) => Key keyrole where Source #
An interface for cryptographic keys used for signatures with a
SigningKey
and a
VerificationKey
key.
This interface does not provide actual signing or verifying functions since this API is concerned with the management of keys: generating and serialising.
data VerificationKey keyrole :: Type Source #
The type of cryptographic verification key, for each key role.
data SigningKey keyrole :: Type Source #
The type of cryptographic signing key, for each key role.
getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole Source #
Get the corresponding verification key from a signing key.
deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole Source #
Generate a
SigningKey
deterministically, given a
Seed
. The
required size of the seed is given by
deterministicSigningKeySeedSize
.
deterministicSigningKeySeedSize :: AsType keyrole -> Word Source #
verificationKeyHash :: VerificationKey keyrole -> Hash keyrole Source #
Instances
Hashes
data family Hash keyrole :: Type Source #
Instances
Payment addresses
Constructing and inspecting Shelley payment addresses
data Address addrtype where Source #
Addresses are used as locations where assets live. The address determines the rights needed to spend assets at the address: in particular holding some signing key or being able to satisfy the conditions of a script.
There are currently two types of address:
-
Byron addresses, which use the type tag
ByronAddr
; and -
Shelley addresses, which use the type tag
ShelleyAddr
. Notably, Shelley addresses support scripts and stake delegation.
The
address type
is subtly from the
ledger era
in which each
address type is valid: while Byron addresses are the only choice in the
Byron era, the Shelley era and all subsequent eras support both Byron and
Shelley addresses. The
Address
type param only says the type of the address
(either Byron or Shelley). The
AddressInEra
type connects the address type
with the era in which it is supported.
ShelleyAddress :: Network -> PaymentCredential StandardCrypto -> StakeReference StandardCrypto -> Address ShelleyAddr |
Shelley addresses allow delegation. Shelley addresses were introduced in Shelley era and are thus supported from the Shelley era onwards |
Instances
toShelleyAddr :: AddressInEra era -> Addr StandardCrypto Source #
fromShelleyAddr :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era Source #
fromShelleyAddrIsSbe :: IsShelleyBasedEra era => Addr StandardCrypto -> AddressInEra era Source #
Stake addresses
data PaymentCredential Source #
Instances
Eq PaymentCredential Source # | |
Defined in Cardano.Api.Address (==) :: PaymentCredential -> PaymentCredential -> Bool Source # (/=) :: PaymentCredential -> PaymentCredential -> Bool Source # |
|
Ord PaymentCredential Source # | |
Defined in Cardano.Api.Address compare :: PaymentCredential -> PaymentCredential -> Ordering Source # (<) :: PaymentCredential -> PaymentCredential -> Bool Source # (<=) :: PaymentCredential -> PaymentCredential -> Bool Source # (>) :: PaymentCredential -> PaymentCredential -> Bool Source # (>=) :: PaymentCredential -> PaymentCredential -> Bool Source # max :: PaymentCredential -> PaymentCredential -> PaymentCredential Source # min :: PaymentCredential -> PaymentCredential -> PaymentCredential Source # |
|
Show PaymentCredential Source # | |
Defined in Cardano.Api.Address |
data StakeAddress where Source #
Instances
data StakeAddressReference Source #
Instances
Eq StakeAddressReference Source # | |
Defined in Cardano.Api.Address (==) :: StakeAddressReference -> StakeAddressReference -> Bool Source # (/=) :: StakeAddressReference -> StakeAddressReference -> Bool Source # |
|
Show StakeAddressReference Source # | |
Defined in Cardano.Api.Address |
data StakeCredential Source #
Instances
Eq StakeCredential Source # | |
Defined in Cardano.Api.Address (==) :: StakeCredential -> StakeCredential -> Bool Source # (/=) :: StakeCredential -> StakeCredential -> Bool Source # |
|
Ord StakeCredential Source # | |
Defined in Cardano.Api.Address compare :: StakeCredential -> StakeCredential -> Ordering Source # (<) :: StakeCredential -> StakeCredential -> Bool Source # |