Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api.Shelley
Description
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 c = ShelleyGenesis {
- sgSystemStart :: !UTCTime
- sgNetworkMagic :: !Word32
- sgNetworkId :: !Network
- sgActiveSlotsCoeff :: !PositiveUnitInterval
- sgSecurityParam :: !Word64
- sgEpochLength :: !EpochSize
- sgSlotsPerKESPeriod :: !Word64
- sgMaxKESEvolutions :: !Word64
- sgSlotLength :: !NominalDiffTimeMicro
- sgUpdateQuorum :: !Word64
- sgMaxLovelaceSupply :: !Word64
- sgProtocolParams :: !(PParams (ShelleyEra c))
- sgGenDelegs :: !(Map (KeyHash 'Genesis c) (GenDelegPair c))
- sgInitialFunds :: ListMap (Addr c) Coin
- sgStaking :: ShelleyGenesisStaking c
- shelleyGenesisDefaults :: ShelleyGenesis StandardCrypto
- alonzoGenesisDefaults :: CardanoEra era -> AlonzoGenesis
- decodeAlonzoGenesis :: forall era t (m :: Type -> Type). MonadTransError String t m => Maybe (CardanoEra era) -> ByteString -> t m AlonzoGenesis
- conwayGenesisDefaults :: ConwayGenesis StandardCrypto
- class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where
- data VerificationKey keyrole
- data SigningKey keyrole
- getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole
- deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole
- deterministicSigningKeySeedSize :: AsType keyrole -> Word
- verificationKeyHash :: VerificationKey keyrole -> Hash keyrole
- data family VerificationKey keyrole
- data family SigningKey keyrole
- data family Hash keyrole
- data family AsType t
- data Address addrtype where
- toShelleyAddr :: AddressInEra era -> Addr StandardCrypto
- fromShelleyAddr :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era
- fromShelleyAddrIsSbe :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era
- fromShelleyAddrToAny :: Addr StandardCrypto -> AddressAny
- toShelleyStakeCredential :: StakeCredential -> StakeCredential StandardCrypto
- fromShelleyStakeCredential :: StakeCredential StandardCrypto -> StakeCredential
- data NetworkId
- data PaymentCredential
- data StakeAddress where
- data StakeAddressReference
- data StakeCredential
- toShelleyStakeAddr :: StakeAddress -> RewardAccount StandardCrypto
- fromShelleyStakeAddr :: RewardAccount StandardCrypto -> StakeAddress
- fromShelleyStakeReference :: StakeReference StandardCrypto -> StakeAddressReference
- fromShelleyPaymentCredential :: PaymentCredential StandardCrypto -> PaymentCredential
- data TxBody era where
- ShelleyTxBody :: forall era. ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> [Script (ShelleyLedgerEra era)] -> TxBodyScriptData era -> Maybe (TxAuxData (ShelleyLedgerEra era)) -> TxScriptValidity era -> TxBody era
- newtype TxId = TxId (Hash StandardCrypto EraIndependentTxBody)
- toShelleyTxId :: TxId -> TxId StandardCrypto
- fromShelleyTxId :: TxId StandardCrypto -> TxId
- getTxIdShelley :: (EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto, EraTxBody (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 :: (HasCallStack, ShelleyLedgerEra era ~ ledgerera) => ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera
- fromShelleyTxOut :: ShelleyBasedEra era -> TxOut (ShelleyLedgerEra era) -> TxOut ctx era
- newtype TxIx = TxIx Word
- toMaryValue :: Value -> MaryValue StandardCrypto
- fromMaryValue :: MaryValue StandardCrypto -> Value
- calcMinimumDeposit :: Value -> Lovelace -> Lovelace
- signArbitraryBytesKes :: SigningKey KesKey -> Period -> ByteString -> SignedKES (KES StandardCrypto) ByteString
- data Tx era where
- ShelleyTx :: forall era. ShelleyBasedEra era -> Tx (ShelleyLedgerEra era) -> Tx era
- data KeyWitness era where
- ShelleyBootstrapWitness :: forall era. ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era
- ShelleyKeyWitness :: forall era. 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 :: CardanoBlock StandardCrypto ~ block => block -> BlockInMode
- toConsensusBlock :: CardanoBlock StandardCrypto ~ block => BlockInMode -> block
- fromConsensusTip :: CardanoBlock StandardCrypto ~ block => Tip block -> ChainTip
- fromConsensusPointHF :: forall block (xs :: [Type]). HeaderHash block ~ OneEraHash xs => Point block -> ChainPoint
- toConsensusPointHF :: forall block (xs :: [Type]). 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
- newtype LedgerProtocolParameters era = LedgerProtocolParameters {}
- data EraBasedProtocolParametersUpdate era where
- ShelleyEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams ShelleyEra -> DeprecatedAfterBabbagePParams ShelleyEra -> ShelleyToAlonzoPParams ShelleyEra -> EraBasedProtocolParametersUpdate ShelleyEra
- AllegraEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams AllegraEra -> ShelleyToAlonzoPParams AllegraEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate AllegraEra
- MaryEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams MaryEra -> ShelleyToAlonzoPParams MaryEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate MaryEra
- AlonzoEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> ShelleyToAlonzoPParams AlonzoEra -> AlonzoOnwardsPParams AlonzoEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate AlonzoEra
- BabbageEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> AlonzoOnwardsPParams BabbageEra -> DeprecatedAfterBabbagePParams ShelleyEra -> IntroducedInBabbagePParams BabbageEra -> EraBasedProtocolParametersUpdate BabbageEra
- ConwayEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> AlonzoOnwardsPParams ConwayEra -> IntroducedInBabbagePParams ConwayEra -> IntroducedInConwayPParams (ShelleyLedgerEra ConwayEra) -> EraBasedProtocolParametersUpdate ConwayEra
- data CommonProtocolParametersUpdate = CommonProtocolParametersUpdate {
- cppMinFeeA :: StrictMaybe Coin
- cppMinFeeB :: StrictMaybe Coin
- cppMaxBlockBodySize :: StrictMaybe Word32
- cppMaxTxSize :: StrictMaybe Word32
- cppMaxBlockHeaderSize :: StrictMaybe Word16
- cppKeyDeposit :: StrictMaybe Coin
- cppPoolDeposit :: StrictMaybe Coin
- cppPoolRetireMaxEpoch :: StrictMaybe EpochInterval
- cppStakePoolTargetNum :: StrictMaybe Word16
- cppPoolPledgeInfluence :: StrictMaybe NonNegativeInterval
- cppTreasuryExpansion :: StrictMaybe UnitInterval
- cppMonetaryExpansion :: StrictMaybe UnitInterval
- cppMinPoolCost :: StrictMaybe Coin
- data AlonzoOnwardsPParams ledgerera = AlonzoOnwardsPParams {}
- newtype DeprecatedAfterBabbagePParams ledgerera = DeprecatedAfterBabbagePParams (StrictMaybe ProtVer)
- newtype DeprecatedAfterMaryPParams ledgerera = DeprecatedAfterMaryPParams (StrictMaybe Coin)
- data ShelleyToAlonzoPParams ledgerera = ShelleyToAlonzoPParams (StrictMaybe Nonce) (StrictMaybe UnitInterval)
- newtype IntroducedInBabbagePParams era = IntroducedInBabbagePParams (StrictMaybe CoinPerByte)
- data IntroducedInConwayPParams era = IntroducedInConwayPParams {
- icPoolVotingThresholds :: StrictMaybe PoolVotingThresholds
- icDRepVotingThresholds :: StrictMaybe DRepVotingThresholds
- icMinCommitteeSize :: StrictMaybe Natural
- icCommitteeTermLength :: StrictMaybe EpochInterval
- icGovActionLifetime :: StrictMaybe EpochInterval
- icGovActionDeposit :: StrictMaybe Coin
- icDRepDeposit :: StrictMaybe Coin
- icDRepActivity :: StrictMaybe EpochInterval
- icMinFeeRefScriptCostPerByte :: StrictMaybe NonNegativeInterval
- createEraBasedProtocolParamUpdate :: ShelleyBasedEra era -> EraBasedProtocolParametersUpdate era -> PParamsUpdate (ShelleyLedgerEra era)
- convertToLedgerProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersConversionError (LedgerProtocolParameters era)
- data ProtocolParameters = ProtocolParameters {
- protocolParamProtocolVersion :: (Natural, Natural)
- protocolParamDecentralization :: Maybe Rational
- protocolParamExtraPraosEntropy :: Maybe PraosNonce
- protocolParamMaxBlockHeaderSize :: Natural
- protocolParamMaxBlockBodySize :: Natural
- protocolParamMaxTxSize :: Natural
- protocolParamTxFeeFixed :: Coin
- protocolParamTxFeePerByte :: Coin
- protocolParamMinUTxOValue :: Maybe Coin
- protocolParamStakeAddressDeposit :: Coin
- protocolParamStakePoolDeposit :: Coin
- protocolParamMinPoolCost :: Coin
- protocolParamPoolRetireMaxEpoch :: EpochInterval
- protocolParamStakePoolTargetNum :: Word16
- protocolParamPoolPledgeInfluence :: Rational
- protocolParamMonetaryExpansion :: Rational
- protocolParamTreasuryCut :: Rational
- protocolParamCostModels :: Map AnyPlutusScriptVersion CostModel
- protocolParamPrices :: Maybe ExecutionUnitPrices
- protocolParamMaxTxExUnits :: Maybe ExecutionUnits
- protocolParamMaxBlockExUnits :: Maybe ExecutionUnits
- protocolParamMaxValueSize :: Maybe Natural
- protocolParamCollateralPercent :: Maybe Natural
- protocolParamMaxCollateralInputs :: Maybe Natural
- protocolParamUTxOCostPerByte :: Maybe Coin
- checkProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersError ()
- data ProtocolParametersError
- fromShelleyBasedScript :: ShelleyBasedEra era -> Script (ShelleyLedgerEra era) -> ScriptInEra era
- toShelleyScript :: ScriptInEra era -> Script (ShelleyLedgerEra era)
- toShelleyMultiSig :: SimpleScript -> Either MultiSigError (MultiSig (ShelleyLedgerEra ShelleyEra))
- fromShelleyMultiSig :: MultiSig (ShelleyLedgerEra ShelleyEra) -> SimpleScript
- toAllegraTimelock :: (AllegraEraScript era, EraCrypto era ~ StandardCrypto, NativeScript era ~ Timelock era) => SimpleScript -> NativeScript era
- fromAllegraTimelock :: (AllegraEraScript era, EraCrypto era ~ StandardCrypto) => NativeScript era -> SimpleScript
- toShelleyScriptHash :: ScriptHash -> ScriptHash StandardCrypto
- fromShelleyScriptHash :: ScriptHash StandardCrypto -> ScriptHash
- data PlutusScript lang where
- PlutusScriptSerialised :: forall lang. ShortByteString -> PlutusScript lang
- data PlutusScriptOrReferenceInput lang
- = PScript (PlutusScript lang)
- | PReferenceScript TxIn
- data SimpleScriptOrReferenceInput lang
- toAlonzoLanguage :: AnyPlutusScriptVersion -> Language
- fromAlonzoLanguage :: Language -> AnyPlutusScriptVersion
- toPlutusData :: ScriptData -> Data
- fromPlutusData :: Data -> ScriptData
- toAlonzoData :: Era ledgerera => HashableScriptData -> Data ledgerera
- fromAlonzoData :: Data ledgerera -> HashableScriptData
- toAlonzoPrices :: ExecutionUnitPrices -> Either ProtocolParametersConversionError Prices
- fromAlonzoPrices :: Prices -> ExecutionUnitPrices
- toAlonzoExUnits :: ExecutionUnits -> ExUnits
- fromAlonzoExUnits :: ExUnits -> ExecutionUnits
- toScriptIndex :: AlonzoEraOnwards era -> PlutusPurpose AsIx (ShelleyLedgerEra era) -> ScriptWitnessIndex
- scriptDataFromJsonDetailedSchema :: Value -> Either ScriptDataJsonSchemaError HashableScriptData
- scriptDataToJsonDetailedSchema :: HashableScriptData -> Value
- calculateExecutionUnitsLovelace :: Prices -> ExecutionUnits -> Maybe Coin
- data ReferenceScript era where
- ReferenceScript :: forall era. BabbageEraOnwards era -> ScriptInAnyLang -> ReferenceScript era
- ReferenceScriptNone :: forall era. ReferenceScript era
- refScriptToShelleyScript :: ShelleyBasedEra era -> ReferenceScript era -> StrictMaybe (Script (ShelleyLedgerEra era))
- data Certificate era where
- ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era
- ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era
- toShelleyCertificate :: Certificate era -> TxCert (ShelleyLedgerEra era)
- fromShelleyCertificate :: ShelleyBasedEra era -> TxCert (ShelleyLedgerEra era) -> Certificate era
- toShelleyPoolParams :: StakePoolParameters -> PoolParams StandardCrypto
- data OperationalCertificate = OperationalCertificate !(OCert StandardCrypto) !(VerificationKey StakePoolKey)
- data OperationalCertificateIssueCounter = OperationalCertificateIssueCounter {}
- 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) Coin Rational StakeAddress Coin [Hash StakeKey] [StakePoolRelay] (Maybe StakePoolMetadataReference)
- stakePoolId :: StakePoolParameters -> PoolId
- stakePoolVRF :: StakePoolParameters -> Hash VrfKey
- stakePoolCost :: StakePoolParameters -> Coin
- stakePoolMargin :: StakePoolParameters -> Rational
- stakePoolRewardAccount :: StakePoolParameters -> StakeAddress
- stakePoolPledge :: StakePoolParameters -> Coin
- 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 {}
- createAnchor :: Url -> ByteString -> Anchor StandardCrypto
- createPreviousGovernanceActionId :: forall era (r :: GovActionPurpose). EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto => TxId -> Word16 -> GovPurposeId r (ShelleyLedgerEra era)
- createGovernanceActionId :: TxId -> Word16 -> GovActionId StandardCrypto
- newtype DRepMetadata = DRepMetadata ByteString
- data DRepMetadataReference = DRepMetadataReference Text (Hash DRepMetadata)
- data StakePoolKey
- type PoolId = Hash StakePoolKey
- data KesKey
- newtype KESPeriod = KESPeriod {
- unKESPeriod :: Word
- data VrfKey
- data LocalNodeConnectInfo = LocalNodeConnectInfo ConsensusModeParams NetworkId SocketPath
- data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) = 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 = (ledgerera :: Type) | ledgerera -> era where ...
- data LedgerEvent
- = PoolRegistration
- | PoolReRegistration
- | IncrementalRewardsDistribution EpochNo (Map StakeCredential (Set (Reward StandardCrypto)))
- | RewardsDistribution EpochNo (Map StakeCredential (Set (Reward StandardCrypto)))
- | MIRDistribution MIRDistributionDetails
- | PoolReap PoolReapDetails
- | SuccessfulPlutusScript (NonEmpty (PlutusWithContext StandardCrypto))
- | FailedPlutusScript (NonEmpty (PlutusWithContext StandardCrypto))
- | NewGovernanceProposals (TxId StandardCrypto) AnyProposals
- | RemovedGovernanceVotes (TxId StandardCrypto) (Set (Voter StandardCrypto, GovActionId StandardCrypto)) (Set (Credential 'DRepRole StandardCrypto))
- | EpochBoundaryRatificationState AnyRatificationState
- data AnyProposals = EraPParams era => AnyProposals (Proposals era)
- data AnyRatificationState = EraPParams era => AnyRatificationState (RatifyState era)
- data MIRDistributionDetails = MIRDistributionDetails {}
- data PoolReapDetails = PoolReapDetails {}
- toLedgerEvent :: ConvertLedgerEvent blk => WrapLedgerEvent blk -> Maybe LedgerEvent
- newtype DebugLedgerState era = DebugLedgerState {}
- decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either (ByteString, DecoderError) (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 CurrentEpochState era = CurrentEpochState (EpochState (ShelleyLedgerEra era))
- newtype SerialisedCurrentEpochState era = SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era)))
- decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era)
- newtype PoolState era = PoolState (PState (ShelleyLedgerEra era))
- newtype SerialisedPoolState era = SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era)))
- decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era)
- newtype PoolDistribution era = PoolDistribution {
- unPoolDistr :: PoolDistr (EraCrypto (ShelleyLedgerEra era))
- newtype SerialisedPoolDistribution era = SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era))))
- decodePoolDistribution :: Crypto (EraCrypto (ShelleyLedgerEra era)) => ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era)
- newtype StakeSnapshot era = StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))
- newtype SerialisedStakeSnapshots era = SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))))
- decodeStakeSnapshot :: FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era)
- decodeBigLedgerPeerSnapshot :: Serialised LedgerPeerSnapshot -> Either (ByteString, DecoderError) LedgerPeerSnapshot
- newtype UTxO era = UTxO {}
- data AcquiringFailure
- newtype SystemStart = SystemStart {}
- data GovernanceAction era
- = MotionOfNoConfidence (StrictMaybe (GovPurposeId 'CommitteePurpose (ShelleyLedgerEra era)))
- | ProposeNewConstitution (StrictMaybe (GovPurposeId 'ConstitutionPurpose (ShelleyLedgerEra era))) (Anchor StandardCrypto) (StrictMaybe (ScriptHash StandardCrypto))
- | ProposeNewCommittee (StrictMaybe (GovPurposeId 'CommitteePurpose (ShelleyLedgerEra era))) [Credential 'ColdCommitteeRole StandardCrypto] (Map (Credential 'ColdCommitteeRole StandardCrypto) EpochNo) Rational
- | InfoAct
- | TreasuryWithdrawal [(Network, StakeCredential, Coin)] !(StrictMaybe (ScriptHash StandardCrypto))
- | InitiateHardfork (StrictMaybe (GovPurposeId 'HardForkPurpose (ShelleyLedgerEra era))) ProtVer
- | UpdatePParams (StrictMaybe (GovPurposeId 'PParamUpdatePurpose (ShelleyLedgerEra era))) (PParamsUpdate (ShelleyLedgerEra era)) !(StrictMaybe (ScriptHash StandardCrypto))
- newtype GovernanceActionId era = GovernanceActionId {
- unGovernanceActionId :: GovActionId (EraCrypto (ShelleyLedgerEra era))
- newtype Proposal era = Proposal {
- unProposal :: ProposalProcedure (ShelleyLedgerEra era)
- newtype VotingProcedure era = VotingProcedure {}
- newtype VotingProcedures era = VotingProcedures {}
- data GovernancePoll = GovernancePoll {
- govPollQuestion :: Text
- govPollAnswers :: [Text]
- govPollNonce :: Maybe Word
- data GovernancePollAnswer = GovernancePollAnswer {}
- data GovernancePollError
- = ErrGovernancePollMismatch GovernancePollMismatchError
- | ErrGovernancePollNoAnswer
- | ErrGovernancePollUnauthenticated
- | ErrGovernancePollMalformedAnswer DecoderError
- | ErrGovernancePollInvalidAnswer GovernancePollInvalidAnswerError
- data Vote
- newtype Voter era = Voter (Voter (EraCrypto (ShelleyLedgerEra era)))
- createProposalProcedure :: ShelleyBasedEra era -> Network -> Coin -> StakeCredential -> GovernanceAction era -> Anchor StandardCrypto -> Proposal era
- createVotingProcedure :: ConwayEraOnwards era -> Vote -> Maybe (Url, Text) -> VotingProcedure era
- renderGovernancePollError :: GovernancePollError -> Text
- fromProposalProcedure :: ShelleyBasedEra era -> Proposal era -> (Coin, StakeCredential, GovernanceAction era)
- hashGovernancePoll :: GovernancePoll -> Hash GovernancePoll
- verifyPollAnswer :: GovernancePoll -> InAnyShelleyBasedEra Tx -> Either GovernancePollError [Hash PaymentKey]
- data LeadershipError
- = LeaderErrDecodeLedgerStateFailure
- | LeaderErrDecodeProtocolStateFailure (ByteString, DecoderError)
- | LeaderErrDecodeProtocolEpochStateFailure DecoderError
- | LeaderErrGenesisSlot
- | LeaderErrStakePoolHasNoStake PoolId
- | LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo
- | LeaderErrSlotRangeCalculationFailure Text
- | LeaderErrCandidateNonceStillEvolving
- currentEpochEligibleLeadershipSlots :: ShelleyBasedEra era -> ShelleyGenesis StandardCrypto -> EpochInfo (Either Text) -> PParams (ShelleyLedgerEra era) -> ProtocolState era -> PoolId -> SigningKey VrfKey -> SerialisedPoolDistribution era -> EpochNo -> Either LeadershipError (Set SlotNo)
- evaluateTransactionExecutionUnitsShelley :: ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> Tx (ShelleyLedgerEra era) -> Either (TransactionValidityError era) (Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits)))
- nextEpochEligibleLeadershipSlots :: ShelleyBasedEra era -> ShelleyGenesis StandardCrypto -> SerialisedCurrentEpochState era -> ProtocolState era -> PoolId -> SigningKey VrfKey -> PParams (ShelleyLedgerEra era) -> EpochInfo (Either Text) -> (ChainTip, EpochNo) -> Either LeadershipError (Set SlotNo)
- shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PubKeyHash
- toConsensusGenTx :: CardanoBlock StandardCrypto ~ block => TxInMode -> GenTx block
- fromAlonzoCostModels :: CostModels -> Map AnyPlutusScriptVersion CostModel
- toLedgerNonce :: Maybe PraosNonce -> Nonce
- toShelleyNetwork :: NetworkId -> Network
- fromShelleyPoolParams :: PoolParams StandardCrypto -> StakePoolParameters
- fromLedgerPParamsUpdate :: ShelleyBasedEra era -> PParamsUpdate (ShelleyLedgerEra era) -> ProtocolParametersUpdate
- emptyVotingProcedures :: VotingProcedures era
- mergeVotingProcedures :: VotingProcedures era -> VotingProcedures era -> Either (VotesMergingConflict era) (VotingProcedures era)
- singletonVotingProcedures :: ConwayEraOnwards era -> Voter (EraCrypto (ShelleyLedgerEra era)) -> GovActionId (EraCrypto (ShelleyLedgerEra era)) -> VotingProcedure (ShelleyLedgerEra era) -> VotingProcedures era
- newtype VotesMergingConflict era = VotesMergingConflict (Voter (EraCrypto (ShelleyLedgerEra era)), [GovActionId (EraCrypto (ShelleyLedgerEra era))])
Documentation
module Cardano.Api
Genesis
data ShelleyGenesis c 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.
Constructors
ShelleyGenesis | |
Fields
|
Instances
shelleyGenesisDefaults :: ShelleyGenesis StandardCrypto 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 blocksgNetworkMagic
to a suitable testnet or mainnet network magic number.sgGenDelegs
to have some initial nodessgInitialFunds
to have any money in the systemsgMaxLovelaceSupply
must be at least the sum of thesgInitialFunds
but more if you want to allow for rewards.
alonzoGenesisDefaults :: CardanoEra era -> AlonzoGenesis Source #
Some reasonable starting defaults for constructing a AlonzoGenesis
.
Based on https://github.com/IntersectMBO/cardano-node/blob/master/cardano-testnet/src/Testnet/Defaults.hs
The era determines Plutus V2 cost model parameters:
* Conway: 185
* <= Babbage: 175
Arguments
:: forall era t (m :: Type -> Type). MonadTransError String t m | |
=> Maybe (CardanoEra era) | An optional era witness in which we're reading the genesis |
-> ByteString | Genesis JSON |
-> t m AlonzoGenesis |
Decode Alonzo genesis in an optionally era sensitive way.
Because the Plutus V2 cost model has changed between Babbage and Conway era, we need to know the era if we want to decde Alonzo Genesis with a cost model baked in. If the V2 cost model is present in genesis, you need to provide an era witness.
When an era witness is provided, for Plutus V2 model the function additionally: 1. Does extra cost model parameters name validation: Checks for mandatory 175 parameters if provided in a map form. 2. If >= Conway: adds defaults for new 10 parameters, if they were not provided (maxBound) 3. Removes extra parameters above the max count: Babbage - 175, Conway - 185.
conwayGenesisDefaults :: ConwayGenesis StandardCrypto Source #
Some reasonable starting defaults for constructing a ConwayGenesis
.
Based on https://github.com/IntersectMBO/cardano-node/blob/master/cardano-testnet/src/Testnet/Defaults.hs
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.
Associated Types
data VerificationKey keyrole Source #
The type of cryptographic verification key, for each key role.
data SigningKey keyrole Source #
The type of cryptographic signing key, for each key role.
Methods
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
Key ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods getVerificationKey :: SigningKey ByronKey -> VerificationKey ByronKey Source # deterministicSigningKey :: AsType ByronKey -> Seed -> SigningKey ByronKey Source # deterministicSigningKeySeedSize :: AsType ByronKey -> Word Source # verificationKeyHash :: VerificationKey ByronKey -> Hash ByronKey Source # | |||||||||
Key ByronKeyLegacy Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods getVerificationKey :: SigningKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy Source # deterministicSigningKey :: AsType ByronKeyLegacy -> Seed -> SigningKey ByronKeyLegacy Source # deterministicSigningKeySeedSize :: AsType ByronKeyLegacy -> Word Source # verificationKeyHash :: VerificationKey ByronKeyLegacy -> Hash ByronKeyLegacy Source # | |||||||||
Key KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
Key VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
Key CommitteeColdExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeColdExtendedKey -> VerificationKey CommitteeColdExtendedKey Source # deterministicSigningKey :: AsType CommitteeColdExtendedKey -> Seed -> SigningKey CommitteeColdExtendedKey Source # deterministicSigningKeySeedSize :: AsType CommitteeColdExtendedKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # | |||||||||
Key CommitteeColdKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeColdKey -> VerificationKey CommitteeColdKey Source # deterministicSigningKey :: AsType CommitteeColdKey -> Seed -> SigningKey CommitteeColdKey Source # deterministicSigningKeySeedSize :: AsType CommitteeColdKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeColdKey -> Hash CommitteeColdKey Source # | |||||||||
Key CommitteeHotExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeHotExtendedKey -> VerificationKey CommitteeHotExtendedKey Source # deterministicSigningKey :: AsType CommitteeHotExtendedKey -> Seed -> SigningKey CommitteeHotExtendedKey Source # deterministicSigningKeySeedSize :: AsType CommitteeHotExtendedKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # | |||||||||
Key CommitteeHotKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeHotKey -> VerificationKey CommitteeHotKey Source # deterministicSigningKey :: AsType CommitteeHotKey -> Seed -> SigningKey CommitteeHotKey Source # deterministicSigningKeySeedSize :: AsType CommitteeHotKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeHotKey -> Hash CommitteeHotKey Source # | |||||||||
Key DRepExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey DRepExtendedKey -> VerificationKey DRepExtendedKey Source # deterministicSigningKey :: AsType DRepExtendedKey -> Seed -> SigningKey DRepExtendedKey Source # deterministicSigningKeySeedSize :: AsType DRepExtendedKey -> Word Source # verificationKeyHash :: VerificationKey DRepExtendedKey -> Hash DRepExtendedKey Source # | |||||||||
Key DRepKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey DRepKey -> VerificationKey DRepKey Source # deterministicSigningKey :: AsType DRepKey -> Seed -> SigningKey DRepKey Source # deterministicSigningKeySeedSize :: AsType DRepKey -> Word Source # verificationKeyHash :: VerificationKey DRepKey -> Hash DRepKey Source # | |||||||||
Key GenesisDelegateExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisDelegateExtendedKey -> VerificationKey GenesisDelegateExtendedKey Source # deterministicSigningKey :: AsType GenesisDelegateExtendedKey -> Seed -> SigningKey GenesisDelegateExtendedKey Source # deterministicSigningKeySeedSize :: AsType GenesisDelegateExtendedKey -> Word Source # verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # | |||||||||
Key GenesisDelegateKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey Source # deterministicSigningKey :: AsType GenesisDelegateKey -> Seed -> SigningKey GenesisDelegateKey Source # deterministicSigningKeySeedSize :: AsType GenesisDelegateKey -> Word Source # verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey Source # | |||||||||
Key GenesisExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisExtendedKey -> VerificationKey GenesisExtendedKey Source # deterministicSigningKey :: AsType GenesisExtendedKey -> Seed -> SigningKey GenesisExtendedKey Source # deterministicSigningKeySeedSize :: AsType GenesisExtendedKey -> Word Source # verificationKeyHash :: VerificationKey GenesisExtendedKey -> Hash GenesisExtendedKey Source # | |||||||||
Key GenesisKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey Source # deterministicSigningKey :: AsType GenesisKey -> Seed -> SigningKey GenesisKey Source # deterministicSigningKeySeedSize :: AsType GenesisKey -> Word Source # verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey Source # | |||||||||
Key GenesisUTxOKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey Source # deterministicSigningKey :: AsType GenesisUTxOKey -> Seed -> SigningKey GenesisUTxOKey Source # deterministicSigningKeySeedSize :: AsType GenesisUTxOKey -> Word Source # verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey Source # | |||||||||
Key PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey PaymentExtendedKey -> VerificationKey PaymentExtendedKey Source # deterministicSigningKey :: AsType PaymentExtendedKey -> Seed -> SigningKey PaymentExtendedKey Source # deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word Source # verificationKeyHash :: VerificationKey PaymentExtendedKey -> Hash PaymentExtendedKey Source # | |||||||||
Key PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey Source # deterministicSigningKey :: AsType PaymentKey -> Seed -> SigningKey PaymentKey Source # deterministicSigningKeySeedSize :: AsType PaymentKey -> Word Source # verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey Source # | |||||||||
Key StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakeExtendedKey -> VerificationKey StakeExtendedKey Source # deterministicSigningKey :: AsType StakeExtendedKey -> Seed -> SigningKey StakeExtendedKey Source # deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word Source # verificationKeyHash :: VerificationKey StakeExtendedKey -> Hash StakeExtendedKey Source # | |||||||||
Key StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey Source # deterministicSigningKey :: AsType StakeKey -> Seed -> SigningKey StakeKey Source # deterministicSigningKeySeedSize :: AsType StakeKey -> Word Source # verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey Source # | |||||||||
Key StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey Source # deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey Source # deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word Source # verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey Source # |
data family VerificationKey keyrole Source #
The type of cryptographic verification key, for each key role.
Instances
IsString (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||
IsString (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> VerificationKey ByronKeyLegacy Source # | |||||
IsString (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey KesKey Source # | |||||
IsString (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey VrfKey Source # | |||||
IsString (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeColdExtendedKey Source # | |||||
IsString (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeColdKey Source # | |||||
IsString (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeHotExtendedKey Source # | |||||
IsString (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeHotKey Source # | |||||
IsString (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey DRepExtendedKey Source # | |||||
IsString (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateExtendedKey Source # | |||||
IsString (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateKey Source # | |||||
IsString (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisExtendedKey Source # | |||||
IsString (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisUTxOKey Source # | |||||
IsString (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey PaymentExtendedKey Source # | |||||
IsString (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakeExtendedKey Source # | |||||
IsString (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakePoolKey Source # | |||||
Show (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> VerificationKey ByronKeyLegacy -> ShowS Source # show :: VerificationKey ByronKeyLegacy -> String Source # showList :: [VerificationKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeColdExtendedKey -> ShowS Source # show :: VerificationKey CommitteeColdExtendedKey -> String Source # showList :: [VerificationKey CommitteeColdExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeColdKey -> ShowS Source # show :: VerificationKey CommitteeColdKey -> String Source # showList :: [VerificationKey CommitteeColdKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeHotExtendedKey -> ShowS Source # show :: VerificationKey CommitteeHotExtendedKey -> String Source # showList :: [VerificationKey CommitteeHotExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeHotKey -> ShowS Source # show :: VerificationKey CommitteeHotKey -> String Source # showList :: [VerificationKey CommitteeHotKey] -> ShowS Source # | |||||
Show (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey DRepExtendedKey -> ShowS Source # show :: VerificationKey DRepExtendedKey -> String Source # showList :: [VerificationKey DRepExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS Source # show :: VerificationKey GenesisDelegateExtendedKey -> String Source # showList :: [VerificationKey GenesisDelegateExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisDelegateKey -> ShowS Source # show :: VerificationKey GenesisDelegateKey -> String Source # showList :: [VerificationKey GenesisDelegateKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisExtendedKey -> ShowS Source # show :: VerificationKey GenesisExtendedKey -> String Source # showList :: [VerificationKey GenesisExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisKey -> ShowS Source # show :: VerificationKey GenesisKey -> String Source # showList :: [VerificationKey GenesisKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS Source # show :: VerificationKey GenesisUTxOKey -> String Source # showList :: [VerificationKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS Source # show :: VerificationKey PaymentExtendedKey -> String Source # showList :: [VerificationKey PaymentExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentKey -> ShowS Source # show :: VerificationKey PaymentKey -> String Source # showList :: [VerificationKey PaymentKey] -> ShowS Source # | |||||
Show (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS Source # show :: VerificationKey StakeExtendedKey -> String Source # showList :: [VerificationKey StakeExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS Source # show :: VerificationKey StakePoolKey -> String Source # showList :: [VerificationKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (VerificationKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (VerificationKey a) -> AsType (VerificationKey a) Source # | |||||
SerialiseAsBech32 (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey KesKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey KesKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey VrfKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey VrfKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey DRepExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey DRepExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey DRepKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey DRepKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakePoolKey) -> [Text] | |||||
SerialiseAsCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: VerificationKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey ByronKey) -> ByteString -> Either DecoderError (VerificationKey ByronKey) Source # | |||||
SerialiseAsCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey KesKey) -> ByteString -> Either DecoderError (VerificationKey KesKey) Source # | |||||
SerialiseAsCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey VrfKey) -> ByteString -> Either DecoderError (VerificationKey VrfKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotKey) Source # | |||||
SerialiseAsCBOR (VerificationKey DRepExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey DRepKey) -> ByteString -> Either DecoderError (VerificationKey DRepKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey StakeExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey StakeKey) -> ByteString -> Either DecoderError (VerificationKey StakeKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) Source # | |||||
SerialiseAsRawBytes (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
SerialiseAsRawBytes (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey DRepExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey PaymentKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakeExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakeKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakePoolKey) Source # | |||||
HasTextEnvelope (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (VerificationKey ByronKeyLegacy) Source # | |||||
HasTextEnvelope (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
HasTextEnvelope (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeColdKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeHotKey) Source # | |||||
HasTextEnvelope (VerificationKey DRepExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisDelegateKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey GenesisUTxOKey) Source # | |||||
HasTextEnvelope (VerificationKey PaymentExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey StakeExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey StakePoolKey) Source # | |||||
FromCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (VerificationKey ByronKeyLegacy) Source # label :: Proxy (VerificationKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdExtendedKey) Source # label :: Proxy (VerificationKey CommitteeColdExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdKey) Source # label :: Proxy (VerificationKey CommitteeColdKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotExtendedKey) Source # label :: Proxy (VerificationKey CommitteeHotExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotKey) Source # label :: Proxy (VerificationKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey DRepExtendedKey) Source # label :: Proxy (VerificationKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateExtendedKey) Source # label :: Proxy (VerificationKey GenesisDelegateExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateKey) Source # label :: Proxy (VerificationKey GenesisDelegateKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisExtendedKey) Source # label :: Proxy (VerificationKey GenesisExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisKey) Source # label :: Proxy (VerificationKey GenesisKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisUTxOKey) Source # label :: Proxy (VerificationKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentExtendedKey) Source # label :: Proxy (VerificationKey PaymentExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentKey) Source # label :: Proxy (VerificationKey PaymentKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakeExtendedKey) Source # label :: Proxy (VerificationKey StakeExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolKey) Source # label :: Proxy (VerificationKey StakePoolKey) -> Text Source # | |||||
ToCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: VerificationKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size Source # | |||||
ToCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotKey] -> Size Source # | |||||
ToCBOR (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey DRepExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisUTxOKey] -> Size Source # | |||||
ToCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolKey] -> Size Source # | |||||
Eq (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # (/=) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # | |||||
Eq (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # (/=) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # | |||||
Eq (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # (/=) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # | |||||
Eq (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # (/=) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # | |||||
Eq (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Eq (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey CommitteeColdKey -> VerificationKey CommitteeColdKey -> Bool Source # (/=) :: VerificationKey CommitteeColdKey -> VerificationKey CommitteeColdKey -> Bool Source # | |||||
Eq (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Eq (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey CommitteeHotKey -> VerificationKey CommitteeHotKey -> Bool Source # (/=) :: VerificationKey CommitteeHotKey -> VerificationKey CommitteeHotKey -> Bool Source # | |||||
Eq (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey DRepExtendedKey -> VerificationKey DRepExtendedKey -> Bool Source # (/=) :: VerificationKey DRepExtendedKey -> VerificationKey DRepExtendedKey -> Bool Source # | |||||
Eq (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # (/=) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # | |||||
Eq (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Eq (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool Source # (/=) :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool Source # | |||||
Eq (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey -> Bool Source # (/=) :: VerificationKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey -> Bool Source # | |||||
Eq (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # (/=) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # | |||||
Eq (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # (/=) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # | |||||
Eq (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # (/=) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # | |||||
Eq (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # (/=) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # | |||||
newtype VerificationKey ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype VerificationKey ByronKeyLegacy Source # | |||||
newtype VerificationKey KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype VerificationKey VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype VerificationKey CommitteeColdExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeColdKey Source # | |||||
newtype VerificationKey CommitteeHotExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeHotKey Source # | |||||
newtype VerificationKey DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateKey Source # | |||||
newtype VerificationKey GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
data AsType (VerificationKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class |
data family SigningKey keyrole Source #
The type of cryptographic signing key, for each key role.
Instances
IsString (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> SigningKey ByronKey Source # | |||||
IsString (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||
IsString (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey KesKey Source # | |||||
IsString (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey VrfKey Source # | |||||
IsString (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeColdExtendedKey Source # | |||||
IsString (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeColdKey Source # | |||||
IsString (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeHotExtendedKey Source # | |||||
IsString (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey DRepKey Source # | |||||
IsString (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisDelegateExtendedKey Source # | |||||
IsString (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisDelegateKey Source # | |||||
IsString (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisExtendedKey Source # | |||||
IsString (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisKey Source # | |||||
IsString (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentExtendedKey Source # | |||||
IsString (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentKey Source # | |||||
IsString (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeExtendedKey Source # | |||||
IsString (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeKey Source # | |||||
IsString (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
Show (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> SigningKey ByronKeyLegacy -> ShowS Source # show :: SigningKey ByronKeyLegacy -> String Source # showList :: [SigningKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeColdExtendedKey -> ShowS Source # show :: SigningKey CommitteeColdExtendedKey -> String Source # showList :: [SigningKey CommitteeColdExtendedKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeColdKey -> ShowS Source # show :: SigningKey CommitteeColdKey -> String Source # showList :: [SigningKey CommitteeColdKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeHotExtendedKey -> ShowS Source # show :: SigningKey CommitteeHotExtendedKey -> String Source # showList :: [SigningKey CommitteeHotExtendedKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeHotKey -> ShowS Source # show :: SigningKey CommitteeHotKey -> String Source # showList :: [SigningKey CommitteeHotKey] -> ShowS Source # | |||||
Show (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey DRepExtendedKey -> ShowS Source # show :: SigningKey DRepExtendedKey -> String Source # showList :: [SigningKey DRepExtendedKey] -> ShowS Source # | |||||
Show (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisDelegateExtendedKey -> ShowS Source # show :: SigningKey GenesisDelegateExtendedKey -> String Source # showList :: [SigningKey GenesisDelegateExtendedKey] -> ShowS Source # | |||||
Show (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS Source # show :: SigningKey GenesisDelegateKey -> String Source # showList :: [SigningKey GenesisDelegateKey] -> ShowS Source # | |||||
Show (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS Source # show :: SigningKey GenesisExtendedKey -> String Source # showList :: [SigningKey GenesisExtendedKey] -> ShowS Source # | |||||
Show (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisKey -> ShowS Source # show :: SigningKey GenesisKey -> String Source # showList :: [SigningKey GenesisKey] -> ShowS Source # | |||||
Show (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS Source # show :: SigningKey GenesisUTxOKey -> String Source # showList :: [SigningKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS Source # show :: SigningKey PaymentExtendedKey -> String Source # showList :: [SigningKey PaymentExtendedKey] -> ShowS Source # | |||||
Show (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentKey -> ShowS Source # show :: SigningKey PaymentKey -> String Source # showList :: [SigningKey PaymentKey] -> ShowS Source # | |||||
Show (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS Source # show :: SigningKey StakeExtendedKey -> String Source # showList :: [SigningKey StakeExtendedKey] -> ShowS Source # | |||||
Show (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakePoolKey -> ShowS Source # show :: SigningKey StakePoolKey -> String Source # showList :: [SigningKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (SigningKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (SigningKey a) -> AsType (SigningKey a) Source # | |||||
SerialiseAsBech32 (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey KesKey -> Text bech32PrefixesPermitted :: AsType (SigningKey KesKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey VrfKey -> Text bech32PrefixesPermitted :: AsType (SigningKey VrfKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeColdExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeHotExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey DRepExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey DRepExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey DRepKey -> Text bech32PrefixesPermitted :: AsType (SigningKey DRepKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakePoolKey) -> [Text] | |||||
SerialiseAsCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKey) -> ByteString -> Either DecoderError (SigningKey ByronKey) Source # | |||||
SerialiseAsCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKeyLegacy) -> ByteString -> Either DecoderError (SigningKey ByronKeyLegacy) Source # | |||||
SerialiseAsCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey KesKey) -> ByteString -> Either DecoderError (SigningKey KesKey) Source # | |||||
SerialiseAsCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey VrfKey) -> ByteString -> Either DecoderError (SigningKey VrfKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey DRepKey) -> ByteString -> Either DecoderError (SigningKey DRepKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisKey) -> ByteString -> Either DecoderError (SigningKey GenesisKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey) -> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey) Source # | |||||
SerialiseAsCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey PaymentKey) -> ByteString -> Either DecoderError (SigningKey PaymentKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakeKey) -> ByteString -> Either DecoderError (SigningKey StakeKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakePoolKey) -> ByteString -> Either DecoderError (SigningKey StakePoolKey) Source # | |||||
SerialiseAsRawBytes (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (SigningKey ByronKeyLegacy) Source # | |||||
SerialiseAsRawBytes (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey KesKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey KesKey) Source # | |||||
SerialiseAsRawBytes (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey VrfKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotKey) Source # | |||||
SerialiseAsRawBytes (SigningKey DRepExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: SigningKey DRepKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey DRepKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey DRepKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey GenesisUTxOKey) Source # | |||||
SerialiseAsRawBytes (SigningKey PaymentExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey StakeExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey KesKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey KesKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey VrfKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey VrfKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey CommitteeColdExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeColdKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeHotExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods textEnvelopeType :: AsType (SigningKey DRepKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey DRepKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisDelegateKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey PaymentExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey StakeExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (SigningKey ByronKeyLegacy) Source # label :: Proxy (SigningKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdExtendedKey) Source # label :: Proxy (SigningKey CommitteeColdExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdKey) Source # label :: Proxy (SigningKey CommitteeColdKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotExtendedKey) Source # label :: Proxy (SigningKey CommitteeHotExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotKey) Source # label :: Proxy (SigningKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey DRepExtendedKey) Source # label :: Proxy (SigningKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateExtendedKey) Source # label :: Proxy (SigningKey GenesisDelegateExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateKey) Source # label :: Proxy (SigningKey GenesisDelegateKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisExtendedKey) Source # label :: Proxy (SigningKey GenesisExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisKey) Source # label :: Proxy (SigningKey GenesisKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisUTxOKey) Source # label :: Proxy (SigningKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentExtendedKey) Source # label :: Proxy (SigningKey PaymentExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentKey) Source # label :: Proxy (SigningKey PaymentKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakeExtendedKey) Source # label :: Proxy (SigningKey StakeExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolKey) Source # label :: Proxy (SigningKey StakePoolKey) -> Text Source # | |||||
ToCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: SigningKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size Source # | |||||
ToCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotKey] -> Size Source # | |||||
ToCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey DRepExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisUTxOKey] -> Size Source # | |||||
ToCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size Source # | |||||
ToCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolKey] -> Size Source # | |||||
newtype SigningKey ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype SigningKey ByronKeyLegacy Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype SigningKey KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype SigningKey VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype SigningKey CommitteeColdExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeHotExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
data AsType (SigningKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class |
Hashes
data family Hash keyrole Source #
Instances
FromJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods parseJSON :: Value -> Parser (Hash BlockHeader) parseJSONList :: Value -> Parser [Hash BlockHeader] omittedField :: Maybe (Hash BlockHeader) | |||||
FromJSON (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash DRepKey) parseJSONList :: Value -> Parser [Hash DRepKey] omittedField :: Maybe (Hash DRepKey) | |||||
FromJSON (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash GenesisKey) parseJSONList :: Value -> Parser [Hash GenesisKey] omittedField :: Maybe (Hash GenesisKey) | |||||
FromJSON (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash PaymentKey) parseJSONList :: Value -> Parser [Hash PaymentKey] omittedField :: Maybe (Hash PaymentKey) | |||||
FromJSON (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash StakePoolKey) parseJSONList :: Value -> Parser [Hash StakePoolKey] | |||||
FromJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods parseJSON :: Value -> Parser (Hash ScriptData) parseJSONList :: Value -> Parser [Hash ScriptData] omittedField :: Maybe (Hash ScriptData) | |||||
FromJSONKey (Hash ScriptData) | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromJSONKey :: FromJSONKeyFunction (Hash ScriptData) fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData] | |||||
ToJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods toJSON :: Hash BlockHeader -> Value toEncoding :: Hash BlockHeader -> Encoding toJSONList :: [Hash BlockHeader] -> Value toEncodingList :: [Hash BlockHeader] -> Encoding omitField :: Hash BlockHeader -> Bool | |||||
ToJSON (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToJSON (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash GenesisKey -> Value toEncoding :: Hash GenesisKey -> Encoding toJSONList :: [Hash GenesisKey] -> Value toEncodingList :: [Hash GenesisKey] -> Encoding omitField :: Hash GenesisKey -> Bool | |||||
ToJSON (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash PaymentKey -> Value toEncoding :: Hash PaymentKey -> Encoding toJSONList :: [Hash PaymentKey] -> Value toEncodingList :: [Hash PaymentKey] -> Encoding omitField :: Hash PaymentKey -> Bool | |||||
ToJSON (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash StakePoolKey -> Value toEncoding :: Hash StakePoolKey -> Encoding toJSONList :: [Hash StakePoolKey] -> Value toEncodingList :: [Hash StakePoolKey] -> Encoding omitField :: Hash StakePoolKey -> Bool | |||||
ToJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSON :: Hash ScriptData -> Value toEncoding :: Hash ScriptData -> Encoding toJSONList :: [Hash ScriptData] -> Value toEncodingList :: [Hash ScriptData] -> Encoding omitField :: Hash ScriptData -> Bool | |||||
ToJSONKey (Hash DRepKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToJSONKey (Hash GenesisKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash GenesisKey) toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey] | |||||
ToJSONKey (Hash PaymentKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash PaymentKey) toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey] | |||||
ToJSONKey (Hash StakePoolKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey] | |||||
ToJSONKey (Hash ScriptData) | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSONKey :: ToJSONKeyFunction (Hash ScriptData) toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData] | |||||
IsString (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods fromString :: String -> Hash BlockHeader Source # | |||||
IsString (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods fromString :: String -> Hash GovernancePoll Source # | |||||
IsString (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
IsString (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> Hash ByronKeyLegacy Source # | |||||
IsString (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
IsString (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
IsString (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeColdExtendedKey Source # | |||||
IsString (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeColdKey Source # | |||||
IsString (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeHotExtendedKey Source # | |||||
IsString (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeHotKey Source # | |||||
IsString (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash DRepExtendedKey Source # | |||||
IsString (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
IsString (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisDelegateExtendedKey Source # | |||||
IsString (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisKey Source # | |||||
IsString (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisUTxOKey Source # | |||||
IsString (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash PaymentKey Source # | |||||
IsString (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakeExtendedKey Source # | |||||
IsString (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
IsString (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakePoolKey Source # | |||||
IsString (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromString :: String -> Hash ScriptData Source # | |||||
Show (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block | |||||
Show (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
Show (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
Show (Hash ByronKey) Source # | |||||
Show (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (Hash KesKey) Source # | |||||
Show (Hash VrfKey) Source # | |||||
Show (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash DRepKey) Source # | |||||
Show (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakeKey) Source # | |||||
Show (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
Show (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
HasTypeProxy a => HasTypeProxy (Hash a) Source # | |||||
Defined in Cardano.Api.Internal.Hash Associated Types
| |||||
SerialiseAsBech32 (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash DRepKey -> Text bech32PrefixesPermitted :: AsType (Hash DRepKey) -> [Text] | |||||
SerialiseAsBech32 (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash StakePoolKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text] | |||||
SerialiseAsCBOR (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKey) -> ByteString -> Either DecoderError (Hash ByronKey) Source # | |||||
SerialiseAsCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKeyLegacy) -> ByteString -> Either DecoderError (Hash ByronKeyLegacy) Source # | |||||
SerialiseAsCBOR (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash KesKey) -> ByteString -> Either DecoderError (Hash KesKey) Source # | |||||
SerialiseAsCBOR (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash VrfKey) -> ByteString -> Either DecoderError (Hash VrfKey) Source # | |||||
SerialiseAsCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeColdKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeColdKey) -> ByteString -> Either DecoderError (Hash CommitteeColdKey) Source # | |||||
SerialiseAsCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeHotKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeHotKey) -> ByteString -> Either DecoderError (Hash CommitteeHotKey) Source # | |||||
SerialiseAsCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepExtendedKey) -> ByteString -> Either DecoderError (Hash DRepExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepKey) -> ByteString -> Either DecoderError (Hash DRepKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisDelegateKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisDelegateKey) -> ByteString -> Either DecoderError (Hash GenesisDelegateKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisExtendedKey) -> ByteString -> Either DecoderError (Hash GenesisExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisKey) -> ByteString -> Either DecoderError (Hash GenesisKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisUTxOKey) -> ByteString -> Either DecoderError (Hash GenesisUTxOKey) Source # | |||||
SerialiseAsCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentExtendedKey) -> ByteString -> Either DecoderError (Hash PaymentExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentKey) -> ByteString -> Either DecoderError (Hash PaymentKey) Source # | |||||
SerialiseAsCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeExtendedKey) -> ByteString -> Either DecoderError (Hash StakeExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeKey) -> ByteString -> Either DecoderError (Hash StakeKey) Source # | |||||
SerialiseAsCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakePoolKey) -> ByteString -> Either DecoderError (Hash StakePoolKey) Source # | |||||
SerialiseAsRawBytes (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods serialiseToRawBytes :: Hash BlockHeader -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash BlockHeader) -> ByteString -> Either SerialiseAsRawBytesError (Hash BlockHeader) Source # | |||||
SerialiseAsRawBytes (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods serialiseToRawBytes :: Hash DRepMetadata -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepMetadata) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepMetadata) Source # | |||||
SerialiseAsRawBytes (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
SerialiseAsRawBytes (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToRawBytes :: Hash ByronKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ByronKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash ByronKey) Source # | |||||
SerialiseAsRawBytes (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash KesKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash KesKey) Source # | |||||
SerialiseAsRawBytes (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash VrfKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash DRepKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash GenesisKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash GenesisKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash GenesisKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash PaymentKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash PaymentKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash PaymentKey) Source # | |||||
SerialiseAsRawBytes (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakeKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakeKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakeKey) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakePoolKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakePoolKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakePoolKey) Source # | |||||
SerialiseAsRawBytes (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods serialiseToRawBytes :: Hash ScriptData -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ScriptData) -> ByteString -> Either SerialiseAsRawBytesError (Hash ScriptData) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolMetadata) Source # | |||||
FromCBOR (Hash ByronKey) Source # | |||||
FromCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (Hash KesKey) Source # | |||||
FromCBOR (Hash VrfKey) Source # | |||||
FromCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash DRepKey) Source # | |||||
FromCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash StakeKey) Source # | |||||
FromCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash ByronKey) Source # | |||||
ToCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (Hash KesKey) Source # | |||||
ToCBOR (Hash VrfKey) Source # | |||||
ToCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash DRepKey) Source # | |||||
ToCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods (==) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (/=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # | |||||
Eq (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods (==) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # (/=) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # | |||||
Eq (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods (==) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (/=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # | |||||
Eq (Hash ByronKey) Source # | |||||
Eq (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (/=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # | |||||
Eq (Hash KesKey) Source # | |||||
Eq (Hash VrfKey) Source # | |||||
Eq (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (/=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # | |||||
Eq (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (/=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # | |||||
Eq (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (/=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # | |||||
Eq (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (/=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # | |||||
Eq (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (/=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # | |||||
Eq (Hash DRepKey) Source # | |||||
Eq (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (/=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # | |||||
Eq (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (/=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # | |||||
Eq (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (/=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # | |||||
Eq (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (/=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # | |||||
Eq (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (/=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # | |||||
Eq (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (/=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # | |||||
Eq (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (/=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # | |||||
Eq (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (/=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # | |||||
Eq (Hash StakeKey) Source # | |||||
Eq (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (/=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # | |||||
Eq (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (/=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # | |||||
Eq (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods (==) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # (/=) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # | |||||
Ord (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods compare :: Hash BlockHeader -> Hash BlockHeader -> Ordering Source # (<) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (<=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # max :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # min :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # | |||||
Ord (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods compare :: Hash GovernancePoll -> Hash GovernancePoll -> Ordering Source # (<) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (<=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # max :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # min :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # | |||||
Ord (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKey -> Hash ByronKey -> Ordering Source # (<) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (<=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # max :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # min :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # | |||||
Ord (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Ordering Source # (<) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (<=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # max :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # min :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # | |||||
Ord (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash KesKey -> Hash KesKey -> Ordering Source # (<) :: Hash KesKey -> Hash KesKey -> Bool Source # (<=) :: Hash KesKey -> Hash KesKey -> Bool Source # (>) :: Hash KesKey -> Hash KesKey -> Bool Source # (>=) :: Hash KesKey -> Hash KesKey -> Bool Source # | |||||
Ord (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash VrfKey -> Hash VrfKey -> Ordering Source # (<) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (<=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # | |||||
Ord (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Ordering Source # (<) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (<=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (>) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (>=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # max :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # min :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # | |||||
Ord (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Ordering Source # (<) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (<=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (>) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (>=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # max :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Hash CommitteeColdKey Source # min :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Hash CommitteeColdKey Source # | |||||
Ord (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Ordering Source # (<) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (<=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (>) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (>=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # max :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # min :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # | |||||
Ord (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Ordering Source # (<) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (<=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (>) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (>=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # max :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Hash CommitteeHotKey Source # min :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Hash CommitteeHotKey Source # | |||||
Ord (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Ordering Source # (<) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (<=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (>) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (>=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # max :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Hash DRepExtendedKey Source # min :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Hash DRepExtendedKey Source # | |||||
Ord (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash DRepKey -> Hash DRepKey -> Ordering Source # (<) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (<=) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (>) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (>=) :: Hash DRepKey -> Hash DRepKey -> Bool Source # max :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey Source # min :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey Source # | |||||
Ord (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Ordering Source # (<) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (<=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (>) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (>=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # max :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # min :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # | |||||
Ord (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering Source # (<) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (<=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (>) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (>=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # max :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey Source # min :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey Source # | |||||
Ord (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering Source # (<) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (<=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (>) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (>=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # max :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey Source # min :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey Source # | |||||
Ord (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisKey -> Hash GenesisKey -> Ordering Source # (<) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (<=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (>) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (>=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # max :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey Source # min :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey Source # | |||||
Ord (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering Source # (<) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (<=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (>) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (>=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # max :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey Source # min :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey Source # | |||||
Ord (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering Source # (<) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (<=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # max :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # min :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # | |||||
Ord (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentKey -> Hash PaymentKey -> Ordering Source # (<) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (<=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # max :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # min :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # | |||||
Ord (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering Source # (<) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (<=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # max :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # min :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # | |||||
Ord (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeKey -> Hash StakeKey -> Ordering Source # (<) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (<=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # max :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # min :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # | |||||
Ord (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering Source # (<) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (<=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # max :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # min :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # | |||||
Ord (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods compare :: Hash ScriptData -> Hash ScriptData -> Ordering Source # (<) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (<=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # max :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # min :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # | |||||
newtype Hash BlockHeader Source # | For now at least we use a fixed concrete hash type for all modes and era. The different eras do use different types, but it's all the same underlying representation. | ||||
Defined in Cardano.Api.Internal.Block | |||||
newtype Hash DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
newtype Hash GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
newtype Hash ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype Hash ByronKeyLegacy Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype Hash KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype Hash VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype Hash CommitteeColdExtendedKey Source # | |||||
newtype Hash CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash CommitteeHotExtendedKey Source # | |||||
newtype Hash CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisDelegateExtendedKey Source # | |||||
newtype Hash GenesisDelegateKey Source # | |||||
newtype Hash GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
newtype Hash StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
data AsType (Hash a) Source # | |||||
Defined in Cardano.Api.Internal.Hash |
Type Proxies
A family of singleton types used in this API to indicate which type to use where it would otherwise be ambiguous or merely unclear.
Values of this type are passed to deserialisation functions for example.
Instances
data AsType AddressAny Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType ByronAddr Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType ShelleyAddr Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType StakeAddress Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType BlockHeader Source # | |
Defined in Cardano.Api.Internal.Block | |
data AsType DRepMetadata Source # | |
Defined in Cardano.Api.Internal.DRepMetadata | |
data AsType AllegraEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType ByronEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType MaryEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType ShelleyEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType GovernancePoll Source # | |
Defined in Cardano.Api.Internal.Governance.Poll | |
data AsType GovernancePollAnswer Source # | |
Defined in Cardano.Api.Internal.Governance.Poll | |
data AsType ByronKey Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
data AsType ByronKeyLegacy Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
data AsType KesKey Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
data AsType VrfKey Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
data AsType CommitteeColdExtendedKey Source # | |
data AsType CommitteeColdKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType CommitteeHotExtendedKey Source # | |
data AsType CommitteeHotKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType DRepExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType DRepKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisDelegateExtendedKey Source # | |
data AsType GenesisDelegateKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisUTxOKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType PaymentExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType PaymentKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType StakeExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType StakeKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType StakePoolKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType OperationalCertificate Source # | |
data AsType OperationalCertificateIssueCounter Source # | |
data AsType PraosNonce Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
data AsType UpdateProposal Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
data AsType PlutusScriptV1 Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType PlutusScriptV2 Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType PlutusScriptV3 Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType ScriptHash Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType ScriptInAnyLang Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType SimpleScript' Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType HashableScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
data AsType ScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
data AsType TextEnvelope Source # | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope | |
data AsType ByronUpdateProposal Source # | |
Defined in Cardano.Api.Internal.SpecialByron | |
data AsType ByronVote Source # | |
Defined in Cardano.Api.Internal.SpecialByron | |
data AsType StakePoolMetadata Source # | |
Defined in Cardano.Api.Internal.StakePoolMetadata | |
data AsType TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
data AsType TxMetadata Source # | |
Defined in Cardano.Api.Internal.TxMetadata | |
data AsType AssetName Source # | |
Defined in Cardano.Api.Internal.Value | |
data AsType PolicyId Source # | |
Defined in Cardano.Api.Internal.Value | |
data AsType (Address addrtype) Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType (AddressInEra era) Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType (Certificate era) Source # | |
Defined in Cardano.Api.Internal.Certificate | |
data AsType (Proposal era) Source # | |
data AsType (VotingProcedure era) Source # | |
data AsType (VotingProcedures era) Source # | |
data AsType (Hash a) Source # | |
Defined in Cardano.Api.Internal.Hash | |
data AsType (SigningKey a) Source # | |
Defined in Cardano.Api.Internal.Keys.Class | |
data AsType (VerificationKey a) Source # | |
Defined in Cardano.Api.Internal.Keys.Class | |
data AsType (PlutusScript lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType (Script lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType (ScriptInEra era) Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType (KeyWitness era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
data AsType (Tx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
data AsType (TxBody era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
data AsType (PlutusScriptInEra era lang) Source # | |
Defined in Cardano.Api.Internal.Script |
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.
Constructors
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
FromJSON (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
FromJSON (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods parseJSON :: Value -> Parser (Address ShelleyAddr) parseJSONList :: Value -> Parser [Address ShelleyAddr] | |||||
ToJSON (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
ToJSON (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods toJSON :: Address ShelleyAddr -> Value toEncoding :: Address ShelleyAddr -> Encoding toJSONList :: [Address ShelleyAddr] -> Value toEncodingList :: [Address ShelleyAddr] -> Encoding omitField :: Address ShelleyAddr -> Bool | |||||
Show (Address addrtype) Source # | |||||
SerialiseAddress (Address ByronAddr) Source # | |||||
SerialiseAddress (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseAddress :: Address ShelleyAddr -> Text Source # deserialiseAddress :: AsType (Address ShelleyAddr) -> Text -> Maybe (Address ShelleyAddr) Source # | |||||
HasTypeProxy addrtype => HasTypeProxy (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
| |||||
SerialiseAsBech32 (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods bech32PrefixFor :: Address ShelleyAddr -> Text bech32PrefixesPermitted :: AsType (Address ShelleyAddr) -> [Text] | |||||
SerialiseAsRawBytes (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseToRawBytes :: Address ByronAddr -> ByteString Source # deserialiseFromRawBytes :: AsType (Address ByronAddr) -> ByteString -> Either SerialiseAsRawBytesError (Address ByronAddr) Source # | |||||
SerialiseAsRawBytes (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
NFData (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
Eq (Address addrtype) Source # | |||||
Ord (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods compare :: Address addrtype -> Address addrtype -> Ordering Source # (<) :: Address addrtype -> Address addrtype -> Bool Source # (<=) :: Address addrtype -> Address addrtype -> Bool Source # (>) :: Address addrtype -> Address addrtype -> Bool Source # (>=) :: Address addrtype -> Address addrtype -> Bool Source # max :: Address addrtype -> Address addrtype -> Address addrtype Source # min :: Address addrtype -> Address addrtype -> Address addrtype Source # | |||||
data AsType (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address |
toShelleyAddr :: AddressInEra era -> Addr StandardCrypto Source #
fromShelleyAddr :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era Source #
fromShelleyAddrIsSbe :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era Source #
Stake addresses
data PaymentCredential Source #
Constructors
PaymentCredentialByKey (Hash PaymentKey) | |
PaymentCredentialByScript ScriptHash |
Instances
Show PaymentCredential Source # | |
Defined in Cardano.Api.Internal.Address | |
Eq PaymentCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods (==) :: PaymentCredential -> PaymentCredential -> Bool Source # (/=) :: PaymentCredential -> PaymentCredential -> Bool Source # | |
Ord PaymentCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods 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 # |
data StakeAddress where Source #
Constructors
StakeAddress :: Network -> StakeCredential StandardCrypto -> StakeAddress |
Instances
FromJSON StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
ToJSON StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods toJSON :: StakeAddress -> Value toEncoding :: StakeAddress -> Encoding toJSONList :: [StakeAddress] -> Value toEncodingList :: [StakeAddress] -> Encoding omitField :: StakeAddress -> Bool | |||||
Show StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
SerialiseAddress StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseAddress :: StakeAddress -> Text Source # deserialiseAddress :: AsType StakeAddress -> Text -> Maybe StakeAddress Source # | |||||
HasTypeProxy StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy StakeAddress -> AsType StakeAddress Source # | |||||
SerialiseAsBech32 StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods bech32PrefixFor :: StakeAddress -> Text | |||||
SerialiseAsRawBytes StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
Eq StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods (==) :: StakeAddress -> StakeAddress -> Bool Source # (/=) :: StakeAddress -> StakeAddress -> Bool Source # | |||||
Ord StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods compare :: StakeAddress -> StakeAddress -> Ordering Source # (<) :: StakeAddress -> StakeAddress -> Bool Source # (<=) :: StakeAddress -> StakeAddress -> Bool Source # (>) :: StakeAddress -> StakeAddress -> Bool Source # (>=) :: StakeAddress -> StakeAddress -> Bool Source # max :: StakeAddress -> StakeAddress -> StakeAddress Source # min :: StakeAddress -> StakeAddress -> StakeAddress Source # | |||||
data AsType StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address |
data StakeAddressReference Source #
Constructors
StakeAddressByValue StakeCredential | |
StakeAddressByPointer StakeAddressPointer | |
NoStakeAddress |
Instances
Show StakeAddressReference Source # | |
Defined in Cardano.Api.Internal.Address | |
Eq StakeAddressReference Source # | |
Defined in Cardano.Api.Internal.Address Methods (==) :: StakeAddressReference -> StakeAddressReference -> Bool Source # (/=) :: StakeAddressReference -> StakeAddressReference -> Bool Source # |
data StakeCredential Source #
Constructors
StakeCredentialByKey (Hash StakeKey) | |
StakeCredentialByScript ScriptHash |
Instances
ToJSON StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods toJSON :: StakeCredential -> Value toEncoding :: StakeCredential -> Encoding toJSONList :: [StakeCredential] -> Value toEncodingList :: [StakeCredential] -> Encoding omitField :: StakeCredential -> Bool | |
Show StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address | |
Eq StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods (==) :: StakeCredential -> StakeCredential -> Bool Source # (/=) :: StakeCredential -> StakeCredential -> Bool Source # | |
Ord StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods compare :: StakeCredential -> StakeCredential -> Ordering Source # (<) :: StakeCredential -> StakeCredential -> Bool Source # (<=) :: StakeCredential -> StakeCredential -> Bool Source # (>) :: StakeCredential -> StakeCredential -> Bool Source # (>=) :: StakeCredential -> StakeCredential -> Bool Source # max :: StakeCredential -> StakeCredential -> StakeCredential Source # min :: StakeCredential -> StakeCredential -> StakeCredential Source # |
Building transactions
Constructing and inspecting transactions
data TxBody era where Source #
Constructors
ShelleyTxBody | |
Fields
|
Instances
Show (TxBody era) Source # | |||||
HasTypeProxy era => HasTypeProxy (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
| |||||
IsShelleyBasedEra era => SerialiseAsCBOR (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods serialiseToCBOR :: TxBody era -> ByteString Source # deserialiseFromCBOR :: AsType (TxBody era) -> ByteString -> Either DecoderError (TxBody era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods textEnvelopeType :: AsType (TxBody era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: TxBody era -> TextEnvelopeDescr Source # | |||||
Eq (TxBody era) Source # | |||||
data AsType (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign |
Constructors
TxId (Hash StandardCrypto EraIndependentTxBody) |
Instances
FromJSON TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSONKey TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxId -> Encoding toJSONList :: [TxId] -> Value toEncodingList :: [TxId] -> Encoding | |
ToJSONKey TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
IsString TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods fromString :: String -> TxId Source # | |
Show TxId Source # | |
HasTypeProxy TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
SerialiseAsRawBytes TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods serialiseToRawBytes :: TxId -> ByteString Source # deserialiseFromRawBytes :: AsType TxId -> ByteString -> Either SerialiseAsRawBytesError TxId Source # | |
Eq TxId Source # | |
Ord TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
data AsType TxId Source # | |
Defined in Cardano.Api.Internal.TxIn |
toShelleyTxId :: TxId -> TxId StandardCrypto Source #
fromShelleyTxId :: TxId StandardCrypto -> TxId Source #
getTxIdShelley :: (EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto, EraTxBody (ShelleyLedgerEra era)) => ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> TxId Source #
Instances
FromJSON TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSONKey TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxIn -> Encoding toJSONList :: [TxIn] -> Value toEncodingList :: [TxIn] -> Encoding | |
ToJSONKey TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
Show TxIn Source # | |
Eq TxIn Source # | |
Ord TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
Pretty TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn |
toShelleyTxIn :: TxIn -> TxIn StandardCrypto Source #
This function may overflow on the transaction index. Call sites must ensure that all uses of this function are appropriately guarded.
fromShelleyTxIn :: TxIn StandardCrypto -> TxIn Source #
Constructors
TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) (ReferenceScript era) |
Instances
IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods parseJSON :: Value -> Parser (TxOut CtxTx era) parseJSONList :: Value -> Parser [TxOut CtxTx era] omittedField :: Maybe (TxOut CtxTx era) | |
IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods parseJSON :: Value -> Parser (TxOut CtxUTxO era) parseJSONList :: Value -> Parser [TxOut CtxUTxO era] omittedField :: Maybe (TxOut CtxUTxO era) | |
IsCardanoEra era => ToJSON (TxOut ctx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods toJSON :: TxOut ctx era -> Value toEncoding :: TxOut ctx era -> Encoding toJSONList :: [TxOut ctx era] -> Value toEncodingList :: [TxOut ctx era] -> Encoding | |
Show (TxOut ctx era) Source # | |
Eq (TxOut ctx era) Source # | |
toShelleyTxOut :: (HasCallStack, ShelleyLedgerEra era ~ ledgerera) => ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera Source #
fromShelleyTxOut :: ShelleyBasedEra era -> TxOut (ShelleyLedgerEra era) -> TxOut ctx era Source #
Instances
FromJSON TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxIx -> Encoding toJSONList :: [TxIx] -> Value toEncodingList :: [TxIx] -> Encoding | |
Enum TxIx Source # | |
Show TxIx Source # | |
Eq TxIx Source # | |
Ord TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn |
calcMinimumDeposit :: Value -> Lovelace -> Lovelace Source #
Calculate cost of making a UTxO entry for a given Value
and
mininimum UTxO value derived from the ProtocolParameters
Arbitrary signing
signArbitraryBytesKes Source #
Arguments
:: SigningKey KesKey | |
-> Period | Desired Kes period |
-> ByteString | Message to sign |
-> SignedKES (KES StandardCrypto) ByteString |
Signing transactions
Creating transaction witnesses one by one, or all in one go.
Constructors
ShelleyTx :: forall era. ShelleyBasedEra era -> Tx (ShelleyLedgerEra era) -> Tx era |
Instances
Show (InAnyShelleyBasedEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign | |||||
Show (InAnyCardanoEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign | |||||
Show (Tx era) Source # | |||||
HasTypeProxy era => HasTypeProxy (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
| |||||
IsShelleyBasedEra era => SerialiseAsCBOR (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods serialiseToCBOR :: Tx era -> ByteString Source # deserialiseFromCBOR :: AsType (Tx era) -> ByteString -> Either DecoderError (Tx era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods textEnvelopeType :: AsType (Tx era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Tx era -> TextEnvelopeDescr Source # | |||||
Eq (InAnyShelleyBasedEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # (/=) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # | |||||
Eq (InAnyCardanoEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # (/=) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # | |||||
Eq (Tx era) Source # | |||||
data AsType (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign |
Incremental signing and separate witnesses
data KeyWitness era where Source #
Constructors
ShelleyBootstrapWitness :: forall era. ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era | |
ShelleyKeyWitness :: forall era. ShelleyBasedEra era -> WitVKey 'Witness StandardCrypto -> KeyWitness era |
Instances
Show (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign | |||||
HasTypeProxy era => HasTypeProxy (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
Methods proxyToAsType :: Proxy (KeyWitness era) -> AsType (KeyWitness era) Source # | |||||
IsCardanoEra era => SerialiseAsCBOR (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods serialiseToCBOR :: KeyWitness era -> ByteString Source # deserialiseFromCBOR :: AsType (KeyWitness era) -> ByteString -> Either DecoderError (KeyWitness era) Source # | |||||
IsCardanoEra era => HasTextEnvelope (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods textEnvelopeType :: AsType (KeyWitness era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: KeyWitness era -> TextEnvelopeDescr Source # | |||||
Eq (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: KeyWitness era -> KeyWitness era -> Bool Source # (/=) :: KeyWitness era -> KeyWitness era -> Bool Source # | |||||
data AsType (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign |
data ShelleyWitnessSigningKey Source #
Constructors
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 Source #
We support making key witnesses with both normal and extended signing keys.
Constructors
ShelleyNormalSigningKey (SignKeyDSIGN StandardCrypto) | A normal ed25519 signing key |
ShelleyExtendedSigningKey XPrv | An extended ed25519 signing key |
getTxBodyAndWitnesses :: Tx era -> (TxBody era, [KeyWitness era]) Source #
makeShelleySignature :: SignableRepresentation tosign => tosign -> ShelleySigningKey -> SignedDSIGN StandardCrypto tosign Source #
Blocks
fromConsensusBlock :: CardanoBlock StandardCrypto ~ block => block -> BlockInMode Source #
toConsensusBlock :: CardanoBlock StandardCrypto ~ block => BlockInMode -> block Source #
fromConsensusTip :: CardanoBlock StandardCrypto ~ block => Tip block -> ChainTip Source #
fromConsensusPointHF :: forall block (xs :: [Type]). HeaderHash block ~ OneEraHash xs => Point block -> ChainPoint Source #
Convert a Point
for multi-era block type
toConsensusPointHF :: forall block (xs :: [Type]). HeaderHash block ~ OneEraHash xs => ChainPoint -> Point block Source #
Convert a Point
for multi-era block type
Transaction metadata
Embedding additional structured data within transactions.
Protocol parameters
newtype LedgerProtocolParameters era Source #
Constructors
LedgerProtocolParameters | |
Fields |
Instances
IsShelleyBasedEra era => Show (LedgerProtocolParameters era) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
IsShelleyBasedEra era => Eq (LedgerProtocolParameters era) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods (==) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # (/=) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # |
data EraBasedProtocolParametersUpdate era where Source #
Each constructor corresponds to the set of protocol parameters available in a given era.
Constructors
ShelleyEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams ShelleyEra -> DeprecatedAfterBabbagePParams ShelleyEra -> ShelleyToAlonzoPParams ShelleyEra -> EraBasedProtocolParametersUpdate ShelleyEra | |
AllegraEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams AllegraEra -> ShelleyToAlonzoPParams AllegraEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate AllegraEra | |
MaryEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams MaryEra -> ShelleyToAlonzoPParams MaryEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate MaryEra | |
AlonzoEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> ShelleyToAlonzoPParams AlonzoEra -> AlonzoOnwardsPParams AlonzoEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate AlonzoEra | |
BabbageEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> AlonzoOnwardsPParams BabbageEra -> DeprecatedAfterBabbagePParams ShelleyEra -> IntroducedInBabbagePParams BabbageEra -> EraBasedProtocolParametersUpdate BabbageEra | |
ConwayEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> AlonzoOnwardsPParams ConwayEra -> IntroducedInBabbagePParams ConwayEra -> IntroducedInConwayPParams (ShelleyLedgerEra ConwayEra) -> EraBasedProtocolParametersUpdate ConwayEra |
Instances
Show (EraBasedProtocolParametersUpdate era) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters |
data CommonProtocolParametersUpdate Source #
Protocol parameters common to each era. This can only ever be reduced if parameters are deprecated.
Constructors
CommonProtocolParametersUpdate | |
Fields
|
Instances
data AlonzoOnwardsPParams ledgerera Source #
Constructors
AlonzoOnwardsPParams | |
Instances
Show (AlonzoOnwardsPParams ledgerera) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters |
newtype DeprecatedAfterBabbagePParams ledgerera Source #
Constructors
DeprecatedAfterBabbagePParams (StrictMaybe ProtVer) |
Instances
Show (DeprecatedAfterBabbagePParams ledgerera) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters |
newtype DeprecatedAfterMaryPParams ledgerera Source #
Constructors
DeprecatedAfterMaryPParams (StrictMaybe Coin) |
Instances
Show (DeprecatedAfterMaryPParams ledgerera) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters |
data ShelleyToAlonzoPParams ledgerera Source #
Constructors
ShelleyToAlonzoPParams | |
Fields
|
Instances
Show (ShelleyToAlonzoPParams ledgerera) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters |
newtype IntroducedInBabbagePParams era Source #
Constructors
IntroducedInBabbagePParams (StrictMaybe CoinPerByte) | Coins per UTxO byte |
Instances
Show (IntroducedInBabbagePParams era) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters |
data IntroducedInConwayPParams era Source #
Constructors
IntroducedInConwayPParams | |
Fields
|
Instances
Show (IntroducedInConwayPParams era) Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters |
createEraBasedProtocolParamUpdate :: ShelleyBasedEra era -> EraBasedProtocolParametersUpdate era -> PParamsUpdate (ShelleyLedgerEra era) Source #
convertToLedgerProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersConversionError (LedgerProtocolParameters era) Source #
Deprecated: Use the ledger's PParams (from module Cardano.Api.Ledger) type instead of ProtocolParameters. The type will be removed after Chang hard fork.
data ProtocolParameters Source #
Deprecated: Use the ledger's PParams (from module Cardano.Api.Ledger) type instead of ProtocolParameters. The type will be removed after Chang hard fork.
The values of the set of updatable protocol parameters. At any particular point on the chain there is a current set of parameters in use.
These parameters can be updated (at epoch boundaries) via an
UpdateProposal
, which contains a ProtocolParametersUpdate
.
The ProtocolParametersUpdate
is essentially a diff for the
ProtocolParameters
.
There are also parameters fixed in the Genesis file. See GenesisParameters
.
Constructors
ProtocolParameters | Deprecated: Use the ledger's PParams (from module Cardano.Api.Ledger) type instead of ProtocolParameters. The type will be removed after Chang hard fork. |
Fields
|
Instances
FromJSON ProtocolParameters Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Methods parseJSON :: Value -> Parser ProtocolParameters parseJSONList :: Value -> Parser [ProtocolParameters] | |||||
ToJSON ProtocolParameters Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Methods toJSON :: ProtocolParameters -> Value toEncoding :: ProtocolParameters -> Encoding toJSONList :: [ProtocolParameters] -> Value toEncodingList :: [ProtocolParameters] -> Encoding omitField :: ProtocolParameters -> Bool | |||||
Generic ProtocolParameters Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Associated Types
Methods from :: ProtocolParameters -> Rep ProtocolParameters x Source # to :: Rep ProtocolParameters x -> ProtocolParameters Source # | |||||
Show ProtocolParameters Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters | |||||
Eq ProtocolParameters Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Methods (==) :: ProtocolParameters -> ProtocolParameters -> Bool Source # (/=) :: ProtocolParameters -> ProtocolParameters -> Bool Source # | |||||
type Rep ProtocolParameters Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters type Rep ProtocolParameters = D1 ('MetaData "ProtocolParameters" "Cardano.Api.Internal.ProtocolParameters" "cardano-api-10.9.0.0-inplace" 'False) (C1 ('MetaCons "ProtocolParameters" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "protocolParamProtocolVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Natural, Natural)) :*: (S1 ('MetaSel ('Just "protocolParamDecentralization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Rational)) :*: S1 ('MetaSel ('Just "protocolParamExtraPraosEntropy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PraosNonce)))) :*: (S1 ('MetaSel ('Just "protocolParamMaxBlockHeaderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: (S1 ('MetaSel ('Just "protocolParamMaxBlockBodySize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "protocolParamMaxTxSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))) :*: ((S1 ('MetaSel ('Just "protocolParamTxFeeFixed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: (S1 ('MetaSel ('Just "protocolParamTxFeePerByte") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: S1 ('MetaSel ('Just "protocolParamMinUTxOValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Coin)))) :*: (S1 ('MetaSel ('Just "protocolParamStakeAddressDeposit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: (S1 ('MetaSel ('Just "protocolParamStakePoolDeposit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: S1 ('MetaSel ('Just "protocolParamMinPoolCost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin))))) :*: (((S1 ('MetaSel ('Just "protocolParamPoolRetireMaxEpoch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochInterval) :*: (S1 ('MetaSel ('Just "protocolParamStakePoolTargetNum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16) :*: S1 ('MetaSel ('Just "protocolParamPoolPledgeInfluence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :*: (S1 ('MetaSel ('Just "protocolParamMonetaryExpansion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: (S1 ('MetaSel ('Just "protocolParamTreasuryCut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: S1 ('MetaSel ('Just "protocolParamCostModels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AnyPlutusScriptVersion CostModel))))) :*: ((S1 ('MetaSel ('Just "protocolParamPrices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExecutionUnitPrices)) :*: (S1 ('MetaSel ('Just "protocolParamMaxTxExUnits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExecutionUnits)) :*: S1 ('MetaSel ('Just "protocolParamMaxBlockExUnits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExecutionUnits)))) :*: ((S1 ('MetaSel ('Just "protocolParamMaxValueSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "protocolParamCollateralPercent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural))) :*: (S1 ('MetaSel ('Just "protocolParamMaxCollateralInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "protocolParamUTxOCostPerByte") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Coin)))))))) |
checkProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersError () Source #
Deprecated: Use the ledger's PParams (from module Cardano.Api.Ledger) type instead of ProtocolParameters. The type will be removed after Chang hard fork. PParams natively enforce these checks.
data ProtocolParametersError Source #
Constructors
PParamsErrorMissingMinUTxoValue !AnyCardanoEra | |
PParamsErrorMissingAlonzoProtocolParameter |
Instances
Show ProtocolParametersError Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
Error ProtocolParametersError Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods prettyError :: ProtocolParametersError -> Doc ann Source # |
Scripts
fromShelleyBasedScript :: ShelleyBasedEra era -> Script (ShelleyLedgerEra era) -> ScriptInEra era Source #
toShelleyScript :: ScriptInEra era -> Script (ShelleyLedgerEra era) Source #
toShelleyMultiSig :: SimpleScript -> Either MultiSigError (MultiSig (ShelleyLedgerEra ShelleyEra)) Source #
Conversion for the MultiSig
language used by the Shelley era.
fromShelleyMultiSig :: MultiSig (ShelleyLedgerEra ShelleyEra) -> SimpleScript Source #
Conversion for the MultiSig
language used by the Shelley era.
toAllegraTimelock :: (AllegraEraScript era, EraCrypto era ~ StandardCrypto, NativeScript era ~ Timelock era) => SimpleScript -> NativeScript era Source #
Conversion for the Timelock
language that is shared between the
Allegra and Mary eras.
fromAllegraTimelock :: (AllegraEraScript era, EraCrypto era ~ StandardCrypto) => NativeScript era -> SimpleScript Source #
Conversion for the Timelock
language that is shared between the
Allegra and Mary eras.
data PlutusScript lang where Source #
Plutus scripts.
Note that Plutus scripts have a binary serialisation but no JSON serialisation.
Constructors
PlutusScriptSerialised :: forall lang. ShortByteString -> PlutusScript lang |
Instances
Show (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasTypeProxy lang => HasTypeProxy (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (PlutusScript lang) -> AsType (PlutusScript lang) Source # | |||||
HasTypeProxy lang => SerialiseAsCBOR (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToCBOR :: PlutusScript lang -> ByteString Source # deserialiseFromCBOR :: AsType (PlutusScript lang) -> ByteString -> Either DecoderError (PlutusScript lang) Source # | |||||
HasTypeProxy lang => SerialiseAsRawBytes (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToRawBytes :: PlutusScript lang -> ByteString Source # deserialiseFromRawBytes :: AsType (PlutusScript lang) -> ByteString -> Either SerialiseAsRawBytesError (PlutusScript lang) Source # | |||||
IsPlutusScriptLanguage lang => HasTextEnvelope (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods textEnvelopeType :: AsType (PlutusScript lang) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: PlutusScript lang -> TextEnvelopeDescr Source # | |||||
Eq (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (/=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # | |||||
Ord (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods compare :: PlutusScript lang -> PlutusScript lang -> Ordering Source # (<) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (<=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (>) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (>=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # max :: PlutusScript lang -> PlutusScript lang -> PlutusScript lang Source # min :: PlutusScript lang -> PlutusScript lang -> PlutusScript lang Source # | |||||
data AsType (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script |
data PlutusScriptOrReferenceInput lang Source #
Scripts can now exist in the UTxO at a transaction output. We can reference these scripts via specification of a reference transaction input in order to witness spending inputs, withdrawals, certificates or to mint tokens. This datatype encapsulates this concept.
Constructors
PScript (PlutusScript lang) | |
PReferenceScript TxIn |
Instances
Show (PlutusScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (PlutusScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # (/=) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # |
data SimpleScriptOrReferenceInput lang Source #
Constructors
SScript SimpleScript | |
SReferenceScript TxIn |
Instances
Show (SimpleScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (SimpleScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # (/=) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # |
toPlutusData :: ScriptData -> Data Source #
fromPlutusData :: Data -> ScriptData Source #
toAlonzoData :: Era ledgerera => HashableScriptData -> Data ledgerera Source #
fromAlonzoData :: Data ledgerera -> HashableScriptData Source #
toScriptIndex :: AlonzoEraOnwards era -> PlutusPurpose AsIx (ShelleyLedgerEra era) -> ScriptWitnessIndex Source #
scriptDataFromJsonDetailedSchema :: Value -> Either ScriptDataJsonSchemaError HashableScriptData Source #
scriptDataToJsonDetailedSchema :: HashableScriptData -> Value Source #
Reference Scripts
data ReferenceScript era where Source #
A reference scripts is a script that can exist at a transaction output. This greatly reduces the size of transactions that use scripts as the script no longer has to be added to the transaction, they can now be referenced via a transaction output.
Constructors
ReferenceScript :: forall era. BabbageEraOnwards era -> ScriptInAnyLang -> ReferenceScript era | |
ReferenceScriptNone :: forall era. ReferenceScript era |
Instances
IsCardanoEra era => FromJSON (ReferenceScript era) Source # | |
Defined in Cardano.Api.Internal.Script Methods parseJSON :: Value -> Parser (ReferenceScript era) parseJSONList :: Value -> Parser [ReferenceScript era] omittedField :: Maybe (ReferenceScript era) | |
IsCardanoEra era => ToJSON (ReferenceScript era) Source # | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ReferenceScript era -> Value toEncoding :: ReferenceScript era -> Encoding toJSONList :: [ReferenceScript era] -> Value toEncodingList :: [ReferenceScript era] -> Encoding omitField :: ReferenceScript era -> Bool | |
Show (ReferenceScript era) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (ReferenceScript era) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: ReferenceScript era -> ReferenceScript era -> Bool Source # (/=) :: ReferenceScript era -> ReferenceScript era -> Bool Source # |
refScriptToShelleyScript :: ShelleyBasedEra era -> ReferenceScript era -> StrictMaybe (Script (ShelleyLedgerEra era)) Source #
Certificates
data Certificate era where Source #
Constructors
ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era | |
ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era |
Instances
Show (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate | |||||
Typeable era => HasTypeProxy (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Associated Types
Methods proxyToAsType :: Proxy (Certificate era) -> AsType (Certificate era) Source # | |||||
IsShelleyBasedEra era => SerialiseAsCBOR (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods serialiseToCBOR :: Certificate era -> ByteString Source # deserialiseFromCBOR :: AsType (Certificate era) -> ByteString -> Either DecoderError (Certificate era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods textEnvelopeType :: AsType (Certificate era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Certificate era -> TextEnvelopeDescr Source # | |||||
IsShelleyBasedEra era => FromCBOR (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate | |||||
IsShelleyBasedEra era => ToCBOR (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods toCBOR :: Certificate era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Certificate era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Certificate era] -> Size Source # | |||||
Eq (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods (==) :: Certificate era -> Certificate era -> Bool Source # (/=) :: Certificate era -> Certificate era -> Bool Source # | |||||
Ord (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods compare :: Certificate era -> Certificate era -> Ordering Source # (<) :: Certificate era -> Certificate era -> Bool Source # (<=) :: Certificate era -> Certificate era -> Bool Source # (>) :: Certificate era -> Certificate era -> Bool Source # (>=) :: Certificate era -> Certificate era -> Bool Source # max :: Certificate era -> Certificate era -> Certificate era Source # min :: Certificate era -> Certificate era -> Certificate era Source # | |||||
data AsType (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate |
toShelleyCertificate :: Certificate era -> TxCert (ShelleyLedgerEra era) Source #
fromShelleyCertificate :: ShelleyBasedEra era -> TxCert (ShelleyLedgerEra era) -> Certificate era Source #
Operational certificates
data OperationalCertificate Source #
Constructors
OperationalCertificate !(OCert StandardCrypto) !(VerificationKey StakePoolKey) |
Instances
Show OperationalCertificate Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate | |||||
HasTypeProxy OperationalCertificate Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate Associated Types
Methods proxyToAsType :: Proxy OperationalCertificate -> AsType OperationalCertificate Source # | |||||
SerialiseAsCBOR OperationalCertificate Source # | |||||
HasTextEnvelope OperationalCertificate Source # | |||||
FromCBOR OperationalCertificate Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate | |||||
ToCBOR OperationalCertificate Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate Methods toCBOR :: OperationalCertificate -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy OperationalCertificate -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [OperationalCertificate] -> Size Source # | |||||
Eq OperationalCertificate Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate Methods (==) :: OperationalCertificate -> OperationalCertificate -> Bool Source # (/=) :: OperationalCertificate -> OperationalCertificate -> Bool Source # | |||||
data AsType OperationalCertificate Source # | |||||
data OperationalCertificateIssueCounter Source #
Constructors
OperationalCertificateIssueCounter | |
Fields |
Instances
Show OperationalCertificateIssueCounter Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate | |||||
HasTypeProxy OperationalCertificateIssueCounter Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate Associated Types
| |||||
SerialiseAsCBOR OperationalCertificateIssueCounter Source # | |||||
HasTextEnvelope OperationalCertificateIssueCounter Source # | |||||
FromCBOR OperationalCertificateIssueCounter Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate | |||||
ToCBOR OperationalCertificateIssueCounter Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate Methods toCBOR :: OperationalCertificateIssueCounter -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy OperationalCertificateIssueCounter -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [OperationalCertificateIssueCounter] -> Size Source # | |||||
Eq OperationalCertificateIssueCounter Source # | |||||
data AsType OperationalCertificateIssueCounter Source # | |||||
data OperationalCertIssueError Source #
Constructors
OperationalCertKeyMismatch (VerificationKey StakePoolKey) (VerificationKey StakePoolKey) | The stake pool verification key expected for the
Order: pool vkey expected, pool skey supplied |
Instances
Show OperationalCertIssueError Source # | |
Defined in Cardano.Api.Internal.OperationalCertificate | |
Error OperationalCertIssueError Source # | |
Defined in Cardano.Api.Internal.OperationalCertificate Methods prettyError :: OperationalCertIssueError -> Doc ann Source # |
Stake Pool
data StakePoolMetadata Source #
A representation of the required fields for off-chain stake pool metadata.
Constructors
StakePoolMetadata !Text !Text !Text !Text |
Instances
FromJSON StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods parseJSON :: Value -> Parser StakePoolMetadata parseJSONList :: Value -> Parser [StakePoolMetadata] | |||||
Show StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
HasTypeProxy StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Associated Types
Methods proxyToAsType :: Proxy StakePoolMetadata -> AsType StakePoolMetadata Source # | |||||
Eq StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods (==) :: StakePoolMetadata -> StakePoolMetadata -> Bool Source # (/=) :: StakePoolMetadata -> StakePoolMetadata -> Bool Source # | |||||
Show (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
SerialiseAsRawBytes (Hash StakePoolMetadata) Source # | |||||
Eq (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods (==) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # (/=) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # | |||||
data AsType StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
newtype Hash StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata |
stakePoolName :: StakePoolMetadata -> Text Source #
A name of up to 50 characters.
stakePoolDescription :: StakePoolMetadata -> Text Source #
A description of up to 255 characters.
stakePoolTicker :: StakePoolMetadata -> Text Source #
A ticker of 3-5 characters, for a compact display of stake pools in a wallet.
stakePoolHomepage :: StakePoolMetadata -> Text Source #
A URL to a homepage with additional information about the pool. n.b. the spec does not specify a character limit for this field.
data StakePoolMetadataReference Source #
Constructors
StakePoolMetadataReference Text (Hash StakePoolMetadata) |
Instances
Show StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: StakePoolMetadataReference -> StakePoolMetadataReference -> Bool Source # (/=) :: StakePoolMetadataReference -> StakePoolMetadataReference -> Bool Source # |
data StakePoolParameters Source #
Constructors
StakePoolParameters PoolId (Hash VrfKey) Coin Rational StakeAddress Coin [Hash StakeKey] [StakePoolRelay] (Maybe StakePoolMetadataReference) |
Instances
Show StakePoolParameters Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq StakePoolParameters Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: StakePoolParameters -> StakePoolParameters -> Bool Source # (/=) :: StakePoolParameters -> StakePoolParameters -> Bool Source # |
data StakePoolRelay Source #
Constructors
StakePoolRelayIp (Maybe IPv4) (Maybe IPv6) (Maybe PortNumber) | One or both of IPv4 & IPv6 |
StakePoolRelayDnsARecord ByteString (Maybe PortNumber) | An DNS name pointing to a |
StakePoolRelayDnsSrvRecord ByteString | A DNS name pointing to a |
Instances
Show StakePoolRelay Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq StakePoolRelay Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (/=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # |
An epoch, i.e. the number of the epoch.
Instances
FromJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
ToJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot Methods toEncoding :: EpochNo -> Encoding toJSONList :: [EpochNo] -> Value toEncodingList :: [EpochNo] -> Encoding | |||||
Enum EpochNo | |||||
Defined in Cardano.Slotting.Slot Methods succ :: EpochNo -> EpochNo Source # pred :: EpochNo -> EpochNo Source # toEnum :: Int -> EpochNo Source # fromEnum :: EpochNo -> Int Source # enumFrom :: EpochNo -> [EpochNo] Source # enumFromThen :: EpochNo -> EpochNo -> [EpochNo] Source # enumFromTo :: EpochNo -> EpochNo -> [EpochNo] Source # enumFromThenTo :: EpochNo -> EpochNo -> EpochNo -> [EpochNo] Source # | |||||
Generic EpochNo | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Show EpochNo | |||||
FromCBOR EpochNo | |||||
ToCBOR EpochNo | |||||
DecCBOR EpochNo | |||||
EncCBOR EpochNo | |||||
NFData EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
Eq EpochNo | |||||
Ord EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
NoThunks EpochNo | |||||
Condense EpochNo | |||||
Serialise EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
type Rep EpochNo | |||||
Defined in Cardano.Slotting.Slot type Rep EpochNo = D1 ('MetaData "EpochNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-cd5925153f267941e5a1c5b3fd90532bb9050966c3f4917f2ef8a79d4affa394" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
Governance Actions
createAnchor :: Url -> ByteString -> Anchor StandardCrypto Source #
createPreviousGovernanceActionId Source #
Arguments
:: forall era (r :: GovActionPurpose). EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto | |
=> TxId | |
-> Word16 | Governance action transation index |
-> GovPurposeId r (ShelleyLedgerEra era) |
DRep
newtype DRepMetadata Source #
A representation of the required fields for off-chain drep metadata.
Constructors
DRepMetadata ByteString |
Instances
Show DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
HasTypeProxy DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Associated Types
Methods proxyToAsType :: Proxy DRepMetadata -> AsType DRepMetadata Source # | |||||
Eq DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods (==) :: DRepMetadata -> DRepMetadata -> Bool Source # (/=) :: DRepMetadata -> DRepMetadata -> Bool Source # | |||||
Show (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
SerialiseAsRawBytes (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods serialiseToRawBytes :: Hash DRepMetadata -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepMetadata) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepMetadata) Source # | |||||
Eq (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods (==) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # (/=) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # | |||||
data AsType DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
newtype Hash DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata |
data DRepMetadataReference Source #
Constructors
DRepMetadataReference Text (Hash DRepMetadata) |
Instances
Show DRepMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq DRepMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: DRepMetadataReference -> DRepMetadataReference -> Bool Source # (/=) :: DRepMetadataReference -> DRepMetadataReference -> Bool Source # |
Stake pool operator's keys
data StakePoolKey Source #
Instances
HasTypeProxy StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy StakePoolKey -> AsType StakePoolKey Source # | |||||||||
Key StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey Source # deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey Source # deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word Source # verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey Source # | |||||||||
FromJSON (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash StakePoolKey) parseJSONList :: Value -> Parser [Hash StakePoolKey] | |||||||||
ToJSON (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash StakePoolKey -> Value toEncoding :: Hash StakePoolKey -> Encoding toJSONList :: [Hash StakePoolKey] -> Value toEncodingList :: [Hash StakePoolKey] -> Encoding omitField :: Hash StakePoolKey -> Bool | |||||||||
ToJSONKey (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey] | |||||||||
IsString (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakePoolKey Source # | |||||||||
IsString (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||||||
IsString (VerificationKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakePoolKey Source # | |||||||||
Show (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
Show (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakePoolKey -> ShowS Source # show :: SigningKey StakePoolKey -> String Source # showList :: [SigningKey StakePoolKey] -> ShowS Source # | |||||||||
Show (VerificationKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS Source # show :: VerificationKey StakePoolKey -> String Source # showList :: [VerificationKey StakePoolKey] -> ShowS Source # | |||||||||
SerialiseAsBech32 (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash StakePoolKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text] | |||||||||
SerialiseAsBech32 (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakePoolKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakePoolKey) -> [Text] | |||||||||
SerialiseAsCBOR (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakePoolKey) -> ByteString -> Either DecoderError (Hash StakePoolKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakePoolKey) -> ByteString -> Either DecoderError (SigningKey StakePoolKey) Source # | |||||||||
SerialiseAsCBOR (VerificationKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsRawBytes (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakePoolKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakePoolKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakePoolKey) Source # | |||||||||
SerialiseAsRawBytes (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsRawBytes (VerificationKey StakePoolKey) Source # | |||||||||
HasTextEnvelope (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
HasTextEnvelope (VerificationKey StakePoolKey) Source # | |||||||||
FromCBOR (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
FromCBOR (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolKey) Source # label :: Proxy (SigningKey StakePoolKey) -> Text Source # | |||||||||
FromCBOR (VerificationKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolKey) Source # label :: Proxy (VerificationKey StakePoolKey) -> Text Source # | |||||||||
ToCBOR (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
ToCBOR (SigningKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolKey] -> Size Source # | |||||||||
ToCBOR (VerificationKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolKey] -> Size Source # | |||||||||
Eq (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (/=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # | |||||||||
Eq (VerificationKey StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # (/=) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # | |||||||||
Ord (Hash StakePoolKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering Source # (<) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (<=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # max :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # min :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # | |||||||||
data AsType StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype Hash StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype SigningKey StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype VerificationKey StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley |
type PoolId = Hash StakePoolKey Source #
KES keys
Instances
HasTypeProxy KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
Key KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
IsString (Hash KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
IsString (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey KesKey Source # | |||||||||
IsString (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey KesKey Source # | |||||||||
Show (Hash KesKey) Source # | |||||||||
Show (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
Show (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
SerialiseAsBech32 (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey KesKey -> Text bech32PrefixesPermitted :: AsType (SigningKey KesKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey KesKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey KesKey) -> [Text] | |||||||||
SerialiseAsCBOR (Hash KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash KesKey) -> ByteString -> Either DecoderError (Hash KesKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey KesKey) -> ByteString -> Either DecoderError (SigningKey KesKey) Source # | |||||||||
SerialiseAsCBOR (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey KesKey) -> ByteString -> Either DecoderError (VerificationKey KesKey) Source # | |||||||||
SerialiseAsRawBytes (Hash KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash KesKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash KesKey) Source # | |||||||||
SerialiseAsRawBytes (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey KesKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey KesKey) Source # | |||||||||
SerialiseAsRawBytes (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
HasTextEnvelope (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey KesKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey KesKey -> TextEnvelopeDescr Source # | |||||||||
HasTextEnvelope (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
FromCBOR (Hash KesKey) Source # | |||||||||
FromCBOR (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
FromCBOR (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
ToCBOR (Hash KesKey) Source # | |||||||||
ToCBOR (SigningKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
ToCBOR (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
Eq (Hash KesKey) Source # | |||||||||
Eq (VerificationKey KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # (/=) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # | |||||||||
Ord (Hash KesKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash KesKey -> Hash KesKey -> Ordering Source # (<) :: Hash KesKey -> Hash KesKey -> Bool Source # (<=) :: Hash KesKey -> Hash KesKey -> Bool Source # (>) :: Hash KesKey -> Hash KesKey -> Bool Source # (>=) :: Hash KesKey -> Hash KesKey -> Bool Source # | |||||||||
data AsType KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
newtype Hash KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
newtype SigningKey KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
newtype VerificationKey KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos |
Constructors
KESPeriod | |
Fields
|
Instances
Generic KESPeriod | |||||
Defined in Cardano.Protocol.TPraos.OCert Associated Types
| |||||
Show KESPeriod | |||||
FromCBOR KESPeriod | |||||
ToCBOR KESPeriod | |||||
DecCBOR KESPeriod | |||||
EncCBOR KESPeriod | |||||
Eq KESPeriod | |||||
Ord KESPeriod | |||||
Defined in Cardano.Protocol.TPraos.OCert | |||||
NoThunks KESPeriod | |||||
type Rep KESPeriod | |||||
Defined in Cardano.Protocol.TPraos.OCert type Rep KESPeriod = D1 ('MetaData "KESPeriod" "Cardano.Protocol.TPraos.OCert" "cardano-protocol-tpraos-1.3.0.0-ca85ff99d9052f7c8448d59579428c1c4bbec0b45d1593062ca02847bf08d349" 'True) (C1 ('MetaCons "KESPeriod" 'PrefixI 'True) (S1 ('MetaSel ('Just "unKESPeriod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))) |
VRF keys
Instances
HasTypeProxy VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
Key VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
IsString (Hash VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
IsString (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey VrfKey Source # | |||||||||
IsString (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey VrfKey Source # | |||||||||
Show (Hash VrfKey) Source # | |||||||||
Show (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
Show (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
SerialiseAsBech32 (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey VrfKey -> Text bech32PrefixesPermitted :: AsType (SigningKey VrfKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey VrfKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey VrfKey) -> [Text] | |||||||||
SerialiseAsCBOR (Hash VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash VrfKey) -> ByteString -> Either DecoderError (Hash VrfKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey VrfKey) -> ByteString -> Either DecoderError (SigningKey VrfKey) Source # | |||||||||
SerialiseAsCBOR (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey VrfKey) -> ByteString -> Either DecoderError (VerificationKey VrfKey) Source # | |||||||||
SerialiseAsRawBytes (Hash VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash VrfKey) Source # | |||||||||
SerialiseAsRawBytes (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey VrfKey) Source # | |||||||||
SerialiseAsRawBytes (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
HasTextEnvelope (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey VrfKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey VrfKey -> TextEnvelopeDescr Source # | |||||||||
HasTextEnvelope (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
FromCBOR (Hash VrfKey) Source # | |||||||||
FromCBOR (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
FromCBOR (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
ToCBOR (Hash VrfKey) Source # | |||||||||
ToCBOR (SigningKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
ToCBOR (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
Eq (Hash VrfKey) Source # | |||||||||
Eq (VerificationKey VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # (/=) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # | |||||||||
Ord (Hash VrfKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash VrfKey -> Hash VrfKey -> Ordering Source # (<) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (<=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # | |||||||||
data AsType VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
newtype Hash VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
newtype SigningKey VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||||||
newtype VerificationKey VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos |
Low level protocol interaction with a Cardano node
data LocalNodeConnectInfo Source #
Constructors
LocalNodeConnectInfo ConsensusModeParams NetworkId SocketPath |
Instances
Show LocalNodeConnectInfo Source # | |
Defined in Cardano.Api.Internal.IPC |
data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) Source #
The protocols we can use with a local node. Use in conjunction with
connectToLocalNode
.
These protocols use the types from the rest of this API. The conversion
to/from the types used by the underlying wire formats is handled by
connectToLocalNode
.
Constructors
LocalNodeClientProtocols (LocalChainSyncClient block point tip m) (Maybe (LocalTxSubmissionClient tx txerr m ())) (Maybe (LocalStateQueryClient block point query m ())) (Maybe (LocalTxMonitorClient txid tx slot m ())) |
Shelley based eras
type family ShelleyLedgerEra era = (ledgerera :: Type) | ledgerera -> era where ... Source #
A type family that connects our era type tags to equivalent type tags used in the Shelley ledger library.
This type mapping connect types from this API with types in the Shelley ledger library which allows writing conversion functions in a more generic way.
Ledger Events
data LedgerEvent Source #
Constructors
PoolRegistration | The given pool is being registered for the first time on chain. |
PoolReRegistration | The given pool already exists and is being re-registered. |
IncrementalRewardsDistribution EpochNo (Map StakeCredential (Set (Reward StandardCrypto))) | Incremental rewards are being computed. |
RewardsDistribution EpochNo (Map StakeCredential (Set (Reward StandardCrypto))) | Reward distribution has completed. |
MIRDistribution MIRDistributionDetails | MIR are being distributed. |
PoolReap PoolReapDetails | Pools have been reaped and deposits refunded. |
SuccessfulPlutusScript (NonEmpty (PlutusWithContext StandardCrypto)) | A number of succeeded Plutus script evaluations. |
FailedPlutusScript (NonEmpty (PlutusWithContext StandardCrypto)) | A number of failed Plutus script evaluations. |
NewGovernanceProposals (TxId StandardCrypto) AnyProposals | Newly submittted governance proposals in a single transaction. |
RemovedGovernanceVotes | Governance votes that were invalidated. |
Fields
| |
EpochBoundaryRatificationState AnyRatificationState | The current state of governance matters at the epoch boundary. I.E the current constitution, committee, protocol parameters, etc. |
Instances
data AnyProposals Source #
Constructors
EraPParams era => AnyProposals (Proposals era) |
Instances
data AnyRatificationState Source #
Constructors
EraPParams era => AnyRatificationState (RatifyState era) |
Instances
data MIRDistributionDetails Source #
Details of fund transfers due to MIR certificates.
Note that the transfers from reserves to treasury and treasury to reserves are inverse; a transfer of 100 ADA in either direction will result in a net movement of 0, but we include both directions for assistance in debugging.
Constructors
MIRDistributionDetails | |
Instances
data PoolReapDetails Source #
Constructors
PoolReapDetails | |
Fields
|
Instances
toLedgerEvent :: ConvertLedgerEvent blk => WrapLedgerEvent blk -> Maybe LedgerEvent Source #
Local State Query
newtype DebugLedgerState era Source #
Constructors
DebugLedgerState | |
Fields |
Instances
IsShelleyBasedEra era => ToJSON (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Internal.Query.Types Methods toJSON :: DebugLedgerState era -> Value toEncoding :: DebugLedgerState era -> Encoding toJSONList :: [DebugLedgerState era] -> Value toEncodingList :: [DebugLedgerState era] -> Encoding omitField :: DebugLedgerState era -> Bool | |
IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Internal.Query.Types |
decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either (ByteString, DecoderError) (DebugLedgerState era) Source #
newtype ProtocolState era Source #
Constructors
ProtocolState (Serialised (ChainDepState (ConsensusProtocol era))) |
decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era)) Source #
newtype SerialisedDebugLedgerState era Source #
Constructors
SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era))) |
newtype CurrentEpochState era Source #
Constructors
CurrentEpochState (EpochState (ShelleyLedgerEra era)) |
newtype SerialisedCurrentEpochState era Source #
Constructors
SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era))) |
decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era) Source #
newtype SerialisedPoolState era Source #
Constructors
SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era))) |
decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era) Source #
newtype PoolDistribution era Source #
Constructors
PoolDistribution | |
Fields
|
newtype SerialisedPoolDistribution era Source #
Constructors
SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era)))) |
decodePoolDistribution :: Crypto (EraCrypto (ShelleyLedgerEra era)) => ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era) Source #
newtype StakeSnapshot era Source #
Constructors
StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) |
newtype SerialisedStakeSnapshots era Source #
Constructors
SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))) |
decodeStakeSnapshot :: FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era) Source #
decodeBigLedgerPeerSnapshot :: Serialised LedgerPeerSnapshot -> Either (ByteString, DecoderError) LedgerPeerSnapshot Source #
Instances
IsShelleyBasedEra era => FromJSON (UTxO era) Source # | |
Defined in Cardano.Api.Internal.Tx.UTxO Methods parseJSON :: Value -> Parser (UTxO era) parseJSONList :: Value -> Parser [UTxO era] omittedField :: Maybe (UTxO era) | |
IsCardanoEra era => ToJSON (UTxO era) Source # | |
Defined in Cardano.Api.Internal.Tx.UTxO Methods toEncoding :: UTxO era -> Encoding toJSONList :: [UTxO era] -> Value toEncodingList :: [UTxO era] -> Encoding | |
Monoid (UTxO era) Source # | |
Semigroup (UTxO era) Source # | |
IsList (UTxO era) Source # | |
Defined in Cardano.Api.Internal.Tx.UTxO | |
Show (UTxO era) Source # | |
Eq (UTxO era) Source # | |
type Item (UTxO era) Source # | |
data AcquiringFailure Source #
Establish a connection to a node and execute a single query using the local state query protocol.
Constructors
AFPointTooOld | |
AFPointNotOnChain |
Instances
Show AcquiringFailure Source # | |
Defined in Cardano.Api.Internal.IPC | |
Eq AcquiringFailure Source # | |
Defined in Cardano.Api.Internal.IPC Methods (==) :: AcquiringFailure -> AcquiringFailure -> Bool Source # (/=) :: AcquiringFailure -> AcquiringFailure -> Bool Source # |
newtype SystemStart Source #
System start
Slots are counted from the system start.
Constructors
SystemStart | |
Fields |
Instances
FromJSON SystemStart | |||||
Defined in Cardano.Slotting.Time | |||||
ToJSON SystemStart | |||||
Defined in Cardano.Slotting.Time Methods toJSON :: SystemStart -> Value toEncoding :: SystemStart -> Encoding toJSONList :: [SystemStart] -> Value toEncodingList :: [SystemStart] -> Encoding omitField :: SystemStart -> Bool | |||||
Generic SystemStart | |||||
Defined in Cardano.Slotting.Time Associated Types
Methods from :: SystemStart -> Rep SystemStart x Source # to :: Rep SystemStart x -> SystemStart Source # | |||||
Show SystemStart | |||||
Defined in Cardano.Slotting.Time | |||||
FromCBOR SystemStart | |||||
Defined in Cardano.Slotting.Time | |||||
ToCBOR SystemStart | |||||
Defined in Cardano.Slotting.Time Methods toCBOR :: SystemStart -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size Source # | |||||
DecCBOR SystemStart | |||||
Defined in Cardano.Ledger.Binary.Decoding.DecCBOR | |||||
EncCBOR SystemStart | |||||
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR Methods encCBOR :: SystemStart -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size Source # | |||||
Eq SystemStart | |||||
Defined in Cardano.Slotting.Time Methods (==) :: SystemStart -> SystemStart -> Bool Source # (/=) :: SystemStart -> SystemStart -> Bool Source # | |||||
NoThunks SystemStart | |||||
Defined in Cardano.Slotting.Time Methods noThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy SystemStart -> String # | |||||
Serialise SystemStart | |||||
Defined in Cardano.Slotting.Time Methods encode :: SystemStart -> Encoding decode :: Decoder s SystemStart encodeList :: [SystemStart] -> Encoding decodeList :: Decoder s [SystemStart] | |||||
type Rep SystemStart | |||||
Defined in Cardano.Slotting.Time type Rep SystemStart = D1 ('MetaData "SystemStart" "Cardano.Slotting.Time" "cardano-slotting-0.2.0.0-cd5925153f267941e5a1c5b3fd90532bb9050966c3f4917f2ef8a79d4affa394" 'True) (C1 ('MetaCons "SystemStart" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSystemStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime))) |
Governance
data GovernanceAction era Source #
Constructors
MotionOfNoConfidence (StrictMaybe (GovPurposeId 'CommitteePurpose (ShelleyLedgerEra era))) | |
ProposeNewConstitution (StrictMaybe (GovPurposeId 'ConstitutionPurpose (ShelleyLedgerEra era))) (Anchor StandardCrypto) (StrictMaybe (ScriptHash StandardCrypto)) | |
ProposeNewCommittee | |
Fields
| |
InfoAct | |
TreasuryWithdrawal [(Network, StakeCredential, Coin)] !(StrictMaybe (ScriptHash StandardCrypto)) | Governance policy |
InitiateHardfork (StrictMaybe (GovPurposeId 'HardForkPurpose (ShelleyLedgerEra era))) ProtVer | |
UpdatePParams (StrictMaybe (GovPurposeId 'PParamUpdatePurpose (ShelleyLedgerEra era))) (PParamsUpdate (ShelleyLedgerEra era)) !(StrictMaybe (ScriptHash StandardCrypto)) | Governance policy |
newtype GovernanceActionId era Source #
Constructors
GovernanceActionId | |
Fields
|
Instances
Show (GovernanceActionId era) Source # | |
IsShelleyBasedEra era => FromCBOR (GovernanceActionId era) Source # | |
IsShelleyBasedEra era => ToCBOR (GovernanceActionId era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods toCBOR :: GovernanceActionId era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (GovernanceActionId era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [GovernanceActionId era] -> Size Source # | |
Eq (GovernanceActionId era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods (==) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # (/=) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # | |
Ord (GovernanceActionId era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods compare :: GovernanceActionId era -> GovernanceActionId era -> Ordering Source # (<) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # (<=) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # (>) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # (>=) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # max :: GovernanceActionId era -> GovernanceActionId era -> GovernanceActionId era Source # min :: GovernanceActionId era -> GovernanceActionId era -> GovernanceActionId era Source # |
Constructors
Proposal | |
Fields
|
Instances
IsShelleyBasedEra era => Show (Proposal era) Source # | |||||
HasTypeProxy era => HasTypeProxy (Proposal era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.ProposalProcedure Associated Types
| |||||
IsShelleyBasedEra era => SerialiseAsCBOR (Proposal era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.ProposalProcedure Methods serialiseToCBOR :: Proposal era -> ByteString Source # deserialiseFromCBOR :: AsType (Proposal era) -> ByteString -> Either DecoderError (Proposal era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (Proposal era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.ProposalProcedure Methods textEnvelopeType :: AsType (Proposal era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Proposal era -> TextEnvelopeDescr Source # | |||||
IsShelleyBasedEra era => FromCBOR (Proposal era) Source # | |||||
IsShelleyBasedEra era => ToCBOR (Proposal era) Source # | |||||
IsShelleyBasedEra era => Eq (Proposal era) Source # | |||||
data AsType (Proposal era) Source # | |||||
newtype VotingProcedure era Source #
Constructors
VotingProcedure | |
Fields |
Instances
Show (VotingProcedure era) Source # | |||||
HasTypeProxy era => HasTypeProxy (VotingProcedure era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Associated Types
Methods proxyToAsType :: Proxy (VotingProcedure era) -> AsType (VotingProcedure era) Source # | |||||
IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedure era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods serialiseToCBOR :: VotingProcedure era -> ByteString Source # deserialiseFromCBOR :: AsType (VotingProcedure era) -> ByteString -> Either DecoderError (VotingProcedure era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (VotingProcedure era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods textEnvelopeType :: AsType (VotingProcedure era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: VotingProcedure era -> TextEnvelopeDescr Source # | |||||
IsShelleyBasedEra era => FromCBOR (VotingProcedure era) Source # | |||||
IsShelleyBasedEra era => ToCBOR (VotingProcedure era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods toCBOR :: VotingProcedure era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VotingProcedure era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VotingProcedure era] -> Size Source # | |||||
Eq (VotingProcedure era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods (==) :: VotingProcedure era -> VotingProcedure era -> Bool Source # (/=) :: VotingProcedure era -> VotingProcedure era -> Bool Source # | |||||
data AsType (VotingProcedure era) Source # | |||||
newtype VotingProcedures era Source #
Constructors
VotingProcedures | |
Fields |
Instances
Generic (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Associated Types
Methods from :: VotingProcedures era -> Rep (VotingProcedures era) x Source # to :: Rep (VotingProcedures era) x -> VotingProcedures era Source # | |||||
Show (VotingProcedures era) Source # | |||||
HasTypeProxy era => HasTypeProxy (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Associated Types
Methods proxyToAsType :: Proxy (VotingProcedures era) -> AsType (VotingProcedures era) Source # | |||||
IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods serialiseToCBOR :: VotingProcedures era -> ByteString Source # deserialiseFromCBOR :: AsType (VotingProcedures era) -> ByteString -> Either DecoderError (VotingProcedures era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods textEnvelopeType :: AsType (VotingProcedures era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: VotingProcedures era -> TextEnvelopeDescr Source # | |||||
IsShelleyBasedEra era => FromCBOR (VotingProcedures era) Source # | |||||
IsShelleyBasedEra era => ToCBOR (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods toCBOR :: VotingProcedures era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VotingProcedures era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VotingProcedures era] -> Size Source # | |||||
Eq (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods (==) :: VotingProcedures era -> VotingProcedures era -> Bool Source # (/=) :: VotingProcedures era -> VotingProcedures era -> Bool Source # | |||||
type Rep (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure type Rep (VotingProcedures era) = D1 ('MetaData "VotingProcedures" "Cardano.Api.Internal.Governance.Actions.VotingProcedure" "cardano-api-10.9.0.0-inplace" 'True) (C1 ('MetaCons "VotingProcedures" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVotingProcedures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VotingProcedures (ShelleyLedgerEra era))))) | |||||
data AsType (VotingProcedures era) Source # | |||||
data GovernancePoll Source #
A governance poll declaration meant to be created by one of the genesis delegates and directed towards SPOs.
A poll is made of a question and some pre-defined answers to chose from. There's an optional nonce used to make poll unique (as things down the line are based on their hashes) if the same question/answers need to be asked multiple times.
Constructors
GovernancePoll | |
Fields
|
Instances
Show GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
HasTypeProxy GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Associated Types
Methods proxyToAsType :: Proxy GovernancePoll -> AsType GovernancePoll Source # | |||||
SerialiseAsCBOR GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods serialiseToCBOR :: GovernancePoll -> ByteString Source # deserialiseFromCBOR :: AsType GovernancePoll -> ByteString -> Either DecoderError GovernancePoll Source # | |||||
HasTextEnvelope GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
AsTxMetadata GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods | |||||
Eq GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods (==) :: GovernancePoll -> GovernancePoll -> Bool Source # (/=) :: GovernancePoll -> GovernancePoll -> Bool Source # | |||||
IsString (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods fromString :: String -> Hash GovernancePoll Source # | |||||
Show (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
SerialiseAsRawBytes (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
Eq (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods (==) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (/=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # | |||||
Ord (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods compare :: Hash GovernancePoll -> Hash GovernancePoll -> Ordering Source # (<) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (<=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # max :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # min :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # | |||||
data AsType GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
newtype Hash GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll |
data GovernancePollAnswer Source #
An (unauthenticated) answer to a poll from an SPO referring to a poll by hash digest value.
Constructors
GovernancePollAnswer | |
Fields
|
Instances
Show GovernancePollAnswer Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
HasTypeProxy GovernancePollAnswer Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Associated Types
Methods proxyToAsType :: Proxy GovernancePollAnswer -> AsType GovernancePollAnswer Source # | |||||
SerialiseAsCBOR GovernancePollAnswer Source # | |||||
AsTxMetadata GovernancePollAnswer Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods | |||||
Eq GovernancePollAnswer Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods (==) :: GovernancePollAnswer -> GovernancePollAnswer -> Bool Source # (/=) :: GovernancePollAnswer -> GovernancePollAnswer -> Bool Source # | |||||
data AsType GovernancePollAnswer Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll |
data GovernancePollError Source #
Constructors
ErrGovernancePollMismatch GovernancePollMismatchError | |
ErrGovernancePollNoAnswer | |
ErrGovernancePollUnauthenticated | |
ErrGovernancePollMalformedAnswer DecoderError | |
ErrGovernancePollInvalidAnswer GovernancePollInvalidAnswerError |
Instances
Constructors
Voter (Voter (EraCrypto (ShelleyLedgerEra era))) |
Instances
Show (Voter era) Source # | |
IsShelleyBasedEra era => FromCBOR (Voter era) Source # | |
IsShelleyBasedEra era => ToCBOR (Voter era) Source # | |
Eq (Voter era) Source # | |
Ord (Voter era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure |
createProposalProcedure Source #
Arguments
:: ShelleyBasedEra era | |
-> Network | |
-> Coin | Deposit |
-> StakeCredential | Credential to return the deposit to. |
-> GovernanceAction era | |
-> Anchor StandardCrypto | |
-> Proposal era |
createVotingProcedure Source #
Arguments
:: ConwayEraOnwards era | |
-> Vote | |
-> Maybe (Url, Text) | Anchor |
-> VotingProcedure era |
fromProposalProcedure :: ShelleyBasedEra era -> Proposal era -> (Coin, StakeCredential, GovernanceAction era) Source #
verifyPollAnswer :: GovernancePoll -> InAnyShelleyBasedEra Tx -> Either GovernancePollError [Hash PaymentKey] Source #
Verify a poll against a given transaction and returns the signatories (verification key only) when valid.
Note: signatures aren't checked as it is assumed to have been done externally (the existence of the transaction in the ledger provides this guarantee).
Various calculations
data LeadershipError Source #
Constructors
LeaderErrDecodeLedgerStateFailure | |
LeaderErrDecodeProtocolStateFailure (ByteString, DecoderError) | |
LeaderErrDecodeProtocolEpochStateFailure DecoderError | |
LeaderErrGenesisSlot | |
LeaderErrStakePoolHasNoStake PoolId | |
LeaderErrStakeDistribUnstable | |
LeaderErrSlotRangeCalculationFailure Text | |
LeaderErrCandidateNonceStillEvolving |
Instances
Show LeadershipError Source # | |
Defined in Cardano.Api.Internal.LedgerState | |
Error LeadershipError Source # | |
Defined in Cardano.Api.Internal.LedgerState Methods prettyError :: LeadershipError -> Doc ann Source # |
currentEpochEligibleLeadershipSlots Source #
Arguments
:: ShelleyBasedEra era | |
-> ShelleyGenesis StandardCrypto | |
-> EpochInfo (Either Text) | |
-> PParams (ShelleyLedgerEra era) | |
-> ProtocolState era | |
-> PoolId | |
-> SigningKey VrfKey | |
-> SerialisedPoolDistribution era | |
-> EpochNo | Current EpochInfo |
-> Either LeadershipError (Set SlotNo) |
Return the slots at which a particular stake pool operator is expected to mint a block.
evaluateTransactionExecutionUnitsShelley :: ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> Tx (ShelleyLedgerEra era) -> Either (TransactionValidityError era) (Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits))) Source #
nextEpochEligibleLeadershipSlots Source #
Arguments
:: ShelleyBasedEra era | |
-> ShelleyGenesis StandardCrypto | |
-> SerialisedCurrentEpochState era | We need the mark stake distribution in order to predict the following epoch's leadership schedule |
-> ProtocolState era | |
-> PoolId | Potential slot leading stake pool |
-> SigningKey VrfKey | VRF signing key of the stake pool |
-> PParams (ShelleyLedgerEra era) | |
-> EpochInfo (Either Text) | |
-> (ChainTip, EpochNo) | |
-> Either LeadershipError (Set SlotNo) |
Conversions
shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PubKeyHash Source #
Converts a Shelley payment address to a Plutus public key hash.
toConsensusGenTx :: CardanoBlock StandardCrypto ~ block => TxInMode -> GenTx block Source #
toLedgerNonce :: Maybe PraosNonce -> Nonce Source #
toShelleyNetwork :: NetworkId -> Network Source #
fromLedgerPParamsUpdate :: ShelleyBasedEra era -> PParamsUpdate (ShelleyLedgerEra era) -> ProtocolParametersUpdate Source #
mergeVotingProcedures Source #
Arguments
:: VotingProcedures era | Votes to merge |
-> VotingProcedures era | Votes to merge |
-> Either (VotesMergingConflict era) (VotingProcedures era) | Either the conflict found, or the merged votes |
mergeVotingProcedures vote1 vote2
merges vote1
and vote2
into a single vote,
or fails if the votes are incompatible.
singletonVotingProcedures :: ConwayEraOnwards era -> Voter (EraCrypto (ShelleyLedgerEra era)) -> GovActionId (EraCrypto (ShelleyLedgerEra era)) -> VotingProcedure (ShelleyLedgerEra era) -> VotingProcedures era Source #
newtype VotesMergingConflict era Source #
A voter, and the conflicting votes of this voter (i.e. votes with the same governance action identifier)
Constructors
VotesMergingConflict (Voter (EraCrypto (ShelleyLedgerEra era)), [GovActionId (EraCrypto (ShelleyLedgerEra era))]) |