Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a library interface that is intended to be the complete API for Shelley covering everything, including exposing constructors for the lower level types.
Synopsis
- module Cardano.Api
- data ShelleyGenesis 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 Natural
- 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 :: Natural
- 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
- 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
- | 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)
- 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.
ShelleyGenesis | |
|
Instances
alonzoGenesisDefaults :: CardanoEra era -> AlonzoGenesis #
decodeAlonzoGenesis :: forall era t (m :: Type -> Type). MonadTransError String t m => Maybe (CardanoEra era) -> ByteString -> t m AlonzoGenesis #
Cryptographic key interface
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 #
Instances
Key ByronKey | |||||||||
Defined in Cardano.Api.Keys.Byron
| |||||||||
Key ByronKeyLegacy | |||||||||
Defined in Cardano.Api.Keys.Byron
getVerificationKey :: SigningKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy # deterministicSigningKey :: AsType ByronKeyLegacy -> Seed -> SigningKey ByronKeyLegacy # deterministicSigningKeySeedSize :: AsType ByronKeyLegacy -> Word # verificationKeyHash :: VerificationKey ByronKeyLegacy -> Hash ByronKeyLegacy # | |||||||||
Key KesKey | |||||||||
Defined in Cardano.Api.Keys.Praos
| |||||||||
Key VrfKey | |||||||||
Defined in Cardano.Api.Keys.Praos
| |||||||||
Key CommitteeColdExtendedKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey CommitteeColdExtendedKey -> VerificationKey CommitteeColdExtendedKey # deterministicSigningKey :: AsType CommitteeColdExtendedKey -> Seed -> SigningKey CommitteeColdExtendedKey # deterministicSigningKeySeedSize :: AsType CommitteeColdExtendedKey -> Word # verificationKeyHash :: VerificationKey CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey # | |||||||||
Key CommitteeColdKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey CommitteeColdKey -> VerificationKey CommitteeColdKey # deterministicSigningKey :: AsType CommitteeColdKey -> Seed -> SigningKey CommitteeColdKey # deterministicSigningKeySeedSize :: AsType CommitteeColdKey -> Word # verificationKeyHash :: VerificationKey CommitteeColdKey -> Hash CommitteeColdKey # | |||||||||
Key CommitteeHotExtendedKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey CommitteeHotExtendedKey -> VerificationKey CommitteeHotExtendedKey # deterministicSigningKey :: AsType CommitteeHotExtendedKey -> Seed -> SigningKey CommitteeHotExtendedKey # deterministicSigningKeySeedSize :: AsType CommitteeHotExtendedKey -> Word # verificationKeyHash :: VerificationKey CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey # | |||||||||
Key CommitteeHotKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey CommitteeHotKey -> VerificationKey CommitteeHotKey # deterministicSigningKey :: AsType CommitteeHotKey -> Seed -> SigningKey CommitteeHotKey # deterministicSigningKeySeedSize :: AsType CommitteeHotKey -> Word # verificationKeyHash :: VerificationKey CommitteeHotKey -> Hash CommitteeHotKey # | |||||||||
Key DRepExtendedKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey DRepExtendedKey -> VerificationKey DRepExtendedKey # deterministicSigningKey :: AsType DRepExtendedKey -> Seed -> SigningKey DRepExtendedKey # deterministicSigningKeySeedSize :: AsType DRepExtendedKey -> Word # verificationKeyHash :: VerificationKey DRepExtendedKey -> Hash DRepExtendedKey # | |||||||||
Key DRepKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
| |||||||||
Key GenesisDelegateExtendedKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey GenesisDelegateExtendedKey -> VerificationKey GenesisDelegateExtendedKey # deterministicSigningKey :: AsType GenesisDelegateExtendedKey -> Seed -> SigningKey GenesisDelegateExtendedKey # deterministicSigningKeySeedSize :: AsType GenesisDelegateExtendedKey -> Word # verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey # | |||||||||
Key GenesisDelegateKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey # deterministicSigningKey :: AsType GenesisDelegateKey -> Seed -> SigningKey GenesisDelegateKey # deterministicSigningKeySeedSize :: AsType GenesisDelegateKey -> Word # verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey # | |||||||||
Key GenesisExtendedKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey GenesisExtendedKey -> VerificationKey GenesisExtendedKey # deterministicSigningKey :: AsType GenesisExtendedKey -> Seed -> SigningKey GenesisExtendedKey # deterministicSigningKeySeedSize :: AsType GenesisExtendedKey -> Word # verificationKeyHash :: VerificationKey GenesisExtendedKey -> Hash GenesisExtendedKey # | |||||||||
Key GenesisKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
| |||||||||
Key GenesisUTxOKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey # deterministicSigningKey :: AsType GenesisUTxOKey -> Seed -> SigningKey GenesisUTxOKey # deterministicSigningKeySeedSize :: AsType GenesisUTxOKey -> Word # verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey # | |||||||||
Key PaymentExtendedKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey PaymentExtendedKey -> VerificationKey PaymentExtendedKey # deterministicSigningKey :: AsType PaymentExtendedKey -> Seed -> SigningKey PaymentExtendedKey # deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word # verificationKeyHash :: VerificationKey PaymentExtendedKey -> Hash PaymentExtendedKey # | |||||||||
Key PaymentKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
| |||||||||
Key StakeExtendedKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey StakeExtendedKey -> VerificationKey StakeExtendedKey # deterministicSigningKey :: AsType StakeExtendedKey -> Seed -> SigningKey StakeExtendedKey # deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word # verificationKeyHash :: VerificationKey StakeExtendedKey -> Hash StakeExtendedKey # | |||||||||
Key StakeKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
| |||||||||
Key StakePoolKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey # deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey # deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word # verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey # |
data family VerificationKey keyrole #
Instances
IsString (VerificationKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
IsString (VerificationKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
IsString (VerificationKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> VerificationKey KesKey Source # | |||||
IsString (VerificationKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> VerificationKey VrfKey Source # | |||||
IsString (VerificationKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey CommitteeHotExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey GenesisDelegateExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey GenesisDelegateKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey GenesisExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey PaymentExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (VerificationKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
Show (VerificationKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron showsPrec :: Int -> VerificationKey ByronKeyLegacy -> ShowS Source # show :: VerificationKey ByronKeyLegacy -> String Source # showList :: [VerificationKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (VerificationKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
Show (VerificationKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
Show (VerificationKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey CommitteeColdKey -> ShowS Source # show :: VerificationKey CommitteeColdKey -> String Source # showList :: [VerificationKey CommitteeColdKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeHotExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey CommitteeHotKey -> ShowS Source # show :: VerificationKey CommitteeHotKey -> String Source # showList :: [VerificationKey CommitteeHotKey] -> ShowS Source # | |||||
Show (VerificationKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey DRepExtendedKey -> ShowS Source # show :: VerificationKey DRepExtendedKey -> String Source # showList :: [VerificationKey DRepExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey GenesisDelegateExtendedKey) | |||||
Show (VerificationKey GenesisDelegateKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey GenesisExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey GenesisKey -> ShowS Source # show :: VerificationKey GenesisKey -> String Source # showList :: [VerificationKey GenesisKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS Source # show :: VerificationKey GenesisUTxOKey -> String Source # showList :: [VerificationKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (VerificationKey PaymentExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey PaymentKey -> ShowS Source # show :: VerificationKey PaymentKey -> String Source # showList :: [VerificationKey PaymentKey] -> ShowS Source # | |||||
Show (VerificationKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS Source # show :: VerificationKey StakeExtendedKey -> String Source # showList :: [VerificationKey StakeExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (VerificationKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS Source # show :: VerificationKey StakePoolKey -> String Source # showList :: [VerificationKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (VerificationKey a) | |||||
Defined in Cardano.Api.Keys.Class
proxyToAsType :: Proxy (VerificationKey a) -> AsType (VerificationKey a) # | |||||
SerialiseAsBech32 (VerificationKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
SerialiseAsBech32 (VerificationKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey PaymentExtendedKey) | |||||
SerialiseAsBech32 (VerificationKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
SerialiseAsCBOR (VerificationKey ByronKeyLegacy) | |||||
SerialiseAsCBOR (VerificationKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
SerialiseAsCBOR (VerificationKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdKey) | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotKey) | |||||
SerialiseAsCBOR (VerificationKey DRepExtendedKey) | |||||
SerialiseAsCBOR (VerificationKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateKey) | |||||
SerialiseAsCBOR (VerificationKey GenesisExtendedKey) | |||||
SerialiseAsCBOR (VerificationKey GenesisKey) | |||||
SerialiseAsCBOR (VerificationKey GenesisUTxOKey) | |||||
SerialiseAsCBOR (VerificationKey PaymentExtendedKey) | |||||
SerialiseAsCBOR (VerificationKey PaymentKey) | |||||
SerialiseAsCBOR (VerificationKey StakeExtendedKey) | |||||
SerialiseAsCBOR (VerificationKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey StakePoolKey) | |||||
SerialiseAsRawBytes (VerificationKey ByronKey) | |||||
SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) | |||||
SerialiseAsRawBytes (VerificationKey KesKey) | |||||
SerialiseAsRawBytes (VerificationKey VrfKey) | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdKey) | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotKey) | |||||
SerialiseAsRawBytes (VerificationKey DRepExtendedKey) | |||||
SerialiseAsRawBytes (VerificationKey DRepKey) | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) | |||||
SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) | |||||
SerialiseAsRawBytes (VerificationKey GenesisKey) | |||||
SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) | |||||
SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) | |||||
SerialiseAsRawBytes (VerificationKey PaymentKey) | |||||
SerialiseAsRawBytes (VerificationKey StakeExtendedKey) | |||||
SerialiseAsRawBytes (VerificationKey StakeKey) | |||||
SerialiseAsRawBytes (VerificationKey StakePoolKey) | |||||
HasTextEnvelope (VerificationKey ByronKey) | |||||
HasTextEnvelope (VerificationKey ByronKeyLegacy) | |||||
HasTextEnvelope (VerificationKey KesKey) | |||||
HasTextEnvelope (VerificationKey VrfKey) | |||||
HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) | |||||
HasTextEnvelope (VerificationKey CommitteeColdKey) | |||||
HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) | |||||
HasTextEnvelope (VerificationKey CommitteeHotKey) | |||||
HasTextEnvelope (VerificationKey DRepExtendedKey) | |||||
HasTextEnvelope (VerificationKey DRepKey) | |||||
HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) | |||||
HasTextEnvelope (VerificationKey GenesisDelegateKey) | |||||
HasTextEnvelope (VerificationKey GenesisExtendedKey) | |||||
HasTextEnvelope (VerificationKey GenesisKey) | |||||
HasTextEnvelope (VerificationKey GenesisUTxOKey) | |||||
HasTextEnvelope (VerificationKey PaymentExtendedKey) | |||||
HasTextEnvelope (VerificationKey PaymentKey) | |||||
HasTextEnvelope (VerificationKey StakeExtendedKey) | |||||
HasTextEnvelope (VerificationKey StakeKey) | |||||
HasTextEnvelope (VerificationKey StakePoolKey) | |||||
FromCBOR (VerificationKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
FromCBOR (VerificationKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron fromCBOR :: Decoder s (VerificationKey ByronKeyLegacy) Source # label :: Proxy (VerificationKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (VerificationKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
FromCBOR (VerificationKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
FromCBOR (VerificationKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey CommitteeHotExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (VerificationKey CommitteeHotKey) Source # label :: Proxy (VerificationKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (VerificationKey DRepExtendedKey) Source # label :: Proxy (VerificationKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey GenesisDelegateExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey GenesisDelegateKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey GenesisExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (VerificationKey GenesisKey) Source # label :: Proxy (VerificationKey GenesisKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (VerificationKey GenesisUTxOKey) Source # label :: Proxy (VerificationKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (VerificationKey PaymentExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (VerificationKey PaymentKey) Source # label :: Proxy (VerificationKey PaymentKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (VerificationKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (VerificationKey StakePoolKey) Source # label :: Proxy (VerificationKey StakePoolKey) -> Text Source # | |||||
ToCBOR (VerificationKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
ToCBOR (VerificationKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron 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) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
ToCBOR (VerificationKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
ToCBOR (VerificationKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
ToCBOR (VerificationKey GenesisDelegateExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
ToCBOR (VerificationKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Byron (==) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # (/=) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # | |||||
Eq (VerificationKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
Eq (VerificationKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos (==) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # (/=) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # | |||||
Eq (VerificationKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos (==) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # (/=) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # | |||||
Eq (VerificationKey CommitteeColdExtendedKey) | |||||
Eq (VerificationKey CommitteeColdKey) | |||||
Eq (VerificationKey CommitteeHotExtendedKey) | |||||
Eq (VerificationKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Eq (VerificationKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Eq (VerificationKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley (==) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # (/=) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # | |||||
Eq (VerificationKey GenesisDelegateExtendedKey) | |||||
Eq (VerificationKey GenesisDelegateKey) | |||||
Eq (VerificationKey GenesisExtendedKey) | |||||
Eq (VerificationKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Eq (VerificationKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Eq (VerificationKey PaymentExtendedKey) | |||||
Eq (VerificationKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Eq (VerificationKey StakeExtendedKey) | |||||
Eq (VerificationKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley (==) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # (/=) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # | |||||
Eq (VerificationKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey ByronKey | |||||
Defined in Cardano.Api.Keys.Byron | |||||
newtype VerificationKey ByronKeyLegacy | |||||
Defined in Cardano.Api.Keys.Byron | |||||
newtype VerificationKey KesKey | |||||
Defined in Cardano.Api.Keys.Praos | |||||
newtype VerificationKey VrfKey | |||||
Defined in Cardano.Api.Keys.Praos | |||||
newtype VerificationKey CommitteeColdExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey CommitteeColdKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey CommitteeHotExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey CommitteeHotKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey DRepExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey DRepKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey GenesisExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey GenesisKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey GenesisUTxOKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey PaymentExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey PaymentKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey StakeExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey StakeKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype VerificationKey StakePoolKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
data AsType (VerificationKey a) | |||||
Defined in Cardano.Api.Keys.Class |
data family SigningKey keyrole #
Instances
IsString (SigningKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron fromString :: String -> SigningKey ByronKey Source # | |||||
IsString (SigningKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
IsString (SigningKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> SigningKey KesKey Source # | |||||
IsString (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> SigningKey VrfKey Source # | |||||
IsString (SigningKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey CommitteeHotExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromString :: String -> SigningKey DRepKey Source # | |||||
IsString (SigningKey GenesisDelegateExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey GenesisDelegateKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey GenesisExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromString :: String -> SigningKey GenesisKey Source # | |||||
IsString (SigningKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey PaymentExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromString :: String -> SigningKey PaymentKey Source # | |||||
IsString (SigningKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
IsString (SigningKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromString :: String -> SigningKey StakeKey Source # | |||||
IsString (SigningKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (SigningKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
Show (SigningKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron showsPrec :: Int -> SigningKey ByronKeyLegacy -> ShowS Source # show :: SigningKey ByronKeyLegacy -> String Source # showList :: [SigningKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (SigningKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
Show (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
Show (SigningKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (SigningKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey CommitteeColdKey -> ShowS Source # show :: SigningKey CommitteeColdKey -> String Source # showList :: [SigningKey CommitteeColdKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeHotExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (SigningKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey CommitteeHotKey -> ShowS Source # show :: SigningKey CommitteeHotKey -> String Source # showList :: [SigningKey CommitteeHotKey] -> ShowS Source # | |||||
Show (SigningKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey DRepExtendedKey -> ShowS Source # show :: SigningKey DRepExtendedKey -> String Source # showList :: [SigningKey DRepExtendedKey] -> ShowS Source # | |||||
Show (SigningKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (SigningKey GenesisDelegateExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (SigningKey GenesisDelegateKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS Source # show :: SigningKey GenesisDelegateKey -> String Source # showList :: [SigningKey GenesisDelegateKey] -> ShowS Source # | |||||
Show (SigningKey GenesisExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS Source # show :: SigningKey GenesisExtendedKey -> String Source # showList :: [SigningKey GenesisExtendedKey] -> ShowS Source # | |||||
Show (SigningKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey GenesisKey -> ShowS Source # show :: SigningKey GenesisKey -> String Source # showList :: [SigningKey GenesisKey] -> ShowS Source # | |||||
Show (SigningKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS Source # show :: SigningKey GenesisUTxOKey -> String Source # showList :: [SigningKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (SigningKey PaymentExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS Source # show :: SigningKey PaymentExtendedKey -> String Source # showList :: [SigningKey PaymentExtendedKey] -> ShowS Source # | |||||
Show (SigningKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey PaymentKey -> ShowS Source # show :: SigningKey PaymentKey -> String Source # showList :: [SigningKey PaymentKey] -> ShowS Source # | |||||
Show (SigningKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS Source # show :: SigningKey StakeExtendedKey -> String Source # showList :: [SigningKey StakeExtendedKey] -> ShowS Source # | |||||
Show (SigningKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
Show (SigningKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey StakePoolKey -> ShowS Source # show :: SigningKey StakePoolKey -> String Source # showList :: [SigningKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (SigningKey a) | |||||
Defined in Cardano.Api.Keys.Class
proxyToAsType :: Proxy (SigningKey a) -> AsType (SigningKey a) # | |||||
SerialiseAsBech32 (SigningKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos bech32PrefixFor :: SigningKey KesKey -> Text bech32PrefixesPermitted :: AsType (SigningKey KesKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos bech32PrefixFor :: SigningKey VrfKey -> Text bech32PrefixesPermitted :: AsType (SigningKey VrfKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) | |||||
SerialiseAsBech32 (SigningKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) | |||||
SerialiseAsBech32 (SigningKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (SigningKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (SigningKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: SigningKey DRepKey -> Text bech32PrefixesPermitted :: AsType (SigningKey DRepKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey PaymentExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (SigningKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: SigningKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsBech32 (SigningKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: SigningKey StakeKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
SerialiseAsCBOR (SigningKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
SerialiseAsCBOR (SigningKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: SigningKey KesKey -> ByteString # deserialiseFromCBOR :: AsType (SigningKey KesKey) -> ByteString -> Either DecoderError (SigningKey KesKey) # | |||||
SerialiseAsCBOR (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: SigningKey VrfKey -> ByteString # deserialiseFromCBOR :: AsType (SigningKey VrfKey) -> ByteString -> Either DecoderError (SigningKey VrfKey) # | |||||
SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) | |||||
SerialiseAsCBOR (SigningKey CommitteeColdKey) | |||||
SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) | |||||
SerialiseAsCBOR (SigningKey CommitteeHotKey) | |||||
SerialiseAsCBOR (SigningKey DRepExtendedKey) | |||||
SerialiseAsCBOR (SigningKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateKey) | |||||
SerialiseAsCBOR (SigningKey GenesisExtendedKey) | |||||
SerialiseAsCBOR (SigningKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey PaymentExtendedKey) | |||||
SerialiseAsCBOR (SigningKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey StakeExtendedKey) | |||||
SerialiseAsCBOR (SigningKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
SerialiseAsRawBytes (SigningKey ByronKeyLegacy) | |||||
SerialiseAsRawBytes (SigningKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
SerialiseAsRawBytes (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdKey) | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotKey) | |||||
SerialiseAsRawBytes (SigningKey DRepExtendedKey) | |||||
SerialiseAsRawBytes (SigningKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateKey) | |||||
SerialiseAsRawBytes (SigningKey GenesisExtendedKey) | |||||
SerialiseAsRawBytes (SigningKey GenesisKey) | |||||
SerialiseAsRawBytes (SigningKey GenesisUTxOKey) | |||||
SerialiseAsRawBytes (SigningKey PaymentExtendedKey) | |||||
SerialiseAsRawBytes (SigningKey PaymentKey) | |||||
SerialiseAsRawBytes (SigningKey StakeExtendedKey) | |||||
SerialiseAsRawBytes (SigningKey StakeKey) | |||||
SerialiseAsRawBytes (SigningKey StakePoolKey) | |||||
HasTextEnvelope (SigningKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
HasTextEnvelope (SigningKey ByronKeyLegacy) | |||||
HasTextEnvelope (SigningKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
HasTextEnvelope (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
HasTextEnvelope (SigningKey CommitteeColdExtendedKey) | |||||
HasTextEnvelope (SigningKey CommitteeColdKey) | |||||
HasTextEnvelope (SigningKey CommitteeHotExtendedKey) | |||||
HasTextEnvelope (SigningKey CommitteeHotKey) | |||||
HasTextEnvelope (SigningKey DRepExtendedKey) | |||||
HasTextEnvelope (SigningKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) | |||||
HasTextEnvelope (SigningKey GenesisDelegateKey) | |||||
HasTextEnvelope (SigningKey GenesisExtendedKey) | |||||
HasTextEnvelope (SigningKey GenesisKey) | |||||
HasTextEnvelope (SigningKey GenesisUTxOKey) | |||||
HasTextEnvelope (SigningKey PaymentExtendedKey) | |||||
HasTextEnvelope (SigningKey PaymentKey) | |||||
HasTextEnvelope (SigningKey StakeExtendedKey) | |||||
HasTextEnvelope (SigningKey StakeKey) | |||||
HasTextEnvelope (SigningKey StakePoolKey) | |||||
FromCBOR (SigningKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
FromCBOR (SigningKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron fromCBOR :: Decoder s (SigningKey ByronKeyLegacy) Source # label :: Proxy (SigningKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (SigningKey KesKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
FromCBOR (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
FromCBOR (SigningKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (SigningKey CommitteeColdKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey CommitteeColdKey) Source # label :: Proxy (SigningKey CommitteeColdKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeHotExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (SigningKey CommitteeHotKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey CommitteeHotKey) Source # label :: Proxy (SigningKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey DRepExtendedKey) Source # label :: Proxy (SigningKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (SigningKey GenesisDelegateExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (SigningKey GenesisDelegateKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey GenesisDelegateKey) Source # label :: Proxy (SigningKey GenesisDelegateKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey GenesisExtendedKey) Source # label :: Proxy (SigningKey GenesisExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey GenesisKey) Source # label :: Proxy (SigningKey GenesisKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisUTxOKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey GenesisUTxOKey) Source # label :: Proxy (SigningKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey PaymentExtendedKey) Source # label :: Proxy (SigningKey PaymentExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey PaymentKey) Source # label :: Proxy (SigningKey PaymentKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey StakeExtendedKey) Source # label :: Proxy (SigningKey StakeExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeKey) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
FromCBOR (SigningKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey StakePoolKey) Source # label :: Proxy (SigningKey StakePoolKey) -> Text Source # | |||||
ToCBOR (SigningKey ByronKey) | |||||
Defined in Cardano.Api.Keys.Byron | |||||
ToCBOR (SigningKey ByronKeyLegacy) | |||||
Defined in Cardano.Api.Keys.Byron 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) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
ToCBOR (SigningKey VrfKey) | |||||
Defined in Cardano.Api.Keys.Praos | |||||
ToCBOR (SigningKey CommitteeColdExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
ToCBOR (SigningKey GenesisDelegateExtendedKey) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
ToCBOR (SigningKey StakePoolKey) | |||||
Defined in Cardano.Api.Keys.Shelley 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 | |||||
Defined in Cardano.Api.Keys.Byron | |||||
newtype SigningKey ByronKeyLegacy | |||||
Defined in Cardano.Api.Keys.Byron | |||||
newtype SigningKey KesKey | |||||
Defined in Cardano.Api.Keys.Praos | |||||
newtype SigningKey VrfKey | |||||
Defined in Cardano.Api.Keys.Praos | |||||
newtype SigningKey CommitteeColdExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey CommitteeColdKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey CommitteeHotExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey CommitteeHotKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey DRepExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey DRepKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey GenesisExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey GenesisKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey GenesisUTxOKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey PaymentExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey PaymentKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey StakeExtendedKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey StakeKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
newtype SigningKey StakePoolKey | |||||
Defined in Cardano.Api.Keys.Shelley | |||||
data AsType (SigningKey a) | |||||
Defined in Cardano.Api.Keys.Class |
Hashes
Instances
FromJSON (Hash BlockHeader) | |
Defined in Cardano.Api.Block parseJSON :: Value -> Parser (Hash BlockHeader) parseJSONList :: Value -> Parser [Hash BlockHeader] omittedField :: Maybe (Hash BlockHeader) | |
FromJSON (Hash DRepKey) | |
Defined in Cardano.Api.Keys.Shelley parseJSON :: Value -> Parser (Hash DRepKey) parseJSONList :: Value -> Parser [Hash DRepKey] omittedField :: Maybe (Hash DRepKey) | |
FromJSON (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley parseJSON :: Value -> Parser (Hash GenesisKey) parseJSONList :: Value -> Parser [Hash GenesisKey] omittedField :: Maybe (Hash GenesisKey) | |
FromJSON (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley parseJSON :: Value -> Parser (Hash PaymentKey) parseJSONList :: Value -> Parser [Hash PaymentKey] omittedField :: Maybe (Hash PaymentKey) | |
FromJSON (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley parseJSON :: Value -> Parser (Hash StakePoolKey) parseJSONList :: Value -> Parser [Hash StakePoolKey] | |
FromJSON (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData parseJSON :: Value -> Parser (Hash ScriptData) parseJSONList :: Value -> Parser [Hash ScriptData] omittedField :: Maybe (Hash ScriptData) | |
FromJSONKey (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData fromJSONKey :: FromJSONKeyFunction (Hash ScriptData) fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData] | |
ToJSON (Hash BlockHeader) | |
Defined in Cardano.Api.Block toJSON :: Hash BlockHeader -> Value toEncoding :: Hash BlockHeader -> Encoding toJSONList :: [Hash BlockHeader] -> Value toEncodingList :: [Hash BlockHeader] -> Encoding omitField :: Hash BlockHeader -> Bool | |
ToJSON (Hash DRepKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToJSON (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley toJSON :: Hash GenesisKey -> Value toEncoding :: Hash GenesisKey -> Encoding toJSONList :: [Hash GenesisKey] -> Value toEncodingList :: [Hash GenesisKey] -> Encoding omitField :: Hash GenesisKey -> Bool | |
ToJSON (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley toJSON :: Hash PaymentKey -> Value toEncoding :: Hash PaymentKey -> Encoding toJSONList :: [Hash PaymentKey] -> Value toEncodingList :: [Hash PaymentKey] -> Encoding omitField :: Hash PaymentKey -> Bool | |
ToJSON (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley toJSON :: Hash StakePoolKey -> Value toEncoding :: Hash StakePoolKey -> Encoding toJSONList :: [Hash StakePoolKey] -> Value toEncodingList :: [Hash StakePoolKey] -> Encoding omitField :: Hash StakePoolKey -> Bool | |
ToJSON (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData 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.Keys.Shelley | |
ToJSONKey (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley toJSONKey :: ToJSONKeyFunction (Hash GenesisKey) toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey] | |
ToJSONKey (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley toJSONKey :: ToJSONKeyFunction (Hash PaymentKey) toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey] | |
ToJSONKey (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey] | |
ToJSONKey (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData toJSONKey :: ToJSONKeyFunction (Hash ScriptData) toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData] | |
IsString (Hash BlockHeader) | |
Defined in Cardano.Api.Block fromString :: String -> Hash BlockHeader Source # | |
IsString (Hash GovernancePoll) | |
Defined in Cardano.Api.Governance.Poll fromString :: String -> Hash GovernancePoll Source # | |
IsString (Hash ByronKey) | |
Defined in Cardano.Api.Keys.Byron | |
IsString (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Keys.Byron fromString :: String -> Hash ByronKeyLegacy Source # | |
IsString (Hash KesKey) | |
Defined in Cardano.Api.Keys.Praos | |
IsString (Hash VrfKey) | |
Defined in Cardano.Api.Keys.Praos | |
IsString (Hash CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash CommitteeColdKey Source # | |
IsString (Hash CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash CommitteeHotKey Source # | |
IsString (Hash DRepExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash DRepExtendedKey Source # | |
IsString (Hash DRepKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash GenesisDelegateKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash GenesisExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash GenesisKey Source # | |
IsString (Hash GenesisUTxOKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash GenesisUTxOKey Source # | |
IsString (Hash PaymentExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash PaymentKey Source # | |
IsString (Hash StakeExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash StakeExtendedKey Source # | |
IsString (Hash StakeKey) | |
Defined in Cardano.Api.Keys.Shelley | |
IsString (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash StakePoolKey Source # | |
IsString (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData fromString :: String -> Hash ScriptData Source # | |
Show (Hash BlockHeader) | |
Defined in Cardano.Api.Block | |
Show (Hash DRepMetadata) | |
Defined in Cardano.Api.DRepMetadata | |
Show (Hash GovernancePoll) | |
Defined in Cardano.Api.Governance.Poll | |
Show (Hash ByronKey) | |
Show (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Keys.Byron | |
Show (Hash KesKey) | |
Show (Hash VrfKey) | |
Show (Hash CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash DRepExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash DRepKey) | |
Show (Hash GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash GenesisDelegateKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash GenesisExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash GenesisUTxOKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash PaymentExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash StakeExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash StakeKey) | |
Show (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Show (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData | |
Show (Hash StakePoolMetadata) | |
Defined in Cardano.Api.StakePoolMetadata | |
HasTypeProxy a => HasTypeProxy (Hash a) | |
Defined in Cardano.Api.Hash | |
SerialiseAsBech32 (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: Hash CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeColdKey) -> [Text] | |
SerialiseAsBech32 (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: Hash CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeHotKey) -> [Text] | |
SerialiseAsBech32 (Hash DRepKey) | |
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: Hash DRepKey -> Text bech32PrefixesPermitted :: AsType (Hash DRepKey) -> [Text] | |
SerialiseAsBech32 (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: Hash StakePoolKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text] | |
SerialiseAsCBOR (Hash ByronKey) | |
Defined in Cardano.Api.Keys.Byron serialiseToCBOR :: Hash ByronKey -> ByteString # deserialiseFromCBOR :: AsType (Hash ByronKey) -> ByteString -> Either DecoderError (Hash ByronKey) # | |
SerialiseAsCBOR (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Keys.Byron | |
SerialiseAsCBOR (Hash KesKey) | |
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: Hash KesKey -> ByteString # deserialiseFromCBOR :: AsType (Hash KesKey) -> ByteString -> Either DecoderError (Hash KesKey) # | |
SerialiseAsCBOR (Hash VrfKey) | |
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: Hash VrfKey -> ByteString # deserialiseFromCBOR :: AsType (Hash VrfKey) -> ByteString -> Either DecoderError (Hash VrfKey) # | |
SerialiseAsCBOR (Hash CommitteeColdExtendedKey) | |
SerialiseAsCBOR (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash CommitteeHotExtendedKey) | |
SerialiseAsCBOR (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash DRepExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash DRepKey) | |
Defined in Cardano.Api.Keys.Shelley serialiseToCBOR :: Hash DRepKey -> ByteString # deserialiseFromCBOR :: AsType (Hash DRepKey) -> ByteString -> Either DecoderError (Hash DRepKey) # | |
SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) | |
SerialiseAsCBOR (Hash GenesisDelegateKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash GenesisExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley serialiseToCBOR :: Hash GenesisKey -> ByteString # deserialiseFromCBOR :: AsType (Hash GenesisKey) -> ByteString -> Either DecoderError (Hash GenesisKey) # | |
SerialiseAsCBOR (Hash GenesisUTxOKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash PaymentExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley serialiseToCBOR :: Hash PaymentKey -> ByteString # deserialiseFromCBOR :: AsType (Hash PaymentKey) -> ByteString -> Either DecoderError (Hash PaymentKey) # | |
SerialiseAsCBOR (Hash StakeExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsCBOR (Hash StakeKey) | |
Defined in Cardano.Api.Keys.Shelley serialiseToCBOR :: Hash StakeKey -> ByteString # deserialiseFromCBOR :: AsType (Hash StakeKey) -> ByteString -> Either DecoderError (Hash StakeKey) # | |
SerialiseAsCBOR (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley serialiseToCBOR :: Hash StakePoolKey -> ByteString # deserialiseFromCBOR :: AsType (Hash StakePoolKey) -> ByteString -> Either DecoderError (Hash StakePoolKey) # | |
SerialiseAsRawBytes (Hash BlockHeader) | |
Defined in Cardano.Api.Block | |
SerialiseAsRawBytes (Hash DRepMetadata) | |
Defined in Cardano.Api.DRepMetadata | |
SerialiseAsRawBytes (Hash GovernancePoll) | |
SerialiseAsRawBytes (Hash ByronKey) | |
Defined in Cardano.Api.Keys.Byron | |
SerialiseAsRawBytes (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Keys.Byron | |
SerialiseAsRawBytes (Hash KesKey) | |
Defined in Cardano.Api.Keys.Praos | |
SerialiseAsRawBytes (Hash VrfKey) | |
Defined in Cardano.Api.Keys.Praos | |
SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) | |
SerialiseAsRawBytes (Hash CommitteeColdKey) | |
SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) | |
SerialiseAsRawBytes (Hash CommitteeHotKey) | |
SerialiseAsRawBytes (Hash DRepExtendedKey) | |
SerialiseAsRawBytes (Hash DRepKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) | |
SerialiseAsRawBytes (Hash GenesisDelegateKey) | |
SerialiseAsRawBytes (Hash GenesisExtendedKey) | |
SerialiseAsRawBytes (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsRawBytes (Hash GenesisUTxOKey) | |
SerialiseAsRawBytes (Hash PaymentExtendedKey) | |
SerialiseAsRawBytes (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsRawBytes (Hash StakeExtendedKey) | |
SerialiseAsRawBytes (Hash StakeKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsRawBytes (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley | |
SerialiseAsRawBytes (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData | |
SerialiseAsRawBytes (Hash StakePoolMetadata) | |
FromCBOR (Hash ByronKey) | |
FromCBOR (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Keys.Byron | |
FromCBOR (Hash KesKey) | |
FromCBOR (Hash VrfKey) | |
FromCBOR (Hash CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash DRepExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash DRepKey) | |
FromCBOR (Hash GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash GenesisDelegateKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash GenesisExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash GenesisUTxOKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash PaymentExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash StakeExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
FromCBOR (Hash StakeKey) | |
FromCBOR (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash ByronKey) | |
ToCBOR (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Keys.Byron | |
ToCBOR (Hash KesKey) | |
ToCBOR (Hash VrfKey) | |
ToCBOR (Hash CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash DRepExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash DRepKey) | |
ToCBOR (Hash GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash GenesisExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash GenesisUTxOKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash PaymentExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash StakeExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
ToCBOR (Hash StakeKey) | |
ToCBOR (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Eq (Hash BlockHeader) | |
Defined in Cardano.Api.Block (==) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (/=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # | |
Eq (Hash DRepMetadata) | |
Defined in Cardano.Api.DRepMetadata (==) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # (/=) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # | |
Eq (Hash GovernancePoll) | |
Defined in Cardano.Api.Governance.Poll (==) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (/=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # | |
Eq (Hash ByronKey) | |
Eq (Hash ByronKeyLegacy) | |
Defined in Cardano.Api.Keys.Byron (==) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (/=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # | |
Eq (Hash KesKey) | |
Eq (Hash VrfKey) | |
Eq (Hash CommitteeColdExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Eq (Hash CommitteeColdKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (/=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # | |
Eq (Hash CommitteeHotExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Eq (Hash CommitteeHotKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (/=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # | |
Eq (Hash DRepExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (/=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # | |
Eq (Hash DRepKey) | |
Eq (Hash GenesisDelegateExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley | |
Eq (Hash GenesisDelegateKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (/=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # | |
Eq (Hash GenesisExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (/=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # | |
Eq (Hash GenesisKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (/=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # | |
Eq (Hash GenesisUTxOKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (/=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # | |
Eq (Hash PaymentExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (/=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # | |
Eq (Hash PaymentKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (/=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # | |
Eq (Hash StakeExtendedKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (/=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # | |
Eq (Hash StakeKey) | |
Eq (Hash StakePoolKey) | |
Defined in Cardano.Api.Keys.Shelley (==) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (/=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # | |
Eq (Hash ScriptData) | |
Defined in Cardano.Api.ScriptData (==) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (/=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # | |
Eq (Hash StakePoolMetadata) | |
Defined in Cardano.Api.StakePoolMetadata (==) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # (/=) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # | |
Ord (Hash BlockHeader) | |
Defined in Cardano.Api.Block 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) | |
Defined in Cardano.Api.Governance.Poll 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) | |
Defined in Cardano.Api.Keys.Byron 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) | |
Defined in Cardano.Api.Keys.Byron 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) | |
Defined in Cardano.Api.Keys.Praos 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) | |
Defined in Cardano.Api.Keys.Praos 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.Keys.Shelley 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) | |
Defined in Cardano.Api.ScriptData 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 | |
Defined in Cardano.Api.Block | |
newtype Hash DRepMetadata | |
Defined in Cardano.Api.DRepMetadata | |
newtype Hash GovernancePoll | |
Defined in Cardano.Api.Governance.Poll | |
newtype Hash ByronKey | |
Defined in Cardano.Api.Keys.Byron | |
newtype Hash ByronKeyLegacy | |
Defined in Cardano.Api.Keys.Byron | |
newtype Hash KesKey | |
Defined in Cardano.Api.Keys.Praos | |
newtype Hash VrfKey | |
Defined in Cardano.Api.Keys.Praos | |
newtype Hash CommitteeColdExtendedKey | |
newtype Hash CommitteeColdKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash CommitteeHotExtendedKey | |
newtype Hash CommitteeHotKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash DRepExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash DRepKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash GenesisDelegateExtendedKey | |
newtype Hash GenesisDelegateKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash GenesisExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash GenesisKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash GenesisUTxOKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash PaymentExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash PaymentKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash StakeExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash StakeKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash StakePoolKey | |
Defined in Cardano.Api.Keys.Shelley | |
newtype Hash ScriptData | |
Defined in Cardano.Api.ScriptData | |
newtype Hash StakePoolMetadata | |
Defined in Cardano.Api.StakePoolMetadata | |
data AsType (Hash a) | |
Defined in Cardano.Api.Hash |
Type Proxies
Instances
data AsType AddressAny | |
Defined in Cardano.Api.Address | |
data AsType ByronAddr | |
Defined in Cardano.Api.Address | |
data AsType ShelleyAddr | |
Defined in Cardano.Api.Address | |
data AsType StakeAddress | |
Defined in Cardano.Api.Address | |
data AsType BlockHeader | |
Defined in Cardano.Api.Block | |
data AsType DRepMetadata | |
Defined in Cardano.Api.DRepMetadata | |
data AsType AllegraEra | |
Defined in Cardano.Api.Eras.Core | |
data AsType AlonzoEra | |
Defined in Cardano.Api.Eras.Core | |
data AsType BabbageEra | |
Defined in Cardano.Api.Eras.Core | |
data AsType ByronEra | |
Defined in Cardano.Api.Eras.Core | |
data AsType ConwayEra | |
Defined in Cardano.Api.Eras.Core | |
data AsType MaryEra | |
Defined in Cardano.Api.Eras.Core | |
data AsType ShelleyEra | |
Defined in Cardano.Api.Eras.Core | |
data AsType GovernancePoll | |
Defined in Cardano.Api.Governance.Poll | |
data AsType GovernancePollAnswer | |
Defined in Cardano.Api.Governance.Poll | |
data AsType ByronKey | |
Defined in Cardano.Api.Keys.Byron | |
data AsType ByronKeyLegacy | |
Defined in Cardano.Api.Keys.Byron | |
data AsType KesKey | |
Defined in Cardano.Api.Keys.Praos | |
data AsType VrfKey | |
Defined in Cardano.Api.Keys.Praos | |
data AsType CommitteeColdExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType CommitteeColdKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType CommitteeHotExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType CommitteeHotKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType DRepExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType DRepKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType GenesisDelegateExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType GenesisDelegateKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType GenesisExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType GenesisKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType GenesisUTxOKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType PaymentExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType PaymentKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType StakeExtendedKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType StakeKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType StakePoolKey | |
Defined in Cardano.Api.Keys.Shelley | |
data AsType OperationalCertificate | |
data AsType OperationalCertificateIssueCounter | |
data AsType PraosNonce | |
Defined in Cardano.Api.ProtocolParameters | |
data AsType UpdateProposal | |
Defined in Cardano.Api.ProtocolParameters | |
data AsType PlutusScriptV1 | |
Defined in Cardano.Api.Script | |
data AsType PlutusScriptV2 | |
Defined in Cardano.Api.Script | |
data AsType PlutusScriptV3 | |
Defined in Cardano.Api.Script | |
data AsType ScriptHash | |
Defined in Cardano.Api.Script | |
data AsType ScriptInAnyLang | |
Defined in Cardano.Api.Script | |
data AsType SimpleScript' | |
Defined in Cardano.Api.Script | |
data AsType HashableScriptData | |
Defined in Cardano.Api.ScriptData | |
data AsType ScriptData | |
Defined in Cardano.Api.ScriptData | |
data AsType TextEnvelope | |
Defined in Cardano.Api.SerialiseTextEnvelope | |
data AsType ByronUpdateProposal | |
Defined in Cardano.Api.SpecialByron | |
data AsType ByronVote | |
Defined in Cardano.Api.SpecialByron | |
data AsType StakePoolMetadata | |
Defined in Cardano.Api.StakePoolMetadata | |
data AsType TxId | |
Defined in Cardano.Api.TxIn | |
data AsType TxMetadata | |
Defined in Cardano.Api.TxMetadata | |
data AsType AssetName | |
Defined in Cardano.Api.Value | |
data AsType PolicyId | |
Defined in Cardano.Api.Value | |
data AsType (Address addrtype) | |
Defined in Cardano.Api.Address | |
data AsType (AddressInEra era) | |
Defined in Cardano.Api.Address | |
data AsType (Certificate era) | |
Defined in Cardano.Api.Certificate | |
data AsType (Proposal era) | |
data AsType (VotingProcedure era) | |
data AsType (VotingProcedures era) | |
data AsType (Hash a) | |
Defined in Cardano.Api.Hash | |
data AsType (SigningKey a) | |
Defined in Cardano.Api.Keys.Class | |
data AsType (VerificationKey a) | |
Defined in Cardano.Api.Keys.Class | |
data AsType (PlutusScript lang) | |
Defined in Cardano.Api.Script | |
data AsType (Script lang) | |
Defined in Cardano.Api.Script | |
data AsType (ScriptInEra era) | |
Defined in Cardano.Api.Script | |
data AsType (KeyWitness era) | |
Defined in Cardano.Api.Tx.Sign | |
data AsType (Tx era) | |
Defined in Cardano.Api.Tx.Sign | |
data AsType (TxBody era) | |
Defined in Cardano.Api.Tx.Sign |
Payment addresses
Constructing and inspecting Shelley payment addresses
ShelleyAddress :: Network -> PaymentCredential StandardCrypto -> StakeReference StandardCrypto -> Address ShelleyAddr |
Instances
FromJSON (Address ByronAddr) | |||||
Defined in Cardano.Api.Address | |||||
FromJSON (Address ShelleyAddr) | |||||
Defined in Cardano.Api.Address parseJSON :: Value -> Parser (Address ShelleyAddr) parseJSONList :: Value -> Parser [Address ShelleyAddr] | |||||
ToJSON (Address ByronAddr) | |||||
Defined in Cardano.Api.Address | |||||
ToJSON (Address ShelleyAddr) | |||||
Defined in Cardano.Api.Address toJSON :: Address ShelleyAddr -> Value toEncoding :: Address ShelleyAddr -> Encoding toJSONList :: [Address ShelleyAddr] -> Value toEncodingList :: [Address ShelleyAddr] -> Encoding omitField :: Address ShelleyAddr -> Bool | |||||
Show (Address addrtype) | |||||
SerialiseAddress (Address ByronAddr) | |||||
Defined in Cardano.Api.Address | |||||
SerialiseAddress (Address ShelleyAddr) | |||||
Defined in Cardano.Api.Address serialiseAddress :: Address ShelleyAddr -> Text # deserialiseAddress :: AsType (Address ShelleyAddr) -> Text -> Maybe (Address ShelleyAddr) # | |||||
HasTypeProxy addrtype => HasTypeProxy (Address addrtype) | |||||
Defined in Cardano.Api.Address
| |||||
SerialiseAsBech32 (Address ShelleyAddr) | |||||
Defined in Cardano.Api.Address bech32PrefixFor :: Address ShelleyAddr -> Text bech32PrefixesPermitted :: AsType (Address ShelleyAddr) -> [Text] | |||||
SerialiseAsRawBytes (Address ByronAddr) | |||||
Defined in Cardano.Api.Address | |||||
SerialiseAsRawBytes (Address ShelleyAddr) | |||||
Defined in Cardano.Api.Address | |||||
NFData (Address addrtype) | |||||
Defined in Cardano.Api.Address | |||||
Eq (Address addrtype) | |||||
Ord (Address addrtype) | |||||
Defined in Cardano.Api.Address 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) | |||||
Defined in Cardano.Api.Address |
toShelleyAddr :: AddressInEra era -> Addr StandardCrypto #
fromShelleyAddr :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era #
fromShelleyAddrIsSbe :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era #
Stake addresses
data PaymentCredential #
Instances
Show PaymentCredential | |
Defined in Cardano.Api.Address | |
Eq PaymentCredential | |
Defined in Cardano.Api.Address (==) :: PaymentCredential -> PaymentCredential -> Bool Source # (/=) :: PaymentCredential -> PaymentCredential -> Bool Source # | |
Ord PaymentCredential | |
Defined in Cardano.Api.Address compare :: PaymentCredential -> PaymentCredential -> Ordering Source # (<) :: PaymentCredential -> PaymentCredential -> Bool Source # (<=) :: PaymentCredential -> PaymentCredential -> Bool Source # (>) :: PaymentCredential -> PaymentCredential -> Bool Source # (>=) :: PaymentCredential -> PaymentCredential -> Bool Source # max :: PaymentCredential -> PaymentCredential -> PaymentCredential Source # min :: PaymentCredential -> PaymentCredential -> PaymentCredential Source # |
data StakeAddress where #
Instances
FromJSON StakeAddress | |||||
Defined in Cardano.Api.Address parseJSON :: Value -> Parser StakeAddress parseJSONList :: Value -> Parser [StakeAddress] | |||||
ToJSON StakeAddress | |||||
Defined in Cardano.Api.Address toJSON :: StakeAddress -> Value toEncoding :: StakeAddress -> Encoding toJSONList :: [StakeAddress] -> Value toEncodingList :: [StakeAddress] -> Encoding omitField :: StakeAddress -> Bool | |||||
Show StakeAddress | |||||
Defined in Cardano.Api.Address | |||||
SerialiseAddress StakeAddress | |||||
Defined in Cardano.Api.Address serialiseAddress :: StakeAddress -> Text # deserialiseAddress :: AsType StakeAddress -> Text -> Maybe StakeAddress # | |||||
HasTypeProxy StakeAddress | |||||
Defined in Cardano.Api.Address
| |||||
SerialiseAsBech32 StakeAddress | |||||
Defined in Cardano.Api.Address bech32PrefixFor :: StakeAddress -> Text | |||||
SerialiseAsRawBytes StakeAddress | |||||
Eq StakeAddress | |||||
Defined in Cardano.Api.Address (==) :: StakeAddress -> StakeAddress -> Bool Source # (/=) :: StakeAddress -> StakeAddress -> Bool Source # | |||||
Ord StakeAddress | |||||
Defined in Cardano.Api.Address 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 | |||||
Defined in Cardano.Api.Address |
data StakeAddressReference #
Instances
Show StakeAddressReference | |
Defined in Cardano.Api.Address | |
Eq StakeAddressReference | |
Defined in Cardano.Api.Address |
data StakeCredential #
Instances
ToJSON StakeCredential | |
Defined in Cardano.Api.Address toJSON :: StakeCredential -> Value toEncoding :: StakeCredential -> Encoding toJSONList :: [StakeCredential] -> Value toEncodingList :: [StakeCredential] -> Encoding omitField :: StakeCredential -> Bool | |
Show StakeCredential | |
Defined in Cardano.Api.Address | |
Eq StakeCredential | |
Defined in Cardano.Api.Address (==) :: StakeCredential -> StakeCredential -> Bool Source # (/=) :: StakeCredential -> StakeCredential -> Bool Source # | |
Ord StakeCredential | |
Defined in Cardano.Api.Address 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
ShelleyTxBody :: forall era. ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> [Script (ShelleyLedgerEra era)] -> TxBodyScriptData era -> Maybe (TxAuxData (ShelleyLedgerEra era)) -> TxScriptValidity era -> TxBody era |
Instances
Show (TxBody era) | |||||
HasTypeProxy era => HasTypeProxy (TxBody era) | |||||
Defined in Cardano.Api.Tx.Sign
| |||||
IsShelleyBasedEra era => SerialiseAsCBOR (TxBody era) | |||||
Defined in Cardano.Api.Tx.Sign serialiseToCBOR :: TxBody era -> ByteString # deserialiseFromCBOR :: AsType (TxBody era) -> ByteString -> Either DecoderError (TxBody era) # | |||||
IsShelleyBasedEra era => HasTextEnvelope (TxBody era) | |||||
Defined in Cardano.Api.Tx.Sign textEnvelopeType :: AsType (TxBody era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: TxBody era -> TextEnvelopeDescr # | |||||
Eq (TxBody era) | |||||
data AsType (TxBody era) | |||||
Defined in Cardano.Api.Tx.Sign |
Instances
FromJSON TxId | |
Defined in Cardano.Api.TxIn | |
FromJSONKey TxId | |
Defined in Cardano.Api.TxIn fromJSONKey :: FromJSONKeyFunction TxId fromJSONKeyList :: FromJSONKeyFunction [TxId] | |
ToJSON TxId | |
Defined in Cardano.Api.TxIn | |
ToJSONKey TxId | |
Defined in Cardano.Api.TxIn toJSONKey :: ToJSONKeyFunction TxId toJSONKeyList :: ToJSONKeyFunction [TxId] | |
IsString TxId | |
Defined in Cardano.Api.TxIn fromString :: String -> TxId Source # | |
Show TxId | |
HasTypeProxy TxId | |
Defined in Cardano.Api.TxIn | |
SerialiseAsRawBytes TxId | |
Defined in Cardano.Api.TxIn | |
Eq TxId | |
Ord TxId | |
data AsType TxId | |
Defined in Cardano.Api.TxIn |
toShelleyTxId :: TxId -> TxId StandardCrypto #
fromShelleyTxId :: TxId StandardCrypto -> TxId #
getTxIdShelley :: (EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto, EraTxBody (ShelleyLedgerEra era)) => ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> TxId #
Instances
FromJSON TxIn | |
Defined in Cardano.Api.TxIn | |
FromJSONKey TxIn | |
Defined in Cardano.Api.TxIn fromJSONKey :: FromJSONKeyFunction TxIn fromJSONKeyList :: FromJSONKeyFunction [TxIn] | |
ToJSON TxIn | |
Defined in Cardano.Api.TxIn | |
ToJSONKey TxIn | |
Defined in Cardano.Api.TxIn toJSONKey :: ToJSONKeyFunction TxIn toJSONKeyList :: ToJSONKeyFunction [TxIn] | |
Show TxIn | |
Eq TxIn | |
Ord TxIn | |
Pretty TxIn | |
Defined in Cardano.Api.TxIn |
toShelleyTxIn :: TxIn -> TxIn StandardCrypto #
fromShelleyTxIn :: TxIn StandardCrypto -> TxIn #
TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) (ReferenceScript era) |
Instances
IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) | |
Defined in Cardano.Api.Tx.Body parseJSON :: Value -> Parser (TxOut CtxTx era) parseJSONList :: Value -> Parser [TxOut CtxTx era] omittedField :: Maybe (TxOut CtxTx era) | |
IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) | |
Defined in Cardano.Api.Tx.Body parseJSON :: Value -> Parser (TxOut CtxUTxO era) parseJSONList :: Value -> Parser [TxOut CtxUTxO era] omittedField :: Maybe (TxOut CtxUTxO era) | |
IsCardanoEra era => ToJSON (TxOut ctx era) | |
Defined in Cardano.Api.Tx.Body toJSON :: TxOut ctx era -> Value toEncoding :: TxOut ctx era -> Encoding toJSONList :: [TxOut ctx era] -> Value toEncodingList :: [TxOut ctx era] -> Encoding | |
Show (TxOut ctx era) | |
Eq (TxOut ctx era) | |
toShelleyTxOut :: (HasCallStack, ShelleyLedgerEra era ~ ledgerera) => ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera #
fromShelleyTxOut :: ShelleyBasedEra era -> TxOut (ShelleyLedgerEra era) -> TxOut ctx era #
Instances
FromJSON TxIx | |
Defined in Cardano.Api.TxIn | |
ToJSON TxIx | |
Defined in Cardano.Api.TxIn | |
Enum TxIx | |
Show TxIx | |
Eq TxIx | |
Ord TxIx | |
toMaryValue :: Value -> MaryValue StandardCrypto #
calcMinimumDeposit :: Value -> Lovelace -> Lovelace #
Arbitrary signing
signArbitraryBytesKes :: SigningKey KesKey -> Period -> ByteString -> SignedKES (KES StandardCrypto) ByteString #
Signing transactions
Creating transaction witnesses one by one, or all in one go.
ShelleyTx :: forall era. ShelleyBasedEra era -> Tx (ShelleyLedgerEra era) -> Tx era |
Instances
Show (InAnyShelleyBasedEra Tx) | |
Defined in Cardano.Api.Tx.Sign | |
Show (InAnyCardanoEra Tx) | |
Defined in Cardano.Api.Tx.Sign | |
Show (Tx era) | |
HasTypeProxy era => HasTypeProxy (Tx era) | |
Defined in Cardano.Api.Tx.Sign | |
IsShelleyBasedEra era => SerialiseAsCBOR (Tx era) | |
Defined in Cardano.Api.Tx.Sign serialiseToCBOR :: Tx era -> ByteString # deserialiseFromCBOR :: AsType (Tx era) -> ByteString -> Either DecoderError (Tx era) # | |
IsShelleyBasedEra era => HasTextEnvelope (Tx era) | |
Defined in Cardano.Api.Tx.Sign textEnvelopeType :: AsType (Tx era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: Tx era -> TextEnvelopeDescr # | |
Eq (InAnyShelleyBasedEra Tx) | |
Defined in Cardano.Api.Tx.Sign (==) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # (/=) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # | |
Eq (InAnyCardanoEra Tx) | |
Defined in Cardano.Api.Tx.Sign (==) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # (/=) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # | |
Eq (Tx era) | |
data AsType (Tx era) | |
Defined in Cardano.Api.Tx.Sign |
Incremental signing and separate witnesses
data KeyWitness era where #
ShelleyBootstrapWitness :: forall era. ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era | |
ShelleyKeyWitness :: forall era. ShelleyBasedEra era -> WitVKey 'Witness StandardCrypto -> KeyWitness era |
Instances
Show (KeyWitness era) | |||||
Defined in Cardano.Api.Tx.Sign | |||||
HasTypeProxy era => HasTypeProxy (KeyWitness era) | |||||
Defined in Cardano.Api.Tx.Sign
proxyToAsType :: Proxy (KeyWitness era) -> AsType (KeyWitness era) # | |||||
IsCardanoEra era => SerialiseAsCBOR (KeyWitness era) | |||||
Defined in Cardano.Api.Tx.Sign serialiseToCBOR :: KeyWitness era -> ByteString # deserialiseFromCBOR :: AsType (KeyWitness era) -> ByteString -> Either DecoderError (KeyWitness era) # | |||||
IsCardanoEra era => HasTextEnvelope (KeyWitness era) | |||||
Defined in Cardano.Api.Tx.Sign textEnvelopeType :: AsType (KeyWitness era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: KeyWitness era -> TextEnvelopeDescr # | |||||
Eq (KeyWitness era) | |||||
Defined in Cardano.Api.Tx.Sign (==) :: KeyWitness era -> KeyWitness era -> Bool Source # (/=) :: KeyWitness era -> KeyWitness era -> Bool Source # | |||||
data AsType (KeyWitness era) | |||||
Defined in Cardano.Api.Tx.Sign |
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 #
getTxBodyAndWitnesses :: Tx era -> (TxBody era, [KeyWitness era]) #
makeShelleySignature :: SignableRepresentation tosign => tosign -> ShelleySigningKey -> SignedDSIGN StandardCrypto tosign #
Blocks
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 #
Transaction metadata
Embedding additional structured data within transactions.
Protocol parameters
newtype LedgerProtocolParameters era #
Instances
IsShelleyBasedEra era => Show (LedgerProtocolParameters era) | |
Defined in Cardano.Api.ProtocolParameters | |
IsShelleyBasedEra era => Eq (LedgerProtocolParameters era) | |
Defined in Cardano.Api.ProtocolParameters (==) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # (/=) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # |
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 |
Instances
Show (EraBasedProtocolParametersUpdate era) | |
Defined in Cardano.Api.ProtocolParameters |
data CommonProtocolParametersUpdate #
CommonProtocolParametersUpdate | |
|
Instances
data AlonzoOnwardsPParams ledgerera #
Instances
Show (AlonzoOnwardsPParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
newtype DeprecatedAfterBabbagePParams ledgerera #
Instances
Show (DeprecatedAfterBabbagePParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
newtype DeprecatedAfterMaryPParams ledgerera #
Instances
Show (DeprecatedAfterMaryPParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
data ShelleyToAlonzoPParams ledgerera #
Instances
Show (ShelleyToAlonzoPParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
newtype IntroducedInBabbagePParams era #
Instances
Show (IntroducedInBabbagePParams era) | |
Defined in Cardano.Api.ProtocolParameters |
data IntroducedInConwayPParams era #
IntroducedInConwayPParams | |
|
Instances
Show (IntroducedInConwayPParams era) | |
Defined in Cardano.Api.ProtocolParameters |
createEraBasedProtocolParamUpdate :: ShelleyBasedEra era -> EraBasedProtocolParametersUpdate era -> PParamsUpdate (ShelleyLedgerEra era) #
convertToLedgerProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersConversionError (LedgerProtocolParameters era) #
data ProtocolParameters #
ProtocolParameters | |
|
Instances
FromJSON ProtocolParameters | |||||
Defined in Cardano.Api.ProtocolParameters parseJSON :: Value -> Parser ProtocolParameters parseJSONList :: Value -> Parser [ProtocolParameters] | |||||
ToJSON ProtocolParameters | |||||
Defined in Cardano.Api.ProtocolParameters toJSON :: ProtocolParameters -> Value toEncoding :: ProtocolParameters -> Encoding toJSONList :: [ProtocolParameters] -> Value toEncodingList :: [ProtocolParameters] -> Encoding omitField :: ProtocolParameters -> Bool | |||||
Generic ProtocolParameters | |||||
Defined in Cardano.Api.ProtocolParameters
from :: ProtocolParameters -> Rep ProtocolParameters x Source # to :: Rep ProtocolParameters x -> ProtocolParameters Source # | |||||
Show ProtocolParameters | |||||
Defined in Cardano.Api.ProtocolParameters | |||||
Eq ProtocolParameters | |||||
Defined in Cardano.Api.ProtocolParameters (==) :: ProtocolParameters -> ProtocolParameters -> Bool Source # (/=) :: ProtocolParameters -> ProtocolParameters -> Bool Source # | |||||
type Rep ProtocolParameters | |||||
Defined in Cardano.Api.ProtocolParameters type Rep ProtocolParameters = D1 ('MetaData "ProtocolParameters" "Cardano.Api.ProtocolParameters" "cardano-api-10.3.0.0-inplace-internal" '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 Natural) :*: 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 () #
data ProtocolParametersError #
Instances
Show ProtocolParametersError | |
Defined in Cardano.Api.ProtocolParameters | |
Error ProtocolParametersError | |
Defined in Cardano.Api.ProtocolParameters prettyError :: ProtocolParametersError -> Doc ann # |
Scripts
fromShelleyBasedScript :: ShelleyBasedEra era -> Script (ShelleyLedgerEra era) -> ScriptInEra era #
toShelleyScript :: ScriptInEra era -> Script (ShelleyLedgerEra era) #
toShelleyMultiSig :: SimpleScript -> Either MultiSigError (MultiSig (ShelleyLedgerEra ShelleyEra)) #
toAllegraTimelock :: (AllegraEraScript era, EraCrypto era ~ StandardCrypto, NativeScript era ~ Timelock era) => SimpleScript -> NativeScript era #
fromAllegraTimelock :: (AllegraEraScript era, EraCrypto era ~ StandardCrypto) => NativeScript era -> SimpleScript #
data PlutusScript lang where #
PlutusScriptSerialised :: forall lang. ShortByteString -> PlutusScript lang |
Instances
Show (PlutusScript lang) | |||||
Defined in Cardano.Api.Script | |||||
HasTypeProxy lang => HasTypeProxy (PlutusScript lang) | |||||
Defined in Cardano.Api.Script
proxyToAsType :: Proxy (PlutusScript lang) -> AsType (PlutusScript lang) # | |||||
HasTypeProxy lang => SerialiseAsCBOR (PlutusScript lang) | |||||
Defined in Cardano.Api.Script serialiseToCBOR :: PlutusScript lang -> ByteString # deserialiseFromCBOR :: AsType (PlutusScript lang) -> ByteString -> Either DecoderError (PlutusScript lang) # | |||||
HasTypeProxy lang => SerialiseAsRawBytes (PlutusScript lang) | |||||
Defined in Cardano.Api.Script serialiseToRawBytes :: PlutusScript lang -> ByteString # deserialiseFromRawBytes :: AsType (PlutusScript lang) -> ByteString -> Either SerialiseAsRawBytesError (PlutusScript lang) # | |||||
IsPlutusScriptLanguage lang => HasTextEnvelope (PlutusScript lang) | |||||
Defined in Cardano.Api.Script textEnvelopeType :: AsType (PlutusScript lang) -> TextEnvelopeType # textEnvelopeDefaultDescr :: PlutusScript lang -> TextEnvelopeDescr # | |||||
HasTypeProxy lang => FromCBOR (PlutusScript lang) | |||||
Defined in Cardano.Api.Script | |||||
HasTypeProxy lang => ToCBOR (PlutusScript lang) | |||||
Defined in Cardano.Api.Script toCBOR :: PlutusScript lang -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PlutusScript lang) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PlutusScript lang] -> Size Source # | |||||
Eq (PlutusScript lang) | |||||
Defined in Cardano.Api.Script (==) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (/=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # | |||||
Ord (PlutusScript lang) | |||||
Defined in Cardano.Api.Script 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) | |||||
Defined in Cardano.Api.Script |
data PlutusScriptOrReferenceInput lang #
PScript (PlutusScript lang) | |
PReferenceScript TxIn |
Instances
Show (PlutusScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script | |
Eq (PlutusScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script (==) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # (/=) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # |
data SimpleScriptOrReferenceInput lang #
Instances
Show (SimpleScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script | |
Eq (SimpleScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script (==) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # (/=) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # |
toPlutusData :: ScriptData -> Data #
fromPlutusData :: Data -> ScriptData #
toAlonzoData :: Era ledgerera => HashableScriptData -> Data ledgerera #
fromAlonzoData :: Data ledgerera -> HashableScriptData #
toScriptIndex :: AlonzoEraOnwards era -> PlutusPurpose AsIx (ShelleyLedgerEra era) -> ScriptWitnessIndex #
scriptDataToJsonDetailedSchema :: HashableScriptData -> Value #
Reference Scripts
data ReferenceScript era where #
ReferenceScript :: forall era. BabbageEraOnwards era -> ScriptInAnyLang -> ReferenceScript era | |
ReferenceScriptNone :: forall era. ReferenceScript era |
Instances
IsCardanoEra era => FromJSON (ReferenceScript era) | |
Defined in Cardano.Api.Script parseJSON :: Value -> Parser (ReferenceScript era) parseJSONList :: Value -> Parser [ReferenceScript era] omittedField :: Maybe (ReferenceScript era) | |
IsCardanoEra era => ToJSON (ReferenceScript era) | |
Defined in Cardano.Api.Script toJSON :: ReferenceScript era -> Value toEncoding :: ReferenceScript era -> Encoding toJSONList :: [ReferenceScript era] -> Value toEncodingList :: [ReferenceScript era] -> Encoding omitField :: ReferenceScript era -> Bool | |
Show (ReferenceScript era) | |
Defined in Cardano.Api.Script | |
Eq (ReferenceScript era) | |
Defined in Cardano.Api.Script (==) :: ReferenceScript era -> ReferenceScript era -> Bool Source # (/=) :: ReferenceScript era -> ReferenceScript era -> Bool Source # |
refScriptToShelleyScript :: ShelleyBasedEra era -> ReferenceScript era -> StrictMaybe (Script (ShelleyLedgerEra era)) #
Certificates
data Certificate era where #
ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era | |
ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era |
Instances
Show (Certificate era) | |||||
Defined in Cardano.Api.Certificate | |||||
Typeable era => HasTypeProxy (Certificate era) | |||||
Defined in Cardano.Api.Certificate
proxyToAsType :: Proxy (Certificate era) -> AsType (Certificate era) # | |||||
IsShelleyBasedEra era => SerialiseAsCBOR (Certificate era) | |||||
Defined in Cardano.Api.Certificate serialiseToCBOR :: Certificate era -> ByteString # deserialiseFromCBOR :: AsType (Certificate era) -> ByteString -> Either DecoderError (Certificate era) # | |||||
IsShelleyBasedEra era => HasTextEnvelope (Certificate era) | |||||
Defined in Cardano.Api.Certificate textEnvelopeType :: AsType (Certificate era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: Certificate era -> TextEnvelopeDescr # | |||||
IsShelleyBasedEra era => FromCBOR (Certificate era) | |||||
Defined in Cardano.Api.Certificate | |||||
IsShelleyBasedEra era => ToCBOR (Certificate era) | |||||
Defined in Cardano.Api.Certificate 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) | |||||
Defined in Cardano.Api.Certificate (==) :: Certificate era -> Certificate era -> Bool Source # (/=) :: Certificate era -> Certificate era -> Bool Source # | |||||
data AsType (Certificate era) | |||||
Defined in Cardano.Api.Certificate |
toShelleyCertificate :: Certificate era -> TxCert (ShelleyLedgerEra era) #
fromShelleyCertificate :: ShelleyBasedEra era -> TxCert (ShelleyLedgerEra era) -> Certificate era #
Operational certificates
data OperationalCertificate #
Instances
Show OperationalCertificate | |
Defined in Cardano.Api.OperationalCertificate | |
HasTypeProxy OperationalCertificate | |
SerialiseAsCBOR OperationalCertificate | |
HasTextEnvelope OperationalCertificate | |
FromCBOR OperationalCertificate | |
Defined in Cardano.Api.OperationalCertificate | |
ToCBOR OperationalCertificate | |
Defined in Cardano.Api.OperationalCertificate 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 | |
Defined in Cardano.Api.OperationalCertificate | |
data AsType OperationalCertificate | |
data OperationalCertificateIssueCounter #
Instances
Show OperationalCertificateIssueCounter | |
HasTypeProxy OperationalCertificateIssueCounter | |
SerialiseAsCBOR OperationalCertificateIssueCounter | |
HasTextEnvelope OperationalCertificateIssueCounter | |
FromCBOR OperationalCertificateIssueCounter | |
ToCBOR OperationalCertificateIssueCounter | |
Defined in Cardano.Api.OperationalCertificate 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 | |
data AsType OperationalCertificateIssueCounter | |
data OperationalCertIssueError #
Instances
Stake Pool
data StakePoolMetadata #
Instances
FromJSON StakePoolMetadata | |||||
Defined in Cardano.Api.StakePoolMetadata parseJSON :: Value -> Parser StakePoolMetadata parseJSONList :: Value -> Parser [StakePoolMetadata] | |||||
Show StakePoolMetadata | |||||
Defined in Cardano.Api.StakePoolMetadata | |||||
HasTypeProxy StakePoolMetadata | |||||
Defined in Cardano.Api.StakePoolMetadata
| |||||
Eq StakePoolMetadata | |||||
Defined in Cardano.Api.StakePoolMetadata (==) :: StakePoolMetadata -> StakePoolMetadata -> Bool Source # (/=) :: StakePoolMetadata -> StakePoolMetadata -> Bool Source # | |||||
Show (Hash StakePoolMetadata) | |||||
Defined in Cardano.Api.StakePoolMetadata | |||||
SerialiseAsRawBytes (Hash StakePoolMetadata) | |||||
Eq (Hash StakePoolMetadata) | |||||
Defined in Cardano.Api.StakePoolMetadata (==) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # (/=) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # | |||||
data AsType StakePoolMetadata | |||||
Defined in Cardano.Api.StakePoolMetadata | |||||
newtype Hash StakePoolMetadata | |||||
Defined in Cardano.Api.StakePoolMetadata |
stakePoolName :: StakePoolMetadata -> Text #
data StakePoolMetadataReference #
Instances
Show StakePoolMetadataReference | |
Defined in Cardano.Api.Certificate | |
Eq StakePoolMetadataReference | |
Defined in Cardano.Api.Certificate |
data StakePoolParameters #
StakePoolParameters PoolId (Hash VrfKey) Coin Rational StakeAddress Coin [Hash StakeKey] [StakePoolRelay] (Maybe StakePoolMetadataReference) |
Instances
Show StakePoolParameters | |
Defined in Cardano.Api.Certificate | |
Eq StakePoolParameters | |
Defined in Cardano.Api.Certificate (==) :: StakePoolParameters -> StakePoolParameters -> Bool Source # (/=) :: StakePoolParameters -> StakePoolParameters -> Bool Source # |
stakePoolOwners :: StakePoolParameters -> [Hash StakeKey] #
data StakePoolRelay #
StakePoolRelayIp (Maybe IPv4) (Maybe IPv6) (Maybe PortNumber) | |
StakePoolRelayDnsARecord ByteString (Maybe PortNumber) | |
StakePoolRelayDnsSrvRecord ByteString |
Instances
Show StakePoolRelay | |
Defined in Cardano.Api.Certificate | |
Eq StakePoolRelay | |
Defined in Cardano.Api.Certificate (==) :: 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 parseJSON :: Value -> Parser EpochNo parseJSONList :: Value -> Parser [EpochNo] | |||||
ToJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot toEncoding :: EpochNo -> Encoding toJSONList :: [EpochNo] -> Value toEncodingList :: [EpochNo] -> Encoding | |||||
Enum EpochNo | |||||
Defined in Cardano.Slotting.Slot 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
| |||||
Show EpochNo | |||||
FromCBOR EpochNo | |||||
ToCBOR EpochNo | |||||
DecCBOR EpochNo | |||||
EncCBOR EpochNo | |||||
NFData EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
Eq EpochNo | |||||
Ord EpochNo | |||||
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-1881c023e0886f672d28a4c45a256e973fe8d96632667e110b19ce5f49f52117" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
Governance Actions
createAnchor :: Url -> ByteString -> Anchor StandardCrypto #
createPreviousGovernanceActionId :: forall era (r :: GovActionPurpose). EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto => TxId -> Word16 -> GovPurposeId r (ShelleyLedgerEra era) #
DRep
newtype DRepMetadata #
Instances
Show DRepMetadata | |||||
Defined in Cardano.Api.DRepMetadata | |||||
HasTypeProxy DRepMetadata | |||||
Defined in Cardano.Api.DRepMetadata
| |||||
Eq DRepMetadata | |||||
Defined in Cardano.Api.DRepMetadata (==) :: DRepMetadata -> DRepMetadata -> Bool Source # (/=) :: DRepMetadata -> DRepMetadata -> Bool Source # | |||||
Show (Hash DRepMetadata) | |||||
Defined in Cardano.Api.DRepMetadata | |||||
SerialiseAsRawBytes (Hash DRepMetadata) | |||||
Defined in Cardano.Api.DRepMetadata | |||||
Eq (Hash DRepMetadata) | |||||
Defined in Cardano.Api.DRepMetadata (==) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # (/=) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # | |||||
data AsType DRepMetadata | |||||
Defined in Cardano.Api.DRepMetadata | |||||
newtype Hash DRepMetadata | |||||
Defined in Cardano.Api.DRepMetadata |
data DRepMetadataReference #
Instances
Show DRepMetadataReference | |
Defined in Cardano.Api.Certificate | |
Eq DRepMetadataReference | |
Defined in Cardano.Api.Certificate |
Stake pool operator's keys
data StakePoolKey #
Instances
HasTypeProxy StakePoolKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
| |||||||||
Key StakePoolKey | |||||||||
Defined in Cardano.Api.Keys.Shelley
getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey # deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey # deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word # verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey # | |||||||||
CastSigningKeyRole GenesisDelegateKey StakePoolKey | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
CastVerificationKeyRole GenesisDelegateKey StakePoolKey | |||||||||
CastVerificationKeyRole StakePoolKey StakeKey | |||||||||
FromJSON (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley parseJSON :: Value -> Parser (Hash StakePoolKey) parseJSONList :: Value -> Parser [Hash StakePoolKey] | |||||||||
ToJSON (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley toJSON :: Hash StakePoolKey -> Value toEncoding :: Hash StakePoolKey -> Encoding toJSONList :: [Hash StakePoolKey] -> Value toEncodingList :: [Hash StakePoolKey] -> Encoding omitField :: Hash StakePoolKey -> Bool | |||||||||
ToJSONKey (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey] | |||||||||
IsString (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley fromString :: String -> Hash StakePoolKey Source # | |||||||||
IsString (SigningKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
IsString (VerificationKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
Show (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
Show (SigningKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> SigningKey StakePoolKey -> ShowS Source # show :: SigningKey StakePoolKey -> String Source # showList :: [SigningKey StakePoolKey] -> ShowS Source # | |||||||||
Show (VerificationKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS Source # show :: VerificationKey StakePoolKey -> String Source # showList :: [VerificationKey StakePoolKey] -> ShowS Source # | |||||||||
SerialiseAsBech32 (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley bech32PrefixFor :: Hash StakePoolKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text] | |||||||||
SerialiseAsBech32 (SigningKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
SerialiseAsBech32 (VerificationKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
SerialiseAsCBOR (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley serialiseToCBOR :: Hash StakePoolKey -> ByteString # deserialiseFromCBOR :: AsType (Hash StakePoolKey) -> ByteString -> Either DecoderError (Hash StakePoolKey) # | |||||||||
SerialiseAsCBOR (SigningKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
SerialiseAsCBOR (VerificationKey StakePoolKey) | |||||||||
SerialiseAsRawBytes (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
SerialiseAsRawBytes (SigningKey StakePoolKey) | |||||||||
SerialiseAsRawBytes (VerificationKey StakePoolKey) | |||||||||
HasTextEnvelope (SigningKey StakePoolKey) | |||||||||
HasTextEnvelope (VerificationKey StakePoolKey) | |||||||||
FromCBOR (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
FromCBOR (SigningKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (SigningKey StakePoolKey) Source # label :: Proxy (SigningKey StakePoolKey) -> Text Source # | |||||||||
FromCBOR (VerificationKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley fromCBOR :: Decoder s (VerificationKey StakePoolKey) Source # label :: Proxy (VerificationKey StakePoolKey) -> Text Source # | |||||||||
ToCBOR (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
ToCBOR (SigningKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||||||
Defined in Cardano.Api.Keys.Shelley 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) | |||||||||
Defined in Cardano.Api.Keys.Shelley (==) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (/=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # | |||||||||
Eq (VerificationKey StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
Ord (Hash StakePoolKey) | |||||||||
Defined in Cardano.Api.Keys.Shelley 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 | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
newtype Hash StakePoolKey | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
newtype SigningKey StakePoolKey | |||||||||
Defined in Cardano.Api.Keys.Shelley | |||||||||
newtype VerificationKey StakePoolKey | |||||||||
Defined in Cardano.Api.Keys.Shelley |
type PoolId = Hash StakePoolKey #
KES keys
Instances
HasTypeProxy KesKey | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
Key KesKey | |||||||||
Defined in Cardano.Api.Keys.Praos
| |||||||||
IsString (Hash KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
IsString (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> SigningKey KesKey Source # | |||||||||
IsString (VerificationKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> VerificationKey KesKey Source # | |||||||||
Show (Hash KesKey) | |||||||||
Show (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
Show (VerificationKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsBech32 (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos bech32PrefixFor :: SigningKey KesKey -> Text bech32PrefixesPermitted :: AsType (SigningKey KesKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsCBOR (Hash KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: Hash KesKey -> ByteString # deserialiseFromCBOR :: AsType (Hash KesKey) -> ByteString -> Either DecoderError (Hash KesKey) # | |||||||||
SerialiseAsCBOR (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: SigningKey KesKey -> ByteString # deserialiseFromCBOR :: AsType (SigningKey KesKey) -> ByteString -> Either DecoderError (SigningKey KesKey) # | |||||||||
SerialiseAsCBOR (VerificationKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsRawBytes (Hash KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsRawBytes (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsRawBytes (VerificationKey KesKey) | |||||||||
HasTextEnvelope (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
HasTextEnvelope (VerificationKey KesKey) | |||||||||
FromCBOR (Hash KesKey) | |||||||||
FromCBOR (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
FromCBOR (VerificationKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
ToCBOR (Hash KesKey) | |||||||||
ToCBOR (SigningKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
ToCBOR (VerificationKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
Eq (Hash KesKey) | |||||||||
Eq (VerificationKey KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos (==) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # (/=) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # | |||||||||
Ord (Hash KesKey) | |||||||||
Defined in Cardano.Api.Keys.Praos 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 | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
newtype Hash KesKey | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
newtype SigningKey KesKey | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
newtype VerificationKey KesKey | |||||||||
Defined in Cardano.Api.Keys.Praos |
Instances
Generic KESPeriod | |||||
Defined in Cardano.Protocol.TPraos.OCert
| |||||
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.2.0.1-36a38d414efb56377eae90ac31718c4f07f2456cde048c9a33e05edf1216b626" 'True) (C1 ('MetaCons "KESPeriod" 'PrefixI 'True) (S1 ('MetaSel ('Just "unKESPeriod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))) |
VRF keys
Instances
HasTypeProxy VrfKey | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
Key VrfKey | |||||||||
Defined in Cardano.Api.Keys.Praos
| |||||||||
IsString (Hash VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
IsString (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> SigningKey VrfKey Source # | |||||||||
IsString (VerificationKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos fromString :: String -> VerificationKey VrfKey Source # | |||||||||
Show (Hash VrfKey) | |||||||||
Show (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
Show (VerificationKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsBech32 (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos bech32PrefixFor :: SigningKey VrfKey -> Text bech32PrefixesPermitted :: AsType (SigningKey VrfKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsCBOR (Hash VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: Hash VrfKey -> ByteString # deserialiseFromCBOR :: AsType (Hash VrfKey) -> ByteString -> Either DecoderError (Hash VrfKey) # | |||||||||
SerialiseAsCBOR (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos serialiseToCBOR :: SigningKey VrfKey -> ByteString # deserialiseFromCBOR :: AsType (SigningKey VrfKey) -> ByteString -> Either DecoderError (SigningKey VrfKey) # | |||||||||
SerialiseAsCBOR (VerificationKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsRawBytes (Hash VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsRawBytes (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
SerialiseAsRawBytes (VerificationKey VrfKey) | |||||||||
HasTextEnvelope (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
HasTextEnvelope (VerificationKey VrfKey) | |||||||||
FromCBOR (Hash VrfKey) | |||||||||
FromCBOR (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
FromCBOR (VerificationKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
ToCBOR (Hash VrfKey) | |||||||||
ToCBOR (SigningKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
ToCBOR (VerificationKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
Eq (Hash VrfKey) | |||||||||
Eq (VerificationKey VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos (==) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # (/=) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # | |||||||||
Ord (Hash VrfKey) | |||||||||
Defined in Cardano.Api.Keys.Praos 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 | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
newtype Hash VrfKey | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
newtype SigningKey VrfKey | |||||||||
Defined in Cardano.Api.Keys.Praos | |||||||||
newtype VerificationKey VrfKey | |||||||||
Defined in Cardano.Api.Keys.Praos |
Low level protocol interaction with a Cardano node
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 ())) |
Shelley based eras
type family ShelleyLedgerEra era = (ledgerera :: Type) | ledgerera -> era where ... #
Ledger Events
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 | |
EpochBoundaryRatificationState AnyRatificationState |
Instances
Show LedgerEvent | |
Defined in Cardano.Api.LedgerEvents.LedgerEvent |
data AnyProposals #
EraPParams era => AnyProposals (Proposals era) |
Instances
Show AnyProposals | |
Defined in Cardano.Api.LedgerEvents.LedgerEvent |
data AnyRatificationState #
EraPParams era => AnyRatificationState (RatifyState era) |
Instances
data MIRDistributionDetails #
Instances
data PoolReapDetails #
PoolReapDetails | |
|
Instances
toLedgerEvent :: ConvertLedgerEvent blk => WrapLedgerEvent blk -> Maybe LedgerEvent #
Local State Query
newtype DebugLedgerState era #
Instances
IsShelleyBasedEra era => ToJSON (DebugLedgerState era) | |
Defined in Cardano.Api.Query.Types 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) | |
Defined in Cardano.Api.Query.Types |
decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either (ByteString, DecoderError) (DebugLedgerState era) #
newtype ProtocolState era #
decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era)) #
newtype SerialisedDebugLedgerState era #
newtype CurrentEpochState era #
newtype SerialisedCurrentEpochState era #
decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState 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 #
newtype SerialisedPoolDistribution 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 #
decodeStakeSnapshot :: FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era) #
Instances
(IsShelleyBasedEra era, FromJSON (TxOut CtxUTxO era)) => FromJSON (UTxO era) | |
Defined in Cardano.Api.Query parseJSON :: Value -> Parser (UTxO era) parseJSONList :: Value -> Parser [UTxO era] omittedField :: Maybe (UTxO era) | |
IsCardanoEra era => ToJSON (UTxO era) | |
Defined in Cardano.Api.Query toEncoding :: UTxO era -> Encoding toJSONList :: [UTxO era] -> Value toEncodingList :: [UTxO era] -> Encoding | |
Show (UTxO era) | |
Eq (UTxO era) | |
data AcquiringFailure #
Instances
Show AcquiringFailure | |
Defined in Cardano.Api.IPC | |
Eq AcquiringFailure | |
Defined in Cardano.Api.IPC (==) :: AcquiringFailure -> AcquiringFailure -> Bool Source # (/=) :: AcquiringFailure -> AcquiringFailure -> Bool Source # |
newtype SystemStart Source #
System start
Slots are counted from the system start.
Instances
FromJSON SystemStart | |||||
Defined in Cardano.Slotting.Time parseJSON :: Value -> Parser SystemStart parseJSONList :: Value -> Parser [SystemStart] | |||||
ToJSON SystemStart | |||||
Defined in Cardano.Slotting.Time toJSON :: SystemStart -> Value toEncoding :: SystemStart -> Encoding toJSONList :: [SystemStart] -> Value toEncodingList :: [SystemStart] -> Encoding omitField :: SystemStart -> Bool | |||||
Generic SystemStart | |||||
Defined in Cardano.Slotting.Time
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 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 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 (==) :: SystemStart -> SystemStart -> Bool Source # (/=) :: SystemStart -> SystemStart -> Bool Source # | |||||
NoThunks SystemStart | |||||
Defined in Cardano.Slotting.Time noThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy SystemStart -> String # | |||||
Serialise SystemStart | |||||
Defined in Cardano.Slotting.Time 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-1881c023e0886f672d28a4c45a256e973fe8d96632667e110b19ce5f49f52117" 'True) (C1 ('MetaCons "SystemStart" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSystemStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime))) |
Governance
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 #
Instances
Show (GovernanceActionId era) | |
IsShelleyBasedEra era => FromCBOR (GovernanceActionId era) | |
IsShelleyBasedEra era => ToCBOR (GovernanceActionId era) | |
Defined in Cardano.Api.Governance.Actions.VotingProcedure 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) | |
Defined in Cardano.Api.Governance.Actions.VotingProcedure (==) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # (/=) :: GovernanceActionId era -> GovernanceActionId era -> Bool Source # | |
Ord (GovernanceActionId era) | |
Defined in Cardano.Api.Governance.Actions.VotingProcedure 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 # |
Instances
IsShelleyBasedEra era => Show (Proposal era) | |
HasTypeProxy era => HasTypeProxy (Proposal era) | |
IsShelleyBasedEra era => SerialiseAsCBOR (Proposal era) | |
Defined in Cardano.Api.Governance.Actions.ProposalProcedure serialiseToCBOR :: Proposal era -> ByteString # deserialiseFromCBOR :: AsType (Proposal era) -> ByteString -> Either DecoderError (Proposal era) # | |
IsShelleyBasedEra era => HasTextEnvelope (Proposal era) | |
Defined in Cardano.Api.Governance.Actions.ProposalProcedure textEnvelopeType :: AsType (Proposal era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: Proposal era -> TextEnvelopeDescr # | |
IsShelleyBasedEra era => FromCBOR (Proposal era) | |
IsShelleyBasedEra era => ToCBOR (Proposal era) | |
IsShelleyBasedEra era => Eq (Proposal era) | |
data AsType (Proposal era) | |
newtype VotingProcedure era #
Instances
Show (VotingProcedure era) | |||||
HasTypeProxy era => HasTypeProxy (VotingProcedure era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure
proxyToAsType :: Proxy (VotingProcedure era) -> AsType (VotingProcedure era) # | |||||
IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedure era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure serialiseToCBOR :: VotingProcedure era -> ByteString # deserialiseFromCBOR :: AsType (VotingProcedure era) -> ByteString -> Either DecoderError (VotingProcedure era) # | |||||
IsShelleyBasedEra era => HasTextEnvelope (VotingProcedure era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure textEnvelopeType :: AsType (VotingProcedure era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: VotingProcedure era -> TextEnvelopeDescr # | |||||
IsShelleyBasedEra era => FromCBOR (VotingProcedure era) | |||||
IsShelleyBasedEra era => ToCBOR (VotingProcedure era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure 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) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure (==) :: VotingProcedure era -> VotingProcedure era -> Bool Source # (/=) :: VotingProcedure era -> VotingProcedure era -> Bool Source # | |||||
data AsType (VotingProcedure era) | |||||
newtype VotingProcedures era #
Instances
Generic (VotingProcedures era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure
from :: VotingProcedures era -> Rep (VotingProcedures era) x Source # to :: Rep (VotingProcedures era) x -> VotingProcedures era Source # | |||||
Show (VotingProcedures era) | |||||
HasTypeProxy era => HasTypeProxy (VotingProcedures era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure
proxyToAsType :: Proxy (VotingProcedures era) -> AsType (VotingProcedures era) # | |||||
IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedures era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure serialiseToCBOR :: VotingProcedures era -> ByteString # deserialiseFromCBOR :: AsType (VotingProcedures era) -> ByteString -> Either DecoderError (VotingProcedures era) # | |||||
IsShelleyBasedEra era => HasTextEnvelope (VotingProcedures era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure textEnvelopeType :: AsType (VotingProcedures era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: VotingProcedures era -> TextEnvelopeDescr # | |||||
IsShelleyBasedEra era => FromCBOR (VotingProcedures era) | |||||
IsShelleyBasedEra era => ToCBOR (VotingProcedures era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure 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) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure (==) :: VotingProcedures era -> VotingProcedures era -> Bool Source # (/=) :: VotingProcedures era -> VotingProcedures era -> Bool Source # | |||||
type Rep (VotingProcedures era) | |||||
Defined in Cardano.Api.Governance.Actions.VotingProcedure type Rep (VotingProcedures era) = D1 ('MetaData "VotingProcedures" "Cardano.Api.Governance.Actions.VotingProcedure" "cardano-api-10.3.0.0-inplace-internal" 'True) (C1 ('MetaCons "VotingProcedures" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVotingProcedures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VotingProcedures (ShelleyLedgerEra era))))) | |||||
data AsType (VotingProcedures era) | |||||
data GovernancePoll #
GovernancePoll | |
|
Instances
Show GovernancePoll | |||||
Defined in Cardano.Api.Governance.Poll | |||||
HasTypeProxy GovernancePoll | |||||
Defined in Cardano.Api.Governance.Poll
| |||||
SerialiseAsCBOR GovernancePoll | |||||
HasTextEnvelope GovernancePoll | |||||
AsTxMetadata GovernancePoll | |||||
Defined in Cardano.Api.Governance.Poll | |||||
Eq GovernancePoll | |||||
Defined in Cardano.Api.Governance.Poll (==) :: GovernancePoll -> GovernancePoll -> Bool Source # (/=) :: GovernancePoll -> GovernancePoll -> Bool Source # | |||||
IsString (Hash GovernancePoll) | |||||
Defined in Cardano.Api.Governance.Poll fromString :: String -> Hash GovernancePoll Source # | |||||
Show (Hash GovernancePoll) | |||||
Defined in Cardano.Api.Governance.Poll | |||||
SerialiseAsRawBytes (Hash GovernancePoll) | |||||
Eq (Hash GovernancePoll) | |||||
Defined in Cardano.Api.Governance.Poll (==) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (/=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # | |||||
Ord (Hash GovernancePoll) | |||||
Defined in Cardano.Api.Governance.Poll 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 | |||||
Defined in Cardano.Api.Governance.Poll | |||||
newtype Hash GovernancePoll | |||||
Defined in Cardano.Api.Governance.Poll |
data GovernancePollAnswer #
Instances
Show GovernancePollAnswer | |||||
Defined in Cardano.Api.Governance.Poll | |||||
HasTypeProxy GovernancePollAnswer | |||||
Defined in Cardano.Api.Governance.Poll
| |||||
SerialiseAsCBOR GovernancePollAnswer | |||||
AsTxMetadata GovernancePollAnswer | |||||
Defined in Cardano.Api.Governance.Poll | |||||
Eq GovernancePollAnswer | |||||
Defined in Cardano.Api.Governance.Poll (==) :: GovernancePollAnswer -> GovernancePollAnswer -> Bool Source # (/=) :: GovernancePollAnswer -> GovernancePollAnswer -> Bool Source # | |||||
data AsType GovernancePollAnswer | |||||
Defined in Cardano.Api.Governance.Poll |
data GovernancePollError #
ErrGovernancePollMismatch GovernancePollMismatchError | |
ErrGovernancePollNoAnswer | |
ErrGovernancePollUnauthenticated | |
ErrGovernancePollMalformedAnswer DecoderError | |
ErrGovernancePollInvalidAnswer GovernancePollInvalidAnswerError |
Instances
Show GovernancePollError | |
Defined in Cardano.Api.Governance.Poll |
Voter (Voter (EraCrypto (ShelleyLedgerEra era))) |
Instances
Show (Voter era) | |
IsShelleyBasedEra era => FromCBOR (Voter era) | |
IsShelleyBasedEra era => ToCBOR (Voter era) | |
Eq (Voter era) | |
Ord (Voter era) | |
createProposalProcedure :: ShelleyBasedEra era -> Network -> Coin -> StakeCredential -> GovernanceAction era -> Anchor StandardCrypto -> Proposal era #
createVotingProcedure :: ConwayEraOnwards era -> Vote -> Maybe (Url, Text) -> VotingProcedure era #
fromProposalProcedure :: ShelleyBasedEra era -> Proposal era -> (Coin, StakeCredential, GovernanceAction era) #
verifyPollAnswer :: GovernancePoll -> InAnyShelleyBasedEra Tx -> Either GovernancePollError [Hash PaymentKey] #
Various calculations
data LeadershipError #
LeaderErrDecodeLedgerStateFailure | |
LeaderErrDecodeProtocolStateFailure (ByteString, DecoderError) | |
LeaderErrDecodeProtocolEpochStateFailure DecoderError | |
LeaderErrGenesisSlot | |
LeaderErrStakePoolHasNoStake PoolId | |
LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo | |
LeaderErrSlotRangeCalculationFailure Text | |
LeaderErrCandidateNonceStillEvolving |
Instances
Show LeadershipError | |
Defined in Cardano.Api.LedgerState | |
Error LeadershipError | |
Defined in Cardano.Api.LedgerState prettyError :: LeadershipError -> Doc ann # |
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) #
Conversions
toConsensusGenTx :: CardanoBlock StandardCrypto ~ block => TxInMode -> GenTx block #
toLedgerNonce :: Maybe PraosNonce -> Nonce #
toShelleyNetwork :: NetworkId -> Network #
fromLedgerPParamsUpdate :: ShelleyBasedEra era -> PParamsUpdate (ShelleyLedgerEra era) -> ProtocolParametersUpdate #
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))]) |
Instances
Show (VotesMergingConflict era) | |