Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api.Byron
Description
This module provides a library interface that is intended to be the complete API for Byron covering everything, including exposing constructors for the lower level types.
Synopsis
- class Pretty a where
- pretty :: a -> Doc ann
- prettyList :: [a] -> Doc ann
- class Monad m => MonadIO (m :: Type -> Type) where
- class (forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- left :: forall (m :: Type -> Type) x a. Monad m => x -> ExceptT x m a
- right :: forall (m :: Type -> Type) a x. Monad m => a -> ExceptT x m a
- (<+>) :: Doc ann -> Doc ann -> Doc ann
- 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 Block era where
- ByronBlock :: ByronBlock -> Block ByronEra
- ShelleyBlock :: forall era. ShelleyBasedEra era -> ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) -> Block era
- pattern Block :: BlockHeader -> [Tx era] -> Block era
- data BlockHeader = BlockHeader !SlotNo !(Hash BlockHeader) !BlockNo
- data family Hash keyrole
- 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
- pattern TxBody :: TxBodyContent ViewTx era -> TxBody era
- newtype TxId = TxId (Hash HASH EraIndependentTxBody)
- getTxId :: TxBody era -> TxId
- class Typeable a => FromCBOR a
- class Typeable a => ToCBOR a
- castHash :: CastHash roleA roleB => Hash roleA -> Hash roleB
- data family VerificationKey keyrole
- data family SigningKey keyrole
- data AllegraEra
- data CardanoEra era where
- hashScript :: Script lang -> ScriptHash
- data Script lang where
- SimpleScript :: !SimpleScript -> Script SimpleScript'
- PlutusScript :: forall lang. IsPlutusScriptLanguage lang => !(PlutusScriptVersion lang) -> !(PlutusScript lang) -> Script lang
- data Value
- data ByronEra
- newtype ScriptHash = ScriptHash ScriptHash
- data Witness witctx era where
- KeyWitness :: forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era
- ScriptWitness :: forall witctx era. ScriptWitnessInCtx witctx -> ScriptWitness witctx era -> Witness witctx era
- data MIRPot
- data MIRTarget
- newtype CostModel = CostModel [Int64]
- data AlonzoEra
- data PlutusScript lang
- data BabbageEra
- data ConwayEra
- newtype TxIx = TxIx Word
- data MaryEra
- data ShelleyEra
- data CommitteeMembersState = CommitteeMembersState {}
- data MemberStatus
- queryAccountState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch AccountState))
- queryCommitteeMembersState :: ConwayEraOnwards era -> Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch CommitteeMembersState))
- queryConstitution :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Constitution (ShelleyLedgerEra era))))
- queryConstitutionHash :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SafeHash AnchorData)))
- queryDRepState :: ConwayEraOnwards era -> Set (Credential 'DRepRole) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Credential 'DRepRole) DRepState)))
- queryFuturePParams :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era)))))
- queryGovState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GovState (ShelleyLedgerEra era))))
- queryProposals :: ConwayEraOnwards era -> Set GovActionId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
- queryRatifyState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (RatifyState (ShelleyLedgerEra era))))
- queryStakePoolDefaultVote :: ConwayEraOnwards era -> KeyHash 'StakePool -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch DefaultVote))
- type Ann = AnsiStyle
- newtype EpochSlots = EpochSlots {}
- class Error e where
- prettyError :: e -> Doc ann
- data ProtocolParametersUpdate = ProtocolParametersUpdate {
- protocolUpdateProtocolVersion :: Maybe (Natural, Natural)
- protocolUpdateDecentralization :: Maybe Rational
- protocolUpdateExtraPraosEntropy :: Maybe (Maybe PraosNonce)
- protocolUpdateMaxBlockHeaderSize :: Maybe Word16
- protocolUpdateMaxBlockBodySize :: Maybe Word32
- protocolUpdateMaxTxSize :: Maybe Word32
- protocolUpdateTxFeeFixed :: Maybe Coin
- protocolUpdateTxFeePerByte :: Maybe Coin
- protocolUpdateMinUTxOValue :: Maybe Coin
- protocolUpdateStakeAddressDeposit :: Maybe Coin
- protocolUpdateStakePoolDeposit :: Maybe Coin
- protocolUpdateMinPoolCost :: Maybe Coin
- protocolUpdatePoolRetireMaxEpoch :: Maybe EpochInterval
- protocolUpdateStakePoolTargetNum :: Maybe Word16
- protocolUpdatePoolPledgeInfluence :: Maybe Rational
- protocolUpdateMonetaryExpansion :: Maybe Rational
- protocolUpdateTreasuryCut :: Maybe Rational
- protocolUpdateCostModels :: Map AnyPlutusScriptVersion CostModel
- protocolUpdatePrices :: Maybe ExecutionUnitPrices
- protocolUpdateMaxTxExUnits :: Maybe ExecutionUnits
- protocolUpdateMaxBlockExUnits :: Maybe ExecutionUnits
- protocolUpdateMaxValueSize :: Maybe Natural
- protocolUpdateCollateralPercent :: Maybe Natural
- protocolUpdateMaxCollateralInputs :: Maybe Natural
- protocolUpdateUTxOCostPerByte :: Maybe Coin
- data ValidationMode
- data NetworkId
- newtype BlockNo = BlockNo {}
- newtype EpochNo = EpochNo {}
- newtype SlotNo = SlotNo {}
- class Inject t s where
- inject :: t -> s
- data PaymentCredential
- data StakeCredential
- data StakePoolRelay
- valueFromList :: [(AssetId, Quantity)] -> Value
- newtype AssetName = AssetName ByteString
- data SimpleScript
- data LedgerState where
- LedgerState { }
- pattern LedgerStateAllegra :: LedgerState StandardAllegraBlock EmptyMK -> LedgerState
- pattern LedgerStateAlonzo :: LedgerState StandardAlonzoBlock EmptyMK -> LedgerState
- pattern LedgerStateBabbage :: LedgerState StandardBabbageBlock EmptyMK -> LedgerState
- pattern LedgerStateByron :: LedgerState ByronBlock EmptyMK -> LedgerState
- pattern LedgerStateConway :: LedgerState StandardConwayBlock EmptyMK -> LedgerState
- pattern LedgerStateMary :: LedgerState StandardMaryBlock EmptyMK -> LedgerState
- pattern LedgerStateShelley :: LedgerState StandardShelleyBlock EmptyMK -> LedgerState
- applyBlock :: Env -> LedgerState -> ValidationMode -> BlockInMode -> Either LedgerStateError (LedgerState, [LedgerEvent])
- newtype SystemStart = SystemStart {}
- class Monad m => MonadError e (m :: Type -> Type) | m -> e where
- throwError :: e -> m a
- catchError :: m a -> (e -> m a) -> m a
- type Except e = ExceptT e Identity
- newtype ExceptT e (m :: Type -> Type) a = ExceptT (m (Either e a))
- runExcept :: Except e a -> Either e a
- mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b
- withExcept :: (e -> e') -> Except e a -> Except e' a
- runExceptT :: ExceptT e m a -> m (Either e a)
- mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b
- withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a
- liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
- liftEither :: MonadError e m => Either e a -> m a
- modifyError :: forall e' t (m :: Type -> Type) e a. MonadTransError e' t m => (e -> e') -> ExceptT e m a -> t m a
- data NodeToClientVersion
- type family ConsensusProtocol era where ...
- slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
- data ShelleyBasedEra era where
- ShelleyBasedEraShelley :: ShelleyBasedEra ShelleyEra
- ShelleyBasedEraAllegra :: ShelleyBasedEra AllegraEra
- ShelleyBasedEraMary :: ShelleyBasedEra MaryEra
- ShelleyBasedEraAlonzo :: ShelleyBasedEra AlonzoEra
- ShelleyBasedEraBabbage :: ShelleyBasedEra BabbageEra
- ShelleyBasedEraConway :: ShelleyBasedEra ConwayEra
- data ShelleyConfig = ShelleyConfig {}
- data QueryInShelleyBasedEra era result where
- QueryEpoch :: forall era. QueryInShelleyBasedEra era EpochNo
- QueryGenesisParameters :: forall era. QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
- QueryProtocolParameters :: forall era. QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
- QueryStakeDistribution :: forall era. QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational)
- QueryUTxO :: forall era. QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
- QueryStakeAddresses :: forall era. Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
- QueryStakePools :: forall era. QueryInShelleyBasedEra era (Set PoolId)
- QueryStakePoolParameters :: forall era. Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
- QueryDebugLedgerState :: forall era. QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
- QueryProtocolState :: forall era. QueryInShelleyBasedEra era (ProtocolState era)
- QueryCurrentEpochState :: forall era. QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
- QueryPoolState :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era)
- QueryPoolDistribution :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
- QueryStakeSnapshot :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
- QueryStakeDelegDeposits :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Coin)
- QueryAccountState :: forall era. QueryInShelleyBasedEra era AccountState
- QueryConstitution :: forall era. QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
- QueryGovState :: forall era. QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
- QueryRatifyState :: forall era. QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era))
- QueryFuturePParams :: forall era. QueryInShelleyBasedEra era (Maybe (PParams (ShelleyLedgerEra era)))
- QueryDRepState :: forall era. Set (Credential 'DRepRole) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole) DRepState)
- QueryDRepStakeDistr :: forall era. Set DRep -> QueryInShelleyBasedEra era (Map DRep Coin)
- QuerySPOStakeDistr :: forall era. Set (KeyHash 'StakePool) -> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
- QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> QueryInShelleyBasedEra era CommitteeMembersState
- QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential DRep)
- QueryProposals :: forall era. Set GovActionId -> QueryInShelleyBasedEra era (Seq (GovActionState (ShelleyLedgerEra era)))
- QueryLedgerPeerSnapshot :: forall era. QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot)
- QueryStakePoolDefaultVote :: forall era. KeyHash 'StakePool -> QueryInShelleyBasedEra era DefaultVote
- data GenesisConfig = GenesisCardano !NodeConfig !Config !GenesisHashShelley !(TransitionConfig LatestKnownEra)
- unNetworkMagic :: NetworkMagic -> Word32
- newtype ChainSyncClientPipelined header point tip (m :: Type -> Type) a = ChainSyncClientPipelined {
- runChainSyncClientPipelined :: m (ClientPipelinedStIdle 'Z header point tip m a)
- newtype ChainSyncClient header point tip (m :: Type -> Type) a = ChainSyncClient {
- runChainSyncClient :: m (ClientStIdle header point tip m a)
- newtype LocalStateQueryClient block point (query :: Type -> Type) (m :: Type -> Type) a = LocalStateQueryClient {
- runLocalStateQueryClient :: m (ClientStIdle block point query m a)
- data MempoolSizeAndCapacity = MempoolSizeAndCapacity {
- capacityInBytes :: !Word32
- sizeInBytes :: !Word32
- numberOfTxs :: !Word32
- newtype LocalTxMonitorClient txid tx slot (m :: Type -> Type) a = LocalTxMonitorClient {
- runLocalTxMonitorClient :: m (ClientStIdle txid tx slot m a)
- data SubmitResult reason
- = SubmitSuccess
- | SubmitFail reason
- newtype LocalTxSubmissionClient tx reject (m :: Type -> Type) a = LocalTxSubmissionClient {
- runLocalTxSubmissionClient :: m (LocalTxClientStIdle tx reject m a)
- data Doc ann
- hsep :: [Doc ann] -> Doc ann
- throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a
- catchE :: forall (m :: Type -> Type) e a e'. Monad m => ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
- except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a
- handleE :: forall (m :: Type -> Type) e e' a. Monad m => (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a
- tryE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m (Either e a)
- finallyE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m () -> ExceptT e m a
- liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a
- liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a
- hoistMaybe :: forall (m :: Type -> Type) x a. Monad m => x -> Maybe a -> ExceptT x m a
- class HasTypeProxy era => IsCardanoEra era where
- cardanoEra :: CardanoEra era
- data AnyCardanoEra where
- AnyCardanoEra :: forall era. Typeable era => CardanoEra era -> AnyCardanoEra
- anyCardanoEra :: CardanoEra era -> AnyCardanoEra
- data InAnyCardanoEra (thing :: Type -> Type) where
- InAnyCardanoEra :: forall era (thing :: Type -> Type). Typeable era => CardanoEra era -> thing era -> InAnyCardanoEra thing
- inAnyCardanoEra :: CardanoEra era -> thing era -> InAnyCardanoEra thing
- cardanoEraConstraints :: CardanoEra era -> (CardanoEraConstraints era => a) -> a
- class ToCardanoEra (eon :: Type -> Type) where
- toCardanoEra :: eon era -> CardanoEra era
- class Eon (eon :: Type -> Type) where
- inEonForEra :: a -> (eon era -> a) -> CardanoEra era -> a
- data EraInEon (eon :: Type -> Type) where
- inEonForEraMaybe :: Eon eon => (eon era -> a) -> CardanoEra era -> Maybe a
- forEraInEon :: Eon eon => CardanoEra era -> a -> (eon era -> a) -> a
- forEraInEonMaybe :: Eon eon => CardanoEra era -> (eon era -> a) -> Maybe a
- forEraMaybeEon :: Eon eon => CardanoEra era -> Maybe (eon era)
- maybeEon :: (Eon eon, IsCardanoEra era) => Maybe (eon era)
- monoidForEraInEon :: (Eon eon, Monoid a) => CardanoEra era -> (eon era -> a) -> a
- monoidForEraInEonA :: (Eon eon, Applicative f, Monoid a) => CardanoEra era -> (eon era -> f a) -> f a
- inEonForShelleyBasedEra :: Eon eon => a -> (eon era -> a) -> ShelleyBasedEra era -> a
- inEonForShelleyBasedEraMaybe :: Eon eon => (eon era -> a) -> ShelleyBasedEra era -> Maybe a
- forShelleyBasedEraInEon :: Eon eon => ShelleyBasedEra era -> a -> (eon era -> a) -> a
- forShelleyBasedEraInEonMaybe :: Eon eon => ShelleyBasedEra era -> (eon era -> a) -> Maybe a
- forShelleyBasedEraMaybeEon :: Eon eon => ShelleyBasedEra era -> Maybe (eon era)
- data Featured (eon :: Type -> Type) era a where
- mkFeatured :: forall (eon :: Type -> Type) era a. (IsCardanoEra era, Eon eon) => a -> Maybe (Featured eon era a)
- unFeatured :: forall (eon :: Type -> Type) era a. Featured eon era a -> a
- asFeaturedInEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> CardanoEra era -> Maybe (Featured eon era a)
- asFeaturedInShelleyBasedEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> ShelleyBasedEra era -> Maybe (Featured eon era a)
- class Convert (f :: a -> Type) (g :: a -> Type) where
- convert :: forall (era :: a). f era -> g era
- data ByronToAlonzoEra era where
- byronToAlonzoEraConstraints :: ByronToAlonzoEra era -> (ByronToAlonzoEraConstraints era => a) -> a
- data ShelleyEraOnly era where
- shelleyEraOnlyConstraints :: ShelleyEraOnly era -> (ShelleyEraOnlyConstraints era => a) -> a
- shelleyEraOnlyToShelleyBasedEra :: ShelleyEraOnly era -> ShelleyBasedEra era
- data ShelleyToAllegraEra era where
- shelleyToAllegraEraConstraints :: ShelleyToAllegraEra era -> (ShelleyToAllegraEraConstraints era => a) -> a
- shelleyToAllegraEraToShelleyBasedEra :: ShelleyToAllegraEra era -> ShelleyBasedEra era
- data ShelleyToMaryEra era where
- shelleyToMaryEraConstraints :: ShelleyToMaryEra era -> (ShelleyToMaryEraConstraints era => a) -> a
- shelleyToMaryEraToShelleyBasedEra :: ShelleyToMaryEra era -> ShelleyBasedEra era
- data ShelleyToAlonzoEra era where
- shelleyToAlonzoEraConstraints :: ShelleyToAlonzoEra era -> (ShelleyToAlonzoEraConstraints era => a) -> a
- shelleyToAlonzoEraToShelleyBasedEra :: ShelleyToAlonzoEra era -> ShelleyBasedEra era
- data ShelleyToBabbageEra era where
- shelleyToBabbageEraConstraints :: ShelleyToBabbageEra era -> (ShelleyToBabbageEraConstraints era => a) -> a
- shelleyToBabbageEraToShelleyBasedEra :: ShelleyToBabbageEra era -> ShelleyBasedEra era
- class IsCardanoEra era => IsShelleyBasedEra era where
- shelleyBasedEra :: ShelleyBasedEra era
- data AnyShelleyBasedEra where
- AnyShelleyBasedEra :: forall era. Typeable era => ShelleyBasedEra era -> AnyShelleyBasedEra
- data InAnyShelleyBasedEra (thing :: Type -> Type) where
- InAnyShelleyBasedEra :: forall era (thing :: Type -> Type). Typeable era => ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing
- inAnyShelleyBasedEra :: ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing
- shelleyBasedEraConstraints :: ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a
- data AllegraEraOnwards era where
- class IsShelleyBasedEra era => IsAllegraBasedEra era where
- allegraBasedEra :: AllegraEraOnwards era
- data MaryEraOnwards era where
- maryEraOnwardsConstraints :: MaryEraOnwards era -> (MaryEraOnwardsConstraints era => a) -> a
- maryEraOnwardsToShelleyBasedEra :: MaryEraOnwards era -> ShelleyBasedEra era
- class IsAllegraBasedEra era => IsMaryBasedEra era where
- maryBasedEra :: MaryEraOnwards era
- data AlonzoEraOnwards era where
- alonzoEraOnwardsConstraints :: AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
- alonzoEraOnwardsToShelleyBasedEra :: AlonzoEraOnwards era -> ShelleyBasedEra era
- class IsMaryBasedEra era => IsAlonzoBasedEra era where
- alonzoBasedEra :: AlonzoEraOnwards era
- data BabbageEraOnwards era where
- babbageEraOnwardsConstraints :: BabbageEraOnwards era -> (BabbageEraOnwardsConstraints era => a) -> a
- babbageEraOnwardsToShelleyBasedEra :: BabbageEraOnwards era -> ShelleyBasedEra era
- class IsAlonzoBasedEra era => IsBabbageBasedEra era where
- babbageBasedEra :: BabbageEraOnwards era
- data ConwayEraOnwards era where
- conwayEraOnwardsConstraints :: ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => a) -> a
- conwayEraOnwardsToShelleyBasedEra :: ConwayEraOnwards era -> ShelleyBasedEra era
- conwayEraOnwardsToBabbageEraOnwards :: ConwayEraOnwards era -> BabbageEraOnwards era
- class IsBabbageBasedEra era => IsConwayBasedEra era where
- conwayBasedEra :: ConwayEraOnwards era
- caseByronOrShelleyBasedEra :: a -> (ShelleyBasedEraConstraints era => ShelleyBasedEra era -> a) -> CardanoEra era -> a
- caseByronToAlonzoOrBabbageEraOnwards :: (ByronToAlonzoEraConstraints era => ByronToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> CardanoEra era -> a
- caseShelleyEraOnlyOrAllegraEraOnwards :: (ShelleyEraOnlyConstraints era => ShelleyEraOnly era -> a) -> (AllegraEraOnwardsConstraints era => AllegraEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToAllegraOrMaryEraOnwards :: (ShelleyToAllegraEraConstraints era => ShelleyToAllegraEra era -> a) -> (MaryEraOnwardsConstraints era => MaryEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToMaryOrAlonzoEraOnwards :: (ShelleyToMaryEraConstraints era => ShelleyToMaryEra era -> a) -> (AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToAlonzoOrBabbageEraOnwards :: (ShelleyToAlonzoEraConstraints era => ShelleyToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToBabbageOrConwayEraOnwards :: (ShelleyToBabbageEraConstraints era => ShelleyToBabbageEra era -> a) -> (ConwayEraOnwardsConstraints era => ConwayEraOnwards era -> a) -> ShelleyBasedEra era -> a
- shelleyToAlonzoEraToShelleyToBabbageEra :: ShelleyToAlonzoEra era -> ShelleyToBabbageEra era
- alonzoEraOnwardsToMaryEraOnwards :: AlonzoEraOnwards era -> MaryEraOnwards era
- babbageEraOnwardsToMaryEraOnwards :: BabbageEraOnwards era -> MaryEraOnwards era
- babbageEraOnwardsToAlonzoEraOnwards :: BabbageEraOnwards era -> AlonzoEraOnwards era
- requireShelleyBasedEra :: Applicative m => CardanoEra era -> m (Maybe (ShelleyBasedEra era))
- newtype File content (direction :: FileDirection) = File {}
- data FileDirection
- mapFile :: forall content (direction :: FileDirection). (FilePath -> FilePath) -> File content direction -> File content direction
- onlyIn :: File content 'InOut -> File content 'In
- onlyOut :: File content 'InOut -> File content 'Out
- intoFile :: File content 'Out -> content -> (File content 'Out -> stream -> result) -> (content -> stream) -> result
- readByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString)
- readLazyByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString)
- readTextFile :: MonadIO m => File content 'In -> m (Either (FileError e) Text)
- writeByteStringFileWithOwnerPermissions :: FilePath -> ByteString -> IO (Either (FileError e) ())
- writeByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringFileWithOwnerPermissions :: File content 'Out -> ByteString -> IO (Either (FileError e) ())
- writeLazyByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeTextFileWithOwnerPermissions :: File content 'Out -> Text -> IO (Either (FileError e) ())
- writeTextFile :: MonadIO m => File content 'Out -> Text -> m (Either (FileError e) ())
- writeTextOutput :: MonadIO m => Maybe (File content 'Out) -> Text -> m (Either (FileError e) ())
- class Typeable t => HasTypeProxy t where
- data AsType t
- proxyToAsType :: Proxy t -> AsType t
- data family AsType t
- asType :: HasTypeProxy t => AsType t
- castVerificationKey :: CastVerificationKeyRole keyroleA keyroleB => VerificationKey keyroleA -> VerificationKey keyroleB
- castSigningKey :: CastSigningKeyRole keyroleA keyroleB => SigningKey keyroleA -> SigningKey keyroleB
- generateSigningKey :: (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole)
- generateInsecureSigningKey :: (MonadIO m, Key keyrole, SerialiseAsRawBytes (SigningKey keyrole)) => StdGen -> AsType keyrole -> m (SigningKey keyrole, StdGen)
- renderSafeHashAsHex :: SafeHash tag -> Text
- data MnemonicSize
- generateMnemonic :: MonadIO m => MnemonicSize -> m [Text]
- data MnemonicToSigningKeyError
- signingKeyFromMnemonic :: SigningKeyFromRootKey keyrole => AsType keyrole -> [Text] -> Word32 -> Either MnemonicToSigningKeyError (SigningKey keyrole)
- signingKeyFromMnemonicWithPaymentKeyIndex :: IndexedSigningKeyFromRootKey keyrole => AsType keyrole -> [Text] -> Word32 -> Word32 -> Either MnemonicToSigningKeyError (SigningKey keyrole)
- findMnemonicWordsWithPrefix :: Text -> [(Text, Int)]
- autocompleteMnemonicPrefix :: Text -> Maybe Text
- data ByronAddr
- data ShelleyAddr
- makeByronAddress :: NetworkId -> VerificationKey ByronKey -> Address ByronAddr
- data ByronKey
- data ByronKeyLegacy
- makeShelleyAddress :: NetworkId -> PaymentCredential -> StakeAddressReference -> Address ShelleyAddr
- newtype StakeAddressPointer = StakeAddressPointer {}
- data StakeAddressReference
- data PaymentKey
- data PaymentExtendedKey
- data AddressAny
- lexPlausibleAddressString :: Parser Text
- parseAddressAny :: SerialiseAddress addr => Parser addr
- data AddressInEra era where
- AddressInEra :: forall addrtype era. AddressTypeInEra addrtype era -> Address addrtype -> AddressInEra era
- isKeyAddress :: AddressInEra era -> Bool
- data AddressTypeInEra addrtype era where
- ByronAddressInAnyEra :: forall era. AddressTypeInEra ByronAddr era
- ShelleyAddressInEra :: forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
- byronAddressInEra :: Address ByronAddr -> AddressInEra era
- shelleyAddressInEra :: ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
- anyAddressInShelleyBasedEra :: ShelleyBasedEra era -> AddressAny -> AddressInEra era
- anyAddressInEra :: CardanoEra era -> AddressAny -> Either String (AddressInEra era)
- toAddressAny :: Address addr -> AddressAny
- makeByronAddressInEra :: NetworkId -> VerificationKey ByronKey -> AddressInEra era
- makeShelleyAddressInEra :: ShelleyBasedEra era -> NetworkId -> PaymentCredential -> StakeAddressReference -> AddressInEra era
- data StakeAddress
- makeStakeAddress :: NetworkId -> StakeCredential -> StakeAddress
- stakeAddressCredential :: StakeAddress -> StakeCredential
- data StakeKey
- data StakeExtendedKey
- newtype Quantity = Quantity Integer
- newtype PolicyId = PolicyId {}
- scriptPolicyId :: Script lang -> PolicyId
- data AssetId
- parsePolicyId :: Parser PolicyId
- parseAssetName :: Parser AssetName
- parseTxOutMultiAssetValue :: Parser Value
- parseMintingMultiAssetValue :: MaryEraOnwards era -> Parser MultiAsset
- parseUTxOValue :: Parser Value
- selectAsset :: Value -> AssetId -> Quantity
- valueToList :: Value -> [(AssetId, Quantity)]
- filterValue :: (AssetId -> Bool) -> Value -> Value
- negateValue :: Value -> Value
- newtype ValueNestedRep = ValueNestedRep [ValueNestedBundle]
- data ValueNestedBundle
- valueToNestedRep :: Value -> ValueNestedRep
- valueFromNestedRep :: ValueNestedRep -> Value
- renderValue :: Value -> Text
- renderMultiAsset :: MultiAsset -> Text
- renderValuePretty :: Value -> Text
- renderMultiAssetPretty :: MultiAsset -> Text
- toLedgerValue :: MaryEraOnwards era -> Value -> Value (ShelleyLedgerEra era)
- fromLedgerValue :: ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> Value
- newtype PolicyAssets = PolicyAssets (Map AssetName Quantity)
- policyAssetsToValue :: PolicyId -> PolicyAssets -> Value
- valueToPolicyAssets :: Value -> Map PolicyId PolicyAssets
- multiAssetToPolicyAssets :: MultiAsset -> Map PolicyId PolicyAssets
- quantityToLovelace :: Quantity -> Lovelace
- lovelaceToQuantity :: Lovelace -> Quantity
- selectLovelace :: Value -> Lovelace
- lovelaceToValue :: Lovelace -> Value
- valueToLovelace :: Value -> Maybe Lovelace
- getBlockHeader :: Block era -> BlockHeader
- getBlockTxs :: Block era -> [Tx era]
- data ChainPoint
- data ChainTip
- chainTipToChainPoint :: ChainTip -> ChainPoint
- createTransactionBody :: HasCallStack => ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
- createAndValidateTransactionBody :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
- makeByronTransactionBody :: TxIns BuildTx ByronEra -> [TxOut CtxTx ByronEra] -> Either TxBodyError (Annotated Tx ByteString)
- data TxBodyContent build era = TxBodyContent {
- txIns :: TxIns build era
- txInsCollateral :: TxInsCollateral era
- txInsReference :: TxInsReference build era
- txOuts :: [TxOut CtxTx era]
- txTotalCollateral :: TxTotalCollateral era
- txReturnCollateral :: TxReturnCollateral CtxTx era
- txFee :: TxFee era
- txValidityLowerBound :: TxValidityLowerBound era
- txValidityUpperBound :: TxValidityUpperBound era
- txMetadata :: TxMetadataInEra era
- txAuxScripts :: TxAuxScripts era
- txExtraKeyWits :: TxExtraKeyWitnesses era
- txProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era))
- txWithdrawals :: TxWithdrawals build era
- txCertificates :: TxCertificates build era
- txUpdateProposal :: TxUpdateProposal era
- txMintValue :: TxMintValue build era
- txScriptValidity :: TxScriptValidity era
- txProposalProcedures :: Maybe (Featured ConwayEraOnwards era (TxProposalProcedures build era))
- txVotingProcedures :: Maybe (Featured ConwayEraOnwards era (TxVotingProcedures build era))
- txCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era (Maybe Coin))
- txTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin)
- getTxBodyContent :: TxBody era -> TxBodyContent ViewTx era
- defaultTxBodyContent :: ShelleyBasedEra era -> TxBodyContent BuildTx era
- defaultTxFee :: ShelleyBasedEra era -> TxFee era
- defaultTxValidityUpperBound :: ShelleyBasedEra era -> TxValidityUpperBound era
- setTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era
- modTxIns :: (TxIns build era -> TxIns build era) -> TxBodyContent build era -> TxBodyContent build era
- addTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era
- addTxIn :: (TxIn, BuildTxWith build (Witness WitCtxTxIn era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxInsCollateral :: TxInsCollateral era -> TxBodyContent build era -> TxBodyContent build era
- modTxInsCollateral :: (TxInsCollateral era -> TxInsCollateral era) -> TxBodyContent build era -> TxBodyContent build era
- addTxInsCollateral :: IsAlonzoBasedEra era => [TxIn] -> TxBodyContent build era -> TxBodyContent build era
- addTxInCollateral :: IsAlonzoBasedEra era => TxIn -> TxBodyContent build era -> TxBodyContent build era
- setTxInsReference :: TxInsReference build era -> TxBodyContent build era -> TxBodyContent build era
- modTxInsReference :: (TxInsReference build era -> TxInsReference build era) -> TxBodyContent build era -> TxBodyContent build era
- addTxInsReference :: (Applicative (BuildTxWith build), IsBabbageBasedEra era) => [TxIn] -> Set HashableScriptData -> TxBodyContent build era -> TxBodyContent build era
- addTxInReference :: (Applicative (BuildTxWith build), IsBabbageBasedEra era) => TxIn -> Maybe HashableScriptData -> TxBodyContent build era -> TxBodyContent build era
- setTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era
- modTxOuts :: ([TxOut CtxTx era] -> [TxOut CtxTx era]) -> TxBodyContent build era -> TxBodyContent build era
- addTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era
- addTxOut :: TxOut CtxTx era -> TxBodyContent build era -> TxBodyContent build era
- setTxTotalCollateral :: TxTotalCollateral era -> TxBodyContent build era -> TxBodyContent build era
- modTxTotalCollateral :: (TxTotalCollateral era -> TxTotalCollateral era) -> TxBodyContent build era -> TxBodyContent build era
- setTxReturnCollateral :: TxReturnCollateral CtxTx era -> TxBodyContent build era -> TxBodyContent build era
- modTxReturnCollateral :: (TxReturnCollateral CtxTx era -> TxReturnCollateral CtxTx era) -> TxBodyContent build era -> TxBodyContent build era
- setTxFee :: TxFee era -> TxBodyContent build era -> TxBodyContent build era
- modTxFee :: (TxFee era -> TxFee era) -> TxBodyContent build era -> TxBodyContent build era
- setTxValidityLowerBound :: TxValidityLowerBound era -> TxBodyContent build era -> TxBodyContent build era
- modTxValidityLowerBound :: (TxValidityLowerBound era -> TxValidityLowerBound era) -> TxBodyContent build era -> TxBodyContent build era
- setTxValidityUpperBound :: TxValidityUpperBound era -> TxBodyContent build era -> TxBodyContent build era
- modTxValidityUpperBound :: (TxValidityUpperBound era -> TxValidityUpperBound era) -> TxBodyContent build era -> TxBodyContent build era
- setTxMetadata :: TxMetadataInEra era -> TxBodyContent build era -> TxBodyContent build era
- modTxMetadata :: (TxMetadataInEra era -> TxMetadataInEra era) -> TxBodyContent build era -> TxBodyContent build era
- setTxAuxScripts :: TxAuxScripts era -> TxBodyContent build era -> TxBodyContent build era
- modTxAuxScripts :: (TxAuxScripts era -> TxAuxScripts era) -> TxBodyContent build era -> TxBodyContent build era
- setTxExtraKeyWits :: TxExtraKeyWitnesses era -> TxBodyContent build era -> TxBodyContent build era
- modTxExtraKeyWits :: (TxExtraKeyWitnesses era -> TxExtraKeyWitnesses era) -> TxBodyContent build era -> TxBodyContent build era
- addTxExtraKeyWits :: IsAlonzoBasedEra era => [Hash PaymentKey] -> TxBodyContent build era -> TxBodyContent build era
- setTxProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxWithdrawals :: TxWithdrawals build era -> TxBodyContent build era -> TxBodyContent build era
- modTxWithdrawals :: (TxWithdrawals build era -> TxWithdrawals build era) -> TxBodyContent build era -> TxBodyContent build era
- setTxCertificates :: TxCertificates build era -> TxBodyContent build era -> TxBodyContent build era
- modTxCertificates :: (TxCertificates build era -> TxCertificates build era) -> TxBodyContent build era -> TxBodyContent build era
- setTxUpdateProposal :: TxUpdateProposal era -> TxBodyContent build era -> TxBodyContent build era
- modTxUpdateProposal :: (TxUpdateProposal era -> TxUpdateProposal era) -> TxBodyContent build era -> TxBodyContent build era
- setTxMintValue :: TxMintValue build era -> TxBodyContent build era -> TxBodyContent build era
- modTxMintValue :: (TxMintValue build era -> TxMintValue build era) -> TxBodyContent build era -> TxBodyContent build era
- addTxMintValue :: IsMaryBasedEra era => Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxBodyContent build era -> TxBodyContent build era
- subtractTxMintValue :: IsMaryBasedEra era => Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxScriptValidity :: TxScriptValidity era -> TxBodyContent build era -> TxBodyContent build era
- modTxScriptValidity :: (TxScriptValidity era -> TxScriptValidity era) -> TxBodyContent build era -> TxBodyContent build era
- setTxProposalProcedures :: Maybe (Featured ConwayEraOnwards era (TxProposalProcedures build era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxVotingProcedures :: Maybe (Featured ConwayEraOnwards era (TxVotingProcedures build era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era (Maybe Coin)) -> TxBodyContent build era -> TxBodyContent build era
- setTxTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin) -> TxBodyContent build era -> TxBodyContent build era
- data TxBodyError
- = TxBodyPlutusScriptDecodeError DecoderError
- | TxBodyEmptyTxIns
- | TxBodyEmptyTxInsCollateral
- | TxBodyEmptyTxOuts
- | TxBodyOutputError !TxOutputError
- | TxBodyMetadataError ![(Word64, TxMetadataRangeError)]
- | TxBodyInIxOverflow !TxIn
- | TxBodyMissingProtocolParams
- | TxBodyProtocolParamsConversionError !ProtocolParametersConversionError
- data TxBodyErrorAutoBalance era
- = TxBodyError TxBodyError
- | TxBodyScriptExecutionError [(ScriptWitnessIndex, ScriptExecutionError)]
- | TxBodyScriptBadScriptValidity
- | TxBodyErrorBalanceNegative Coin MultiAsset
- | TxBodyErrorAdaBalanceTooSmall TxOutInAnyEra Coin Coin
- | TxBodyErrorByronEraNotSupported
- | TxBodyErrorMissingParamMinUTxO
- | TxBodyErrorMinUTxONotMet TxOutInAnyEra Coin
- | TxBodyErrorNonAdaAssetsUnbalanced Value
- | TxBodyErrorScriptWitnessIndexMissingFromExecUnitsMap ScriptWitnessIndex (Map ScriptWitnessIndex ExecutionUnits)
- data TxOutputError
- data TxBodyScriptData era where
- TxBodyNoScriptData :: forall era. TxBodyScriptData era
- TxBodyScriptData :: forall era. AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> TxDats (ShelleyLedgerEra era) -> Redeemers (ShelleyLedgerEra era) -> TxBodyScriptData era
- getTxIdByron :: ATxAux ByteString -> TxId
- type TxIns build era = [(TxIn, BuildTxWith build (Witness WitCtxTxIn era))]
- renderTxIn :: TxIn -> Text
- getReferenceInputsSizeForTxIds :: ShelleyLedgerEra era ~ ledgerera => BabbageEraOnwards era -> UTxO ledgerera -> Set TxIn -> Int
- data CtxTx
- data CtxUTxO
- data TxOutValue era where
- TxOutValueByron :: Coin -> TxOutValue ByronEra
- TxOutValueShelleyBased :: forall era. (Eq (Value (ShelleyLedgerEra era)), Show (Value (ShelleyLedgerEra era))) => ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> TxOutValue era
- data TxOutInAnyEra where
- TxOutInAnyEra :: forall era. CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra
- txOutInAnyEra :: CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra
- txOutValueToLovelace :: TxOutValue era -> Coin
- txOutValueToValue :: TxOutValue era -> Value
- lovelaceToTxOutValue :: ShelleyBasedEra era -> Coin -> TxOutValue era
- data TxOutDatum ctx era where
- TxOutDatumNone :: forall ctx era. TxOutDatum ctx era
- TxOutDatumHash :: forall era ctx. AlonzoEraOnwards era -> Hash ScriptData -> TxOutDatum ctx era
- TxOutSupplementalDatum :: forall era. AlonzoEraOnwards era -> HashableScriptData -> TxOutDatum CtxTx era
- TxOutDatumInline :: forall era ctx. BabbageEraOnwards era -> HashableScriptData -> TxOutDatum ctx era
- parseHash :: SerialiseAsRawBytes (Hash a) => Parser (Hash a)
- data TxInsCollateral era where
- TxInsCollateralNone :: forall era. TxInsCollateral era
- TxInsCollateral :: forall era. AlonzoEraOnwards era -> [TxIn] -> TxInsCollateral era
- data TxInsReference build era where
- TxInsReferenceNone :: forall build era. TxInsReference build era
- TxInsReference :: forall era build. BabbageEraOnwards era -> [TxIn] -> TxInsReferenceDatums build -> TxInsReference build era
- data TxTotalCollateral era where
- TxTotalCollateralNone :: forall era. TxTotalCollateral era
- TxTotalCollateral :: forall era. BabbageEraOnwards era -> Coin -> TxTotalCollateral era
- data TxReturnCollateral ctx era where
- TxReturnCollateralNone :: forall ctx era. TxReturnCollateral ctx era
- TxReturnCollateral :: forall era ctx. BabbageEraOnwards era -> TxOut ctx era -> TxReturnCollateral ctx era
- data TxFee era where
- TxFeeExplicit :: forall era. ShelleyBasedEra era -> Coin -> TxFee era
- data TxValidityLowerBound era where
- TxValidityNoLowerBound :: forall era. TxValidityLowerBound era
- TxValidityLowerBound :: forall era. AllegraEraOnwards era -> SlotNo -> TxValidityLowerBound era
- data TxValidityUpperBound era where
- TxValidityUpperBound :: forall era. ShelleyBasedEra era -> Maybe SlotNo -> TxValidityUpperBound era
- data TxMetadataInEra era where
- TxMetadataNone :: forall era. TxMetadataInEra era
- TxMetadataInEra :: forall era. ShelleyBasedEra era -> TxMetadata -> TxMetadataInEra era
- data TxAuxScripts era where
- TxAuxScriptsNone :: forall era. TxAuxScripts era
- TxAuxScripts :: forall era. AllegraEraOnwards era -> [ScriptInEra era] -> TxAuxScripts era
- data TxExtraKeyWitnesses era where
- TxExtraKeyWitnessesNone :: forall era. TxExtraKeyWitnesses era
- TxExtraKeyWitnesses :: forall era. AlonzoEraOnwards era -> [Hash PaymentKey] -> TxExtraKeyWitnesses era
- data TxWithdrawals build era where
- TxWithdrawalsNone :: forall build era. TxWithdrawals build era
- TxWithdrawals :: forall era build. ShelleyBasedEra era -> [(StakeAddress, Coin, BuildTxWith build (Witness WitCtxStake era))] -> TxWithdrawals build era
- data TxCertificates build era where
- TxCertificatesNone :: forall build era. TxCertificates build era
- TxCertificates :: forall era build. ShelleyBasedEra era -> OMap (Certificate era) (BuildTxWith build (Maybe (StakeCredential, Witness WitCtxStake era))) -> TxCertificates build era
- mkTxCertificates :: Applicative (BuildTxWith build) => ShelleyBasedEra era -> [(Certificate era, Maybe (ScriptWitness WitCtxStake era))] -> TxCertificates build era
- data TxUpdateProposal era where
- TxUpdateProposalNone :: forall era. TxUpdateProposal era
- TxUpdateProposal :: forall era. ShelleyToBabbageEra era -> UpdateProposal -> TxUpdateProposal era
- data TxMintValue build era where
- TxMintNone :: forall build era. TxMintValue build era
- TxMintValue :: forall era build. MaryEraOnwards era -> Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxMintValue build era
- mkTxMintValue :: MaryEraOnwards era -> [(PolicyId, PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era))] -> TxMintValue build era
- txMintValueToValue :: TxMintValue build era -> Value
- indexTxMintValue :: TxMintValue build era -> [(ScriptWitnessIndex, PolicyId, PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era))]
- data TxVotingProcedures build era where
- TxVotingProceduresNone :: forall build era. TxVotingProcedures build era
- TxVotingProcedures :: forall era build. VotingProcedures (ShelleyLedgerEra era) -> BuildTxWith build (Map Voter (ScriptWitness WitCtxStake era)) -> TxVotingProcedures build era
- mkTxVotingProcedures :: Applicative (BuildTxWith build) => [(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))] -> Either (VotesMergingConflict era) (TxVotingProcedures build era)
- data TxProposalProcedures build era where
- TxProposalProceduresNone :: forall build era. TxProposalProcedures build era
- TxProposalProcedures :: forall era build. EraPParams (ShelleyLedgerEra era) => OMap (ProposalProcedure (ShelleyLedgerEra era)) (BuildTxWith build (Maybe (ScriptWitness WitCtxStake era))) -> TxProposalProcedures build era
- mkTxProposalProcedures :: forall era build. (Applicative (BuildTxWith build), IsShelleyBasedEra era) => [(ProposalProcedure (ShelleyLedgerEra era), Maybe (ScriptWitness WitCtxStake era))] -> TxProposalProcedures build era
- convProposalProcedures :: TxProposalProcedures build era -> OSet (ProposalProcedure (ShelleyLedgerEra era))
- data BuildTxWith build a where
- ViewTx :: forall a. BuildTxWith ViewTx a
- BuildTxWith :: forall a. a -> BuildTxWith BuildTx a
- data BuildTx
- data ViewTx
- buildTxWithToMaybe :: BuildTxWith build a -> Maybe a
- newtype LedgerEpochInfo = LedgerEpochInfo {}
- toLedgerEpochInfo :: EraHistory -> LedgerEpochInfo
- evaluateTransactionFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> TxBody era -> Word -> Word -> Int -> Coin
- calculateMinTxFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> UTxO era -> TxBody era -> Word -> Coin
- estimateTransactionKeyWitnessCount :: TxBodyContent BuildTx era -> Word
- calculateMinimumUTxO :: HasCallStack => ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> TxOut CtxTx era -> Coin
- evaluateTransactionExecutionUnits :: CardanoEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> TxBody era -> Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits))
- data ScriptExecutionError
- = ScriptErrorMissingTxIn TxIn
- | ScriptErrorTxInWithoutDatum TxIn
- | ScriptErrorWrongDatum (Hash ScriptData)
- | ScriptErrorEvaluationFailed DebugPlutusFailure
- | ScriptErrorExecutionUnitsOverflow
- | ScriptErrorNotPlutusWitnessedTxIn ScriptWitnessIndex ScriptHash
- | ScriptErrorRedeemerPointsToUnknownScriptHash ScriptWitnessIndex
- | ScriptErrorMissingScript ScriptWitnessIndex ResolvablePointers
- | ScriptErrorMissingCostModel Language
- | (EraPlutusContext (ShelleyLedgerEra era), Show (ContextError (ShelleyLedgerEra era))) => ScriptErrorTranslationError (ContextError (ShelleyLedgerEra era))
- data TransactionValidityError era where
- TransactionValidityIntervalError :: forall era. PastHorizonException -> TransactionValidityError era
- TransactionValidityCostModelError :: forall era. Map AnyPlutusScriptVersion CostModel -> String -> TransactionValidityError era
- evaluateTransactionBalance :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> UTxO era -> TxBody era -> TxOutValue era
- estimateBalancedTxBody :: HasCallStack => MaryEraOnwards era -> TxBodyContent BuildTx era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> Map ScriptWitnessIndex ExecutionUnits -> Coin -> Int -> Int -> Int -> AddressInEra era -> Value -> Either (TxFeeEstimationError era) (BalancedTxBody era)
- estimateOrCalculateBalancedTxBody :: ShelleyBasedEra era -> FeeEstimationMode era -> PParams (ShelleyLedgerEra era) -> TxBodyContent BuildTx era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> AddressInEra era -> Either (AutoBalanceError era) (BalancedTxBody era)
- makeTransactionBodyAutoBalance :: HasCallStack => ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> UTxO era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> Either (TxBodyErrorAutoBalance era) (BalancedTxBody era)
- data AutoBalanceError era
- data BalancedTxBody era = BalancedTxBody (TxBodyContent BuildTx era) (TxBody era) (TxOut CtxTx era) Coin
- data FeeEstimationMode era
- newtype RequiredShelleyKeyWitnesses = RequiredShelleyKeyWitnesses {}
- newtype RequiredByronKeyWitnesses = RequiredByronKeyWitnesses {}
- newtype TotalReferenceScriptsSize = TotalReferenceScriptsSize {}
- data TxFeeEstimationError era
- = TxFeeEstimationTransactionTranslationError (TransactionValidityError era)
- | TxFeeEstimationScriptExecutionError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationBalanceError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationxBodyError TxBodyError
- | TxFeeEstimationFinalConstructionError TxBodyError
- | TxFeeEstimationOnlyMaryOnwardsSupportedError
- data TxScriptValidity era where
- TxScriptValidityNone :: forall era. TxScriptValidity era
- TxScriptValidity :: forall era. AlonzoEraOnwards era -> ScriptValidity -> TxScriptValidity era
- data ScriptValidity
- txScriptValidityToScriptValidity :: TxScriptValidity era -> ScriptValidity
- getTxBody :: Tx era -> TxBody era
- getTxWitnesses :: Tx era -> [KeyWitness era]
- signByronTransaction :: NetworkId -> Annotated Tx ByteString -> [SigningKey ByronKey] -> ATxAux ByteString
- signShelleyTransaction :: ShelleyBasedEra era -> TxBody era -> [ShelleyWitnessSigningKey] -> Tx era
- makeSignedByronTransaction :: [KeyWitness era] -> Annotated Tx ByteString -> ATxAux ByteString
- makeSignedTransaction :: [KeyWitness era] -> TxBody era -> Tx era
- data KeyWitness era
- makeByronKeyWitness :: IsByronKey key => NetworkId -> Annotated Tx ByteString -> SigningKey key -> KeyWitness ByronEra
- data ShelleyWitnessSigningKey
- = WitnessPaymentKey (SigningKey PaymentKey)
- | WitnessPaymentExtendedKey (SigningKey PaymentExtendedKey)
- | WitnessStakeKey (SigningKey StakeKey)
- | WitnessStakeExtendedKey (SigningKey StakeExtendedKey)
- | WitnessStakePoolKey (SigningKey StakePoolKey)
- | WitnessStakePoolExtendedKey (SigningKey StakePoolExtendedKey)
- | WitnessGenesisKey (SigningKey GenesisKey)
- | WitnessGenesisExtendedKey (SigningKey GenesisExtendedKey)
- | WitnessGenesisDelegateKey (SigningKey GenesisDelegateKey)
- | WitnessGenesisDelegateExtendedKey (SigningKey GenesisDelegateExtendedKey)
- | WitnessGenesisUTxOKey (SigningKey GenesisUTxOKey)
- | WitnessCommitteeColdKey (SigningKey CommitteeColdKey)
- | WitnessCommitteeColdExtendedKey (SigningKey CommitteeColdExtendedKey)
- | WitnessCommitteeHotKey (SigningKey CommitteeHotKey)
- | WitnessCommitteeHotExtendedKey (SigningKey CommitteeHotExtendedKey)
- | WitnessDRepKey (SigningKey DRepKey)
- | WitnessDRepExtendedKey (SigningKey DRepExtendedKey)
- makeShelleyKeyWitness :: ShelleyBasedEra era -> TxBody era -> ShelleyWitnessSigningKey -> KeyWitness era
- makeShelleyKeyWitness' :: ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> ShelleyWitnessSigningKey -> KeyWitness era
- makeShelleyBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody era -> SigningKey ByronKey -> KeyWitness era
- makeShelleyBasedBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody (ShelleyLedgerEra era) -> SigningKey ByronKey -> KeyWitness era
- newtype TxMetadata = TxMetadata {}
- class AsTxMetadata a where
- asTxMetadata :: a -> TxMetadata
- data TxMetadataValue
- makeTransactionMetadata :: Map Word64 TxMetadataValue -> TxMetadata
- mergeTransactionMetadata :: (TxMetadataValue -> TxMetadataValue -> TxMetadataValue) -> TxMetadata -> TxMetadata -> TxMetadata
- metaTextChunks :: Text -> TxMetadataValue
- metaBytesChunks :: ByteString -> TxMetadataValue
- validateTxMetadata :: TxMetadata -> Either [(Word64, TxMetadataRangeError)] ()
- data TxMetadataRangeError
- data TxMetadataJsonError
- data TxMetadataJsonSchema
- metadataFromJson :: TxMetadataJsonSchema -> Value -> Either TxMetadataJsonError TxMetadata
- metadataToJson :: TxMetadataJsonSchema -> TxMetadata -> Value
- metadataValueFromJsonNoSchema :: Value -> Either TxMetadataJsonSchemaError TxMetadataValue
- metadataValueToJsonNoSchema :: TxMetadataValue -> Value
- data TxMetadataJsonSchemaError
- = TxMetadataJsonNullNotAllowed
- | TxMetadataJsonBoolNotAllowed
- | TxMetadataJsonNumberNotInteger !Double
- | TxMetadataJsonNotObject !Value
- | TxMetadataJsonBadObject ![(Text, Value)]
- | TxMetadataJsonBadMapPair !Value
- | TxMetadataJsonTypeMismatch !Text !Value
- data CIP108 = BaseGovActionMetadata
- data DRepMetadata
- data DRepMetadataReference
- hashDRepMetadata :: ByteString -> (DRepMetadata, Hash DRepMetadata)
- data CIP119 = DrepRegistrationMetadata
- data StakeAddressRequirements era where
- StakeAddrRegistrationConway :: forall era. ConwayEraOnwards era -> Coin -> StakeCredential -> StakeAddressRequirements era
- StakeAddrRegistrationPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> StakeAddressRequirements era
- data StakeDelegationRequirements era where
- StakeDelegationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> StakeCredential -> Delegatee -> StakeDelegationRequirements era
- StakeDelegationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> PoolId -> StakeDelegationRequirements era
- makeStakeAddressDelegationCertificate :: StakeDelegationRequirements era -> Certificate era
- makeStakeAddressRegistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakeAddressUnregistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakeAddressAndDRepDelegationCertificate :: ConwayEraOnwards era -> StakeCredential -> Delegatee -> Coin -> Certificate era
- data StakePoolRegistrationRequirements era where
- StakePoolRegistrationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolParams -> StakePoolRegistrationRequirements era
- StakePoolRegistrationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolParams -> StakePoolRegistrationRequirements era
- data StakePoolRetirementRequirements era where
- StakePoolRetirementRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- StakePoolRetirementRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- makeStakePoolRegistrationCertificate :: StakePoolRegistrationRequirements era -> Certificate era
- makeStakePoolRetirementCertificate :: StakePoolRetirementRequirements era -> Certificate era
- data StakePoolParameters
- data StakePoolMetadataReference
- data AnchorDataFromCertificateError = InvalidPoolMetadataHashError Url ByteString
- getAnchorDataFromCertificate :: Certificate era -> Either AnchorDataFromCertificateError (Maybe Anchor)
- isDRepRegOrUpdateCert :: Certificate era -> Bool
- newtype DelegationsAndRewards = DelegationsAndRewards (Map StakeAddress Coin, Map StakeAddress PoolId)
- mergeDelegsAndRewards :: DelegationsAndRewards -> [(StakeAddress, Maybe Coin, Maybe PoolId)]
- data StakePoolMetadata
- validateAndHashStakePoolMetadata :: ByteString -> Either StakePoolMetadataValidationError (StakePoolMetadata, Hash StakePoolMetadata)
- data StakePoolMetadataValidationError
- data SimpleScript'
- data PlutusScriptV1
- data PlutusScriptVersion lang where
- data PlutusScriptV2
- data PlutusScriptV3
- data ScriptLanguage lang where
- SimpleScriptLanguage :: ScriptLanguage SimpleScript'
- PlutusScriptLanguage :: forall lang. IsPlutusScriptLanguage lang => PlutusScriptVersion lang -> ScriptLanguage lang
- data AnyScriptLanguage where
- AnyScriptLanguage :: forall lang. ScriptLanguage lang -> AnyScriptLanguage
- data AnyPlutusScriptVersion where
- AnyPlutusScriptVersion :: forall lang. IsPlutusScriptLanguage lang => PlutusScriptVersion lang -> AnyPlutusScriptVersion
- class IsScriptLanguage lang => IsPlutusScriptLanguage lang where
- class HasTypeProxy lang => IsScriptLanguage lang where
- scriptLanguage :: ScriptLanguage lang
- data PlutusScriptInEra era lang where
- PlutusScriptInEra :: forall lang era. PlutusScript lang -> PlutusScriptInEra era lang
- data ScriptInAnyLang where
- ScriptInAnyLang :: forall lang. ScriptLanguage lang -> Script lang -> ScriptInAnyLang
- toScriptInAnyLang :: Script lang -> ScriptInAnyLang
- data ScriptInEra era where
- ScriptInEra :: forall lang era. ScriptLanguageInEra lang era -> Script lang -> ScriptInEra era
- toScriptInEra :: ShelleyBasedEra era -> ScriptInAnyLang -> Maybe (ScriptInEra era)
- eraOfScriptInEra :: ScriptInEra era -> ShelleyBasedEra era
- class HasScriptLanguageInEra lang era where
- scriptLanguageInEra :: ScriptLanguageInEra lang era
- class ToAlonzoScript lang era where
- toLedgerScript :: PlutusScript lang -> AlonzoScript (ShelleyLedgerEra era)
- type AlonzoEraOnwardsConstraints era = (HashAlgorithm HASH, Signable (VRF StandardCrypto) Seed, PraosProtocolSupportsNode (ConsensusProtocol era), ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) ~ ConsensusBlockForEra era, ShelleyCompatible (ConsensusProtocol era) (ShelleyLedgerEra era), ADDRHASH ~ Blake2b_224, AlonzoEraPParams (ShelleyLedgerEra era), AlonzoEraTx (ShelleyLedgerEra era), AlonzoEraTxBody (ShelleyLedgerEra era), AlonzoEraTxOut (ShelleyLedgerEra era), AlonzoEraTxWits (ShelleyLedgerEra era), Era (ShelleyLedgerEra era), EraPParams (ShelleyLedgerEra era), EraTx (ShelleyLedgerEra era), EraTxBody (ShelleyLedgerEra era), EraTxOut (ShelleyLedgerEra era), EraUTxO (ShelleyLedgerEra era), HashAnnotated (TxBody (ShelleyLedgerEra era)) EraIndependentTxBody, MaryEraTxBody (ShelleyLedgerEra era), NativeScript (ShelleyLedgerEra era) ~ Timelock (ShelleyLedgerEra era), EraPlutusContext (ShelleyLedgerEra era), Script (ShelleyLedgerEra era) ~ AlonzoScript (ShelleyLedgerEra era), ScriptsNeeded (ShelleyLedgerEra era) ~ AlonzoScriptsNeeded (ShelleyLedgerEra era), ShelleyEraTxCert (ShelleyLedgerEra era), Value (ShelleyLedgerEra era) ~ MaryValue, FromCBOR (ChainDepState (ConsensusProtocol era)), FromCBOR (DebugLedgerState era), IsCardanoEra era, IsShelleyBasedEra era, ToJSON (ChainDepState (ConsensusProtocol era)), ToJSON (DebugLedgerState era), Typeable era, (era == ByronEra) ~ 'False)
- data WitCtxTxIn
- data WitCtx witctx where
- data WitCtxMint
- data WitCtxStake
- data ScriptWitness witctx era where
- SimpleScriptWitness :: forall era witctx. ScriptLanguageInEra SimpleScript' era -> SimpleScriptOrReferenceInput SimpleScript' -> ScriptWitness witctx era
- PlutusScriptWitness :: forall lang era witctx. IsPlutusScriptLanguage lang => ScriptLanguageInEra lang era -> PlutusScriptVersion lang -> PlutusScriptOrReferenceInput lang -> ScriptDatum witctx -> ScriptRedeemer -> ExecutionUnits -> ScriptWitness witctx era
- getScriptWitnessScript :: ScriptWitness witctx era -> Maybe (ScriptInEra era)
- getScriptWitnessReferenceInput :: ScriptWitness witctx era -> Maybe TxIn
- getScriptWitnessReferenceInputOrScript :: ScriptWitness witctx era -> Either (ScriptInEra era) TxIn
- data KeyWitnessInCtx witctx where
- data ScriptWitnessInCtx witctx where
- class IsScriptWitnessInCtx ctx where
- data ScriptDatum witctx where
- type ScriptRedeemer = HashableScriptData
- data AnyScriptWitness era where
- AnyScriptWitness :: forall witctx era. Typeable witctx => ScriptWitness witctx era -> AnyScriptWitness era
- data ScriptWitnessIndex
- renderScriptWitnessIndex :: ScriptWitnessIndex -> String
- collectTxBodyScriptWitnesses :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> [(ScriptWitnessIndex, AnyScriptWitness era)]
- data ScriptLanguageInEra lang era where
- SimpleScriptInShelley :: ScriptLanguageInEra SimpleScript' ShelleyEra
- SimpleScriptInAllegra :: ScriptLanguageInEra SimpleScript' AllegraEra
- SimpleScriptInMary :: ScriptLanguageInEra SimpleScript' MaryEra
- SimpleScriptInAlonzo :: ScriptLanguageInEra SimpleScript' AlonzoEra
- SimpleScriptInBabbage :: ScriptLanguageInEra SimpleScript' BabbageEra
- SimpleScriptInConway :: ScriptLanguageInEra SimpleScript' ConwayEra
- PlutusScriptV1InAlonzo :: ScriptLanguageInEra PlutusScriptV1 AlonzoEra
- PlutusScriptV1InBabbage :: ScriptLanguageInEra PlutusScriptV1 BabbageEra
- PlutusScriptV1InConway :: ScriptLanguageInEra PlutusScriptV1 ConwayEra
- PlutusScriptV2InBabbage :: ScriptLanguageInEra PlutusScriptV2 BabbageEra
- PlutusScriptV2InConway :: ScriptLanguageInEra PlutusScriptV2 ConwayEra
- PlutusScriptV3InConway :: ScriptLanguageInEra PlutusScriptV3 ConwayEra
- scriptLanguageSupportedInEra :: ShelleyBasedEra era -> ScriptLanguage lang -> Maybe (ScriptLanguageInEra lang era)
- sbeToSimpleScriptLanguageInEra :: ShelleyBasedEra era -> ScriptLanguageInEra SimpleScript' era
- languageOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ScriptLanguage lang
- eraOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ShelleyBasedEra era
- examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1
- examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1
- collectPlutusScriptHashes :: AlonzoEraOnwards era -> Tx era -> UTxO era -> Map ScriptWitnessIndex ScriptHash
- data HashableScriptData
- hashScriptDataBytes :: HashableScriptData -> Hash ScriptData
- getOriginalScriptDataBytes :: HashableScriptData -> ByteString
- getScriptData :: HashableScriptData -> ScriptData
- unsafeHashableScriptData :: ScriptData -> HashableScriptData
- data ScriptData
- newtype ScriptDataRangeError = ScriptDataConstructorOutOfRange Integer
- data ScriptDataJsonError
- validateScriptData :: ScriptData -> Either ScriptDataRangeError ()
- data ScriptDataJsonSchema
- scriptDataFromJson :: ScriptDataJsonSchema -> Value -> Either ScriptDataJsonError HashableScriptData
- scriptDataToJson :: ScriptDataJsonSchema -> HashableScriptData -> Value
- data ScriptDataJsonSchemaError
- = ScriptDataJsonNullNotAllowed
- | ScriptDataJsonBoolNotAllowed
- | ScriptDataJsonNumberNotInteger !Double
- | ScriptDataJsonNotObject !Value
- | ScriptDataJsonBadObject ![(Text, Value)]
- | ScriptDataJsonBadMapPair !Value
- | ScriptDataJsonTypeMismatch !Text !Value
- data ScriptDataJsonBytesError
- scriptDataJsonToHashable :: ScriptDataJsonSchema -> Value -> Either ScriptDataJsonBytesError HashableScriptData
- data ExecutionUnits = ExecutionUnits {}
- data ExecutionUnitPrices = ExecutionUnitPrices {}
- toAlonzoCostModel :: CostModel -> Language -> Either ProtocolParametersConversionError CostModel
- fromAlonzoCostModel :: CostModel -> CostModel
- toAlonzoCostModels :: Map AnyPlutusScriptVersion CostModel -> Either ProtocolParametersConversionError CostModels
- data InputFormat a where
- InputFormatBech32 :: forall a. SerialiseAsBech32 a => InputFormat a
- InputFormatHex :: forall a. SerialiseAsRawBytes a => InputFormat a
- InputFormatTextEnvelope :: forall a. HasTextEnvelope a => InputFormat a
- data InputDecodeError
- deserialiseInput :: NonEmpty (InputFormat a) -> ByteString -> Either InputDecodeError a
- deserialiseInputAnyOf :: [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> ByteString -> Either InputDecodeError b
- renderInputDecodeError :: InputDecodeError -> Doc ann
- data SomeAddressVerificationKey
- = AByronVerificationKey (VerificationKey ByronKey)
- | APaymentVerificationKey (VerificationKey PaymentKey)
- | APaymentExtendedVerificationKey (VerificationKey PaymentExtendedKey)
- | AGenesisUTxOVerificationKey (VerificationKey GenesisUTxOKey)
- | AGenesisExtendedVerificationKey (VerificationKey GenesisExtendedKey)
- | AGenesisDelegateExtendedVerificationKey (VerificationKey GenesisDelegateExtendedKey)
- | AKesVerificationKey (VerificationKey KesKey)
- | AVrfVerificationKey (VerificationKey VrfKey)
- | AStakeVerificationKey (VerificationKey StakeKey)
- | AStakeExtendedVerificationKey (VerificationKey StakeExtendedKey)
- | AStakePoolVerificationKey (VerificationKey StakePoolKey)
- | AStakePoolExtendedVerificationKey (VerificationKey StakePoolExtendedKey)
- | ADRepVerificationKey (VerificationKey DRepKey)
- | ADRepExtendedVerificationKey (VerificationKey DRepExtendedKey)
- | ACommitteeColdVerificationKey (VerificationKey CommitteeColdKey)
- | ACommitteeColdExtendedVerificationKey (VerificationKey CommitteeColdExtendedKey)
- | ACommitteeHotVerificationKey (VerificationKey CommitteeHotKey)
- | ACommitteeHotExtendedVerificationKey (VerificationKey CommitteeHotExtendedKey)
- deserialiseAnyVerificationKey :: ByteString -> Either InputDecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyBech32 :: ByteString -> Either Bech32DecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyTextEnvelope :: ByteString -> Either TextEnvelopeError SomeAddressVerificationKey
- renderSomeAddressVerificationKey :: SomeAddressVerificationKey -> Text
- mapSomeAddressVerificationKey :: (forall keyrole. Key keyrole => VerificationKey keyrole -> a) -> SomeAddressVerificationKey -> a
- class HasTypeProxy a => SerialiseAsCBOR a where
- serialiseToCBOR :: a -> ByteString
- deserialiseFromCBOR :: AsType a -> ByteString -> Either DecoderError a
- class ToJSON a
- class FromJSON a
- serialiseToJSON :: ToJSON a => a -> ByteString
- deserialiseFromJSON :: FromJSON a => ByteString -> Either JsonDecodeError a
- newtype JsonDecodeError = JsonDecodeError String
- readFileJSON :: FromJSON a => FilePath -> IO (Either (FileError JsonDecodeError) a)
- writeFileJSON :: ToJSON a => FilePath -> a -> IO (Either (FileError ()) ())
- prettyPrintJSON :: ToJSON a => a -> ByteString
- class (HasTypeProxy a, SerialiseAsRawBytes a) => SerialiseAsBech32 a
- serialiseToBech32 :: SerialiseAsBech32 a => a -> Text
- deserialiseFromBech32 :: SerialiseAsBech32 a => Text -> Either Bech32DecodeError a
- deserialiseAnyOfFromBech32 :: [FromSomeType SerialiseAsBech32 b] -> Text -> Either Bech32DecodeError b
- data Bech32DecodeError
- = Bech32DecodingError !DecodingError
- | Bech32UnexpectedPrefix !Text !(Set Text)
- | Bech32DataPartToBytesError !Text
- | Bech32DeserialiseFromBytesError !ByteString
- | Bech32WrongPrefix !Text !Text
- | Bech32UnexpectedHeader !Text !Text
- newtype UsingBech32 a = UsingBech32 a
- class (SerialiseAsRawBytes a, HasTypeProxy a) => Cip129 a where
- cip129Bech32PrefixFor :: AsType a -> HumanReadablePart
- cip129HeaderHexByte :: a -> ByteString
- cip129Bech32PrefixesPermitted :: AsType a -> [Text]
- deserialiseFromBech32Cip129 :: Cip129 a => Text -> Either Bech32DecodeError a
- serialiseToBech32Cip129 :: Cip129 a => a -> Text
- serialiseGovActionIdToBech32Cip129 :: GovActionId -> Text
- deserialiseGovActionIdFromBech32Cip129 :: Text -> Either Bech32DecodeError GovActionId
- class HasTypeProxy addr => SerialiseAddress addr where
- serialiseAddress :: addr -> Text
- deserialiseAddress :: AsType addr -> Text -> Maybe addr
- class (HasTypeProxy a, Typeable a) => SerialiseAsRawBytes a where
- serialiseToRawBytes :: a -> ByteString
- deserialiseFromRawBytes :: AsType a -> ByteString -> Either SerialiseAsRawBytesError a
- newtype SerialiseAsRawBytesError = SerialiseAsRawBytesError {}
- serialiseToRawBytesHex :: SerialiseAsRawBytes a => a -> ByteString
- deserialiseFromRawBytesHex :: SerialiseAsRawBytes a => ByteString -> Either RawBytesHexError a
- serialiseToRawBytesHexText :: SerialiseAsRawBytes a => a -> Text
- data RawBytesHexError
- newtype UsingRawBytes a = UsingRawBytes a
- newtype UsingRawBytesHex a = UsingRawBytesHex a
- class SerialiseAsCBOR a => HasTextEnvelope a where
- data TextEnvelope = TextEnvelope {}
- newtype TextEnvelopeType = TextEnvelopeType String
- data TextEnvelopeDescr
- data TextEnvelopeError
- textEnvelopeTypeInEra :: HasTextEnvelope (f era) => CardanoEra era -> AsType (f era) -> TextEnvelopeType
- textEnvelopeRawCBOR :: TextEnvelope -> ByteString
- textEnvelopeToJSON :: HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString
- serialiseToTextEnvelope :: HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> TextEnvelope
- deserialiseFromTextEnvelope :: HasTextEnvelope a => TextEnvelope -> Either TextEnvelopeError a
- readFileTextEnvelope :: HasTextEnvelope a => File content 'In -> IO (Either (FileError TextEnvelopeError) a)
- writeFileTextEnvelope :: HasTextEnvelope a => File content 'Out -> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
- readTextEnvelopeFromFile :: FilePath -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
- readTextEnvelopeOfTypeFromFile :: TextEnvelopeType -> FilePath -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
- data FromSomeTypeCDDL c b where
- FromCDDLTx :: forall b. Text -> (InAnyShelleyBasedEra Tx -> b) -> FromSomeTypeCDDL TextEnvelope b
- FromCDDLWitness :: forall b. Text -> (InAnyShelleyBasedEra KeyWitness -> b) -> FromSomeTypeCDDL TextEnvelope b
- readFileTextEnvelopeCddlAnyOf :: [FromSomeTypeCDDL TextEnvelope b] -> FilePath -> IO (Either (FileError TextEnvelopeCddlError) b)
- deserialiseFromTextEnvelopeCddlAnyOf :: [FromSomeTypeCDDL TextEnvelope b] -> TextEnvelope -> Either TextEnvelopeCddlError b
- writeTxFileTextEnvelopeCddl :: ShelleyBasedEra era -> File content 'Out -> Tx era -> IO (Either (FileError ()) ())
- writeTxFileTextEnvelopeCanonicalCddl :: ShelleyBasedEra era -> File content 'Out -> Tx era -> IO (Either (FileError ()) ())
- writeTxWitnessFileTextEnvelopeCddl :: ShelleyBasedEra era -> File () 'Out -> KeyWitness era -> IO (Either (FileError ()) ())
- deserialiseByronTxCddl :: TextEnvelope -> Either TextEnvelopeCddlError (ATxAux ByteString)
- serialiseWitnessLedgerCddl :: ShelleyBasedEra era -> KeyWitness era -> TextEnvelope
- deserialiseWitnessLedgerCddl :: ShelleyBasedEra era -> TextEnvelope -> Either TextEnvelopeCddlError (KeyWitness era)
- data TextEnvelopeCddlError
- readKeyFile :: NonEmpty (InputFormat a) -> FilePath -> IO (Either (FileError InputDecodeError) a)
- readKeyFileTextEnvelope :: HasTextEnvelope a => File content 'In -> IO (Either (FileError InputDecodeError) a)
- readKeyFileAnyOf :: forall content b. [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError InputDecodeError) b)
- data FromSomeType (c :: Type -> Constraint) b where
- FromSomeType :: forall (c :: Type -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b
- deserialiseFromTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b] -> TextEnvelope -> Either TextEnvelopeError b
- readFileTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError TextEnvelopeError) b)
- throwErrorAsException :: Error e => e -> IO a
- data FileError e
- data NodeConfig = NodeConfig {
- ncPBftSignatureThreshold :: !(Maybe Double)
- ncByronGenesisFile :: !(File ByronGenesisConfig 'In)
- ncByronGenesisHash :: !GenesisHashByron
- ncShelleyGenesisFile :: !(File ShelleyGenesisConfig 'In)
- ncShelleyGenesisHash :: !GenesisHashShelley
- ncAlonzoGenesisFile :: !(File AlonzoGenesis 'In)
- ncAlonzoGenesisHash :: !GenesisHashAlonzo
- ncConwayGenesisFile :: !(Maybe (File ConwayGenesisConfig 'In))
- ncConwayGenesisHash :: !(Maybe GenesisHashConway)
- ncRequiresNetworkMagic :: !RequiresNetworkMagic
- ncByronProtocolVersion :: !ProtocolVersion
- ncHardForkTriggers :: !CardanoHardForkTriggers
- type NodeConfigFile = File NodeConfig
- readNodeConfig :: (MonadError Text m, MonadIO m) => NodeConfigFile 'In -> m NodeConfig
- type ByronGenesisFile = File ByronGenesisConfig
- type ShelleyGenesisFile = File ShelleyGenesisConfig
- type AlonzoGenesisFile = File AlonzoGenesisConfig
- type ConwayGenesisFile = File ConwayGenesisConfig
- readCardanoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m GenesisConfig
- mkProtocolInfoCardano :: GenesisConfig -> (ProtocolInfo (CardanoBlock StandardCrypto), IO [BlockForging IO (CardanoBlock StandardCrypto)])
- readByronGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m Config
- newtype GenesisHashByron = GenesisHashByron {}
- newtype GenesisHashShelley = GenesisHashShelley {}
- readShelleyGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m ShelleyConfig
- shelleyPraosNonce :: GenesisHashShelley -> Nonce
- newtype GenesisHashAlonzo = GenesisHashAlonzo {}
- readAlonzoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m AlonzoGenesis
- newtype GenesisHashConway = GenesisHashConway {}
- readConwayGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m ConwayGenesis
- data Env = Env {}
- genesisConfigToEnv :: GenesisConfig -> Either GenesisConfigError Env
- envSecurityParam :: Env -> Word64
- initialLedgerState :: forall t (m :: Type -> Type). MonadIOTransError InitialLedgerStateError t m => NodeConfigFile 'In -> t m (Env, LedgerState)
- encodeLedgerState :: LedgerState -> Encoding
- decodeLedgerState :: Decoder s LedgerState
- foldBlocks :: forall a t (m :: Type -> Type). (Show a, MonadIOTransError FoldBlocksError t m) => NodeConfigFile 'In -> SocketPath -> ValidationMode -> a -> (Env -> LedgerState -> [LedgerEvent] -> BlockInMode -> a -> IO (a, FoldStatus)) -> t m a
- data FoldStatus
- chainSyncClientWithLedgerState :: forall (m :: Type -> Type) a. Monad m => Env -> LedgerState -> ValidationMode -> ChainSyncClient (BlockInMode, Either LedgerStateError (LedgerState, [LedgerEvent])) ChainPoint ChainTip m a -> ChainSyncClient BlockInMode ChainPoint ChainTip m a
- chainSyncClientPipelinedWithLedgerState :: forall (m :: Type -> Type) a. Monad m => Env -> LedgerState -> ValidationMode -> ChainSyncClientPipelined (BlockInMode, Either LedgerStateError (LedgerState, [LedgerEvent])) ChainPoint ChainTip m a -> ChainSyncClientPipelined BlockInMode ChainPoint ChainTip m a
- data ConditionResult
- fromConditionResult :: ConditionResult -> Bool
- toConditionResult :: Bool -> ConditionResult
- data AnyNewEpochState where
- AnyNewEpochState :: forall era. ShelleyBasedEra era -> NewEpochState (ShelleyLedgerEra era) -> LedgerTables (LedgerState (CardanoBlock StandardCrypto)) ValuesMK -> AnyNewEpochState
- foldEpochState :: forall t (m :: Type -> Type) s. MonadIOTransError FoldBlocksError t m => NodeConfigFile 'In -> SocketPath -> ValidationMode -> EpochNo -> s -> (AnyNewEpochState -> SlotNo -> BlockNo -> StateT s IO ConditionResult) -> t m (ConditionResult, s)
- getAnyNewEpochState :: ShelleyBasedEra era -> LedgerState -> Either LedgerStateError AnyNewEpochState
- getLedgerTablesUTxOValues :: ShelleyBasedEra era -> LedgerTables (LedgerState (CardanoBlock StandardCrypto)) ValuesMK -> Map TxIn (TxOut CtxUTxO era)
- data LedgerStateError
- = ApplyBlockHashMismatch Text
- | ApplyBlockError (CardanoLedgerError StandardCrypto)
- | InvalidRollback SlotNo ChainPoint
- | TerminationEpochReached EpochNo
- | UnexpectedLedgerState AnyShelleyBasedEra (NS (Current (Flip LedgerState EmptyMK)) (CardanoEras StandardCrypto))
- | ByronEraUnsupported
- | DebugError !String
- data FoldBlocksError
- data GenesisConfigError
- data InitialLedgerStateError
- connectToLocalNode :: MonadIO m => LocalNodeConnectInfo -> LocalNodeClientProtocolsInMode -> m ()
- connectToLocalNodeWithVersion :: MonadIO m => LocalNodeConnectInfo -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> m ()
- data LocalNodeConnectInfo = LocalNodeConnectInfo {}
- data ConsensusModeParams where
- type family ChainDepStateProtocol era where ...
- type family ConsensusBlockForEra era where ...
- data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) = LocalNodeClientProtocols {
- localChainSyncClient :: LocalChainSyncClient block point tip m
- localTxSubmissionClient :: Maybe (LocalTxSubmissionClient tx txerr m ())
- localStateQueryClient :: Maybe (LocalStateQueryClient block point query m ())
- localTxMonitoringClient :: Maybe (LocalTxMonitorClient txid tx slot m ())
- data LocalNodeClientParams where
- LocalNodeClientParamsSingleBlock :: forall block. (ProtocolClient block, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) ShelleyEra)) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- LocalNodeClientParamsCardano :: forall block. (ProtocolClient block, CardanoHardForkConstraints (ConsensusCryptoForBlock block)) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- mkLocalNodeClientParams :: ConsensusModeParams -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> LocalNodeClientParams
- data LocalChainSyncClient block point tip (m :: Type -> Type)
- = NoLocalChainSyncClient
- | LocalChainSyncClientPipelined (ChainSyncClientPipelined block point tip m ())
- | LocalChainSyncClient (ChainSyncClient block point tip m ())
- data BlockType blk where
- data SomeBlockType where
- SomeBlockType :: forall blk. BlockType blk -> SomeBlockType
- reflBlockType :: BlockType blk -> BlockType blk' -> Maybe (blk :~: blk')
- class (RunNode blk, IOLike m) => Protocol (m :: Type -> Type) blk where
- data ProtocolInfoArgs blk
- protocolInfo :: ProtocolInfoArgs blk -> (ProtocolInfo blk, m [BlockForging m blk])
- data family ProtocolInfoArgs blk
- data BlockInMode where
- BlockInMode :: forall era. CardanoEra era -> Block era -> BlockInMode
- type LocalNodeClientProtocolsInMode = LocalNodeClientProtocols BlockInMode ChainPoint ChainTip SlotNo TxInMode TxIdInMode TxValidationErrorInCardanoMode QueryInMode IO
- data TxInMode where
- TxInMode :: forall era. ShelleyBasedEra era -> Tx era -> TxInMode
- TxInByronSpecial :: GenTx ByronBlock -> TxInMode
- data TxValidationErrorInCardanoMode where
- submitTxToNodeLocal :: MonadIO m => LocalNodeConnectInfo -> TxInMode -> m (SubmitResult TxValidationErrorInCardanoMode)
- data QueryInMode result where
- QueryCurrentEra :: QueryInMode AnyCardanoEra
- QueryInEra :: forall era result1. QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
- QueryEraHistory :: QueryInMode EraHistory
- QuerySystemStart :: QueryInMode SystemStart
- QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo)
- QueryChainPoint :: QueryInMode ChainPoint
- QueryLedgerConfig :: QueryInMode (HardForkLedgerConfig (CardanoEras StandardCrypto))
- data QueryInEra era result where
- QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState
- QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result
- data QueryUTxOFilter
- queryNodeLocalState :: LocalNodeConnectInfo -> Target ChainPoint -> QueryInMode result -> ExceptT AcquiringFailure IO result
- executeQueryCardanoMode :: SocketPath -> NetworkId -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- data UnsupportedNtcVersionError = UnsupportedNtcVersionError !NodeToClientVersion ![NodeToClientVersion]
- data LocalTxMonitoringQuery
- data LocalTxMonitoringResult
- queryTxMonitoringLocal :: MonadIO m => LocalNodeConnectInfo -> LocalTxMonitoringQuery -> m LocalTxMonitoringResult
- data TxIdInMode where
- TxIdInMode :: forall era. CardanoEra era -> TxId -> TxIdInMode
- data EraHistory where
- EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory
- getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength)
- getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo
- determineEra :: LocalNodeConnectInfo -> ExceptT AcquiringFailure IO AnyCardanoEra
- getLocalChainTip :: MonadIO m => LocalNodeConnectInfo -> m ChainTip
- data OperationalCertificate
- data OperationalCertificateIssueCounter
- data OperationalCertIssueError
- getHotKey :: OperationalCertificate -> VerificationKey KesKey
- getKesPeriod :: OperationalCertificate -> Word
- getOpCertCount :: OperationalCertificate -> Word64
- issueOperationalCertificate :: VerificationKey KesKey -> Either AnyStakePoolSigningKey (SigningKey GenesisDelegateExtendedKey) -> KESPeriod -> OperationalCertificateIssueCounter -> Either OperationalCertIssueError (OperationalCertificate, OperationalCertificateIssueCounter)
- data CommitteeColdKey
- data CommitteeColdExtendedKey
- data CommitteeHotKey
- data CommitteeHotExtendedKey
- data GenesisKey
- data GenesisExtendedKey
- data GenesisDelegateKey
- data GenesisDelegateExtendedKey
- data GenesisUTxOKey
- genesisUTxOPseudoTxIn :: NetworkId -> Hash GenesisUTxOKey -> TxIn
- data GenesisParameters era = GenesisParameters {
- protocolParamSystemStart :: UTCTime
- protocolParamNetworkId :: NetworkId
- protocolParamActiveSlotsCoefficient :: Rational
- protocolParamSecurity :: NonZero Word64
- protocolParamEpochLength :: EpochSize
- protocolParamSlotLength :: NominalDiffTime
- protocolParamSlotsPerKESPeriod :: Int
- protocolParamMaxKESEvolutions :: Int
- protocolParamUpdateQuorum :: Int
- protocolParamMaxLovelaceSupply :: Coin
- protocolInitialUpdateableProtocolParameters :: PParams (ShelleyLedgerEra era)
- data GenesisKeyDelegationRequirements era where
- GenesisKeyDelegationRequirements :: forall era. ShelleyToBabbageEra era -> Hash GenesisKey -> Hash GenesisDelegateKey -> Hash VrfKey -> GenesisKeyDelegationRequirements era
- data MirCertificateRequirements era where
- MirCertificateRequirements :: forall era. ShelleyToBabbageEra era -> MIRPot -> MIRTarget -> MirCertificateRequirements era
- makeMIRCertificate :: Typeable era => MirCertificateRequirements era -> Certificate era
- makeGenesisKeyDelegationCertificate :: Typeable era => GenesisKeyDelegationRequirements era -> Certificate era
- selectStakeCredentialWitness :: Certificate era -> Maybe StakeCredential
- data UpdateProposal = UpdateProposal !(Map (Hash GenesisKey) ProtocolParametersUpdate) !EpochNo
- makeShelleyUpdateProposal :: ProtocolParametersUpdate -> [Hash GenesisKey] -> EpochNo -> UpdateProposal
- data PraosNonce
- makePraosNonce :: ByteString -> PraosNonce
- data ProtocolParametersConversionError
- = PpceOutOfBounds !ProtocolParameterName !Rational
- | PpceVersionInvalid !ProtocolParameterVersion
- | PpceInvalidCostModel !CostModel !CostModelApplyError
- | PpceMissingParameter !ProtocolParameterName
- toCtxUTxOTxOut :: TxOut CtxTx era -> TxOut CtxUTxO era
- fromCtxUTxOTxOut :: TxOut CtxUTxO era -> TxOut CtxTx era
- fromNetworkMagic :: NetworkMagic -> NetworkId
- toNetworkMagic :: NetworkId -> NetworkMagic
- fromLedgerTxOuts :: ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> TxBodyScriptData era -> [TxOut CtxTx era]
- toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO (ShelleyLedgerEra era)
- fromLedgerUTxO :: ShelleyBasedEra era -> UTxO (ShelleyLedgerEra era) -> UTxO era
- runParsecParser :: Parser a -> Text -> Parser a
- newtype SlotsInEpoch = SlotsInEpoch Word64
- newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
- type SocketPath = File Socket 'InOut
- executeQueryAnyMode :: LocalNodeConnectInfo -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- data LocalStateQueryExpr block point (query :: Type -> Type) r (m :: Type -> Type) a
- executeLocalStateQueryExpr :: LocalNodeConnectInfo -> Target ChainPoint -> LocalStateQueryExpr BlockInMode ChainPoint QueryInMode () IO a -> IO (Either AcquiringFailure a)
- queryExpr :: QueryInMode a -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
- chainPointToSlotNo :: ChainPoint -> Maybe SlotNo
- chainPointToHeaderHash :: ChainPoint -> Maybe (Hash BlockHeader)
- makeChainTip :: WithOrigin BlockNo -> ChainPoint -> ChainTip
- writeSecrets :: FilePath -> [Char] -> [Char] -> (a -> ByteString) -> [a] -> IO ()
- constructBalancedTx :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> UTxO era -> LedgerProtocolParameters era -> LedgerEpochInfo -> SystemStart -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> [ShelleyWitnessSigningKey] -> Either (TxBodyErrorAutoBalance era) (Tx era)
- data QueryConvenienceError
- newtype TxCurrentTreasuryValue = TxCurrentTreasuryValue {}
- queryStateForBalancedTx :: CardanoEra era -> [TxIn] -> [Certificate era] -> LocalStateQueryExpr block point QueryInMode r IO (Either QueryConvenienceError (UTxO era, LedgerProtocolParameters era, EraHistory, SystemStart, Set PoolId, Map StakeCredential Coin, Map (Credential 'DRepRole) Coin, Maybe (Featured ConwayEraOnwards era TxCurrentTreasuryValue)))
- renderQueryConvenienceError :: QueryConvenienceError -> Text
- newtype ScriptLockedTxInsError = ScriptLockedTxIns [TxIn]
- data TxInsExistError
- = TxInsDoNotExist [TxIn]
- | EmptyUTxO
- renderNotScriptLockedTxInsError :: ScriptLockedTxInsError -> Text
- renderTxInsExistError :: TxInsExistError -> Text
- txInsExistInUTxO :: [TxIn] -> UTxO era -> Either TxInsExistError ()
- notScriptLockedTxIns :: [TxIn] -> UTxO era -> Either ScriptLockedTxInsError ()
- textShow :: Show a => a -> Text
- queryChainBlockNo :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (WithOrigin BlockNo))
- queryChainPoint :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError ChainPoint)
- queryCurrentEpochState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedCurrentEpochState era)))
- queryCurrentEra :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError AnyCardanoEra)
- queryDebugLedgerState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedDebugLedgerState era)))
- queryLedgerPeerSnapshot :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Serialised LedgerPeerSnapshot)))
- queryEpoch :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
- queryEraHistory :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError EraHistory)
- queryGenesisParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GenesisParameters ShelleyEra)))
- queryPoolDistribution :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolDistribution era)))
- queryPoolState :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolState era)))
- queryProtocolParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (PParams (ShelleyLedgerEra era))))
- queryProtocolState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (ProtocolState era)))
- queryStakeAddresses :: ShelleyBasedEra era -> Set StakeCredential -> NetworkId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId)))
- queryStakeDelegDeposits :: BabbageEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential Coin)))
- queryStakeDistribution :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Hash StakePoolKey) Rational)))
- queryStakePoolParameters :: ShelleyBasedEra era -> Set PoolId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map PoolId StakePoolParameters)))
- queryStakePools :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
- queryStakeSnapshot :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedStakeSnapshots era)))
- querySystemStart :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError SystemStart)
- queryUtxo :: ShelleyBasedEra era -> QueryUTxOFilter -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
- queryDRepStakeDistribution :: ConwayEraOnwards era -> Set DRep -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin)))
- querySPOStakeDistribution :: ConwayEraOnwards era -> Set (KeyHash 'StakePool) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (KeyHash 'StakePool) Coin)))
- queryStakeVoteDelegatees :: ConwayEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential DRep)))
- queryLedgerConfig :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (CardanoLedgerConfig StandardCrypto))
- data DRepKey
- data DRepExtendedKey
- getAnchorDataFromGovernanceAction :: GovAction (ShelleyLedgerEra era) -> Maybe Anchor
- validateGovActionAnchorData :: FromJSON (GovActionMetadata cip) => cip -> ByteString -> Either String ()
- newtype AnchorDataHash = AnchorDataHash {}
- newtype AnchorUrl = AnchorUrl {
- unAnchorUrl :: Url
- data CommitteeColdkeyResignationRequirements era where
- CommitteeColdkeyResignationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Maybe Anchor -> CommitteeColdkeyResignationRequirements era
- data CommitteeHotKeyAuthorizationRequirements era where
- CommitteeHotKeyAuthorizationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> CommitteeHotKeyAuthorizationRequirements era
- data DRepRegistrationRequirements era where
- DRepRegistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole -> Coin -> DRepRegistrationRequirements era
- data DRepUnregistrationRequirements era where
- DRepUnregistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole -> Coin -> DRepUnregistrationRequirements era
- data DRepUpdateRequirements era where
- DRepUpdateRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole -> DRepUpdateRequirements era
- makeCommitteeColdkeyResignationCertificate :: Typeable era => CommitteeColdkeyResignationRequirements era -> Certificate era
- makeCommitteeHotKeyAuthorizationCertificate :: Typeable era => CommitteeHotKeyAuthorizationRequirements era -> Certificate era
- makeDrepRegistrationCertificate :: Typeable era => DRepRegistrationRequirements era -> Maybe Anchor -> Certificate era
- makeDrepUnregistrationCertificate :: Typeable era => DRepUnregistrationRequirements era -> Certificate era
- makeDrepUpdateCertificate :: Typeable era => DRepUpdateRequirements era -> Maybe Anchor -> Certificate era
- data ResolvablePointers where
- ResolvablePointers :: forall era. (Era (ShelleyLedgerEra era), Show (PlutusPurpose AsIx (ShelleyLedgerEra era)), Show (PlutusPurpose AsItem (ShelleyLedgerEra era)), Show (PlutusScript (ShelleyLedgerEra era))) => ShelleyBasedEra era -> !(Map (PlutusPurpose AsIx (ShelleyLedgerEra era)) (PlutusPurpose AsItem (ShelleyLedgerEra era), Maybe (PlutusScriptBytes, Language), ScriptHash)) -> ResolvablePointers
- unsafeBoundedRational :: (HasCallStack, Typeable r, BoundedRational r) => Rational -> r
- data DebugPlutusFailure = DebugPlutusFailure {}
- renderDebugPlutusFailure :: DebugPlutusFailure -> Text
- handleIOExceptT :: forall (m :: Type -> Type) x a. MonadIO m => (IOException -> x) -> IO a -> ExceptT x m a
- prettyException :: Exception a => a -> Doc ann
- newtype ShowOf a = ShowOf a
- docToText :: Doc AnsiStyle -> Text
- docToLazyText :: Doc AnsiStyle -> Text
- docToString :: Doc AnsiStyle -> String
- pshow :: Show a => a -> Doc ann
- vsep :: [Doc ann] -> Doc ann
- black :: Doc AnsiStyle -> Doc AnsiStyle
- red :: Doc AnsiStyle -> Doc AnsiStyle
- green :: Doc AnsiStyle -> Doc AnsiStyle
- yellow :: Doc AnsiStyle -> Doc AnsiStyle
- blue :: Doc AnsiStyle -> Doc AnsiStyle
- magenta :: Doc AnsiStyle -> Doc AnsiStyle
- cyan :: Doc AnsiStyle -> Doc AnsiStyle
- white :: Doc AnsiStyle -> Doc AnsiStyle
- firstExceptT :: forall (m :: Type -> Type) x y a. Functor m => (x -> y) -> ExceptT x m a -> ExceptT y m a
- hoistEither :: forall (m :: Type -> Type) x a. Monad m => Either x a -> ExceptT x m a
- newExceptT :: m (Either x a) -> ExceptT x m a
- pattern ShelleyAddress :: Network -> PaymentCredential -> StakeReference -> Address ShelleyAddr
- pattern ByronAddress :: Address -> Address ByronAddr
- type MonadTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (Monad m, MonadTrans t, MonadError e (t m))
- type MonadIOTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (MonadIO m, MonadIO (t m), MonadCatch m, MonadTrans t, MonadError e (t m))
- liftExceptT :: forall e t (m :: Type -> Type) a. MonadTransError e t m => ExceptT e m a -> t m a
- handleIOExceptionsWith :: (MonadError e' m, MonadCatch m, Exception e) => (e -> e') -> m a -> m a
- handleIOExceptionsLiftWith :: (MonadIOTransError e' t m, Exception e) => (e -> e') -> m a -> t m a
- hoistIOEither :: forall e t (m :: Type -> Type) a. MonadIOTransError e t m => IO (Either e a) -> t m a
- liftMaybe :: MonadError e m => e -> Maybe a -> m a
- bimapExceptT :: forall (m :: Type -> Type) x y a b. Functor m => (x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b
- bracketExceptT :: forall (m :: Type -> Type) e a b c. Monad m => ExceptT e m a -> (a -> ExceptT e m b) -> (a -> ExceptT e m c) -> ExceptT e m c
- bracketExceptionT :: forall (m :: Type -> Type) e a c b. MonadMask m => ExceptT e m a -> (a -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m b
- catchExceptT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> ExceptT x m a
- catchIOExceptT :: forall (m :: Type -> Type) a x. MonadIO m => IO a -> (IOException -> x) -> ExceptT x m a
- catchLeftT :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a
- catchesExceptT :: (Foldable f, MonadCatch m) => m a -> f (Handler m x) -> ExceptT x m a
- exceptT :: Monad m => (x -> m b) -> (a -> m b) -> ExceptT x m a -> m b
- handleExceptT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> ExceptT x m a
- handleLeftT :: forall (m :: Type -> Type) e a. Monad m => (e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a
- handlesExceptT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> ExceptT x m a
- hoistExceptT :: (forall b. m b -> n b) -> ExceptT x m a -> ExceptT x n a
- hushM :: Monad m => Either e a -> (e -> m ()) -> m (Maybe a)
- onLeft :: forall e x (m :: Type -> Type) a. Monad m => (e -> ExceptT x m a) -> ExceptT x m (Either e a) -> ExceptT x m a
- onNothing :: forall x (m :: Type -> Type) a. Monad m => ExceptT x m a -> ExceptT x m (Maybe a) -> ExceptT x m a
- secondExceptT :: forall (m :: Type -> Type) a b x. Functor m => (a -> b) -> ExceptT x m a -> ExceptT x m b
- pattern ConwayCertificate :: ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era
- pattern ShelleyRelatedCertificate :: ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era
- data family AsType t
- data family VerificationKey keyrole
- data family SigningKey keyrole
- data SomeByronSigningKey
- data family Hash keyrole
- data NetworkId
- data KeyWitness era where
- data WitnessNetworkIdOrByronAddress
- class Error e where
- prettyError :: e -> Doc ann
- data FileError e
- 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 ()))
- newtype ChainSyncClient header point tip (m :: Type -> Type) a = ChainSyncClient {
- runChainSyncClient :: m (ClientStIdle header point tip m a)
- newtype LocalTxSubmissionClient tx reject (m :: Type -> Type) a = LocalTxSubmissionClient (m (LocalTxClientStIdle tx reject m a))
- newtype LocalStateQueryClient block point (query :: Type -> Type) (m :: Type -> Type) a = LocalStateQueryClient {
- runLocalStateQueryClient :: m (ClientStIdle block point query m a)
- newtype ByronUpdateProposal = ByronUpdateProposal {}
- data ByronProtocolParametersUpdate = ByronProtocolParametersUpdate {
- bPpuScriptVersion :: !(Maybe Word16)
- bPpuSlotDuration :: !(Maybe Natural)
- bPpuMaxBlockSize :: !(Maybe Natural)
- bPpuMaxHeaderSize :: !(Maybe Natural)
- bPpuMaxTxSize :: !(Maybe Natural)
- bPpuMaxProposalSize :: !(Maybe Natural)
- bPpuMpcThd :: !(Maybe LovelacePortion)
- bPpuHeavyDelThd :: !(Maybe LovelacePortion)
- bPpuUpdateVoteThd :: !(Maybe LovelacePortion)
- bPpuUpdateProposalThd :: !(Maybe LovelacePortion)
- bPpuUpdateProposalTTL :: !(Maybe SlotNumber)
- bPpuSoftforkRule :: !(Maybe SoftforkRule)
- bPpuTxFeePolicy :: !(Maybe TxFeePolicy)
- bPpuUnlockStakeEpoch :: !(Maybe EpochNumber)
- makeByronUpdateProposal :: NetworkId -> ProtocolVersion -> SoftwareVersion -> SystemTag -> InstallerHash -> SomeByronSigningKey -> ByronProtocolParametersUpdate -> ByronUpdateProposal
- toByronLedgerUpdateProposal :: ByronUpdateProposal -> GenTx ByronBlock
- makeProtocolParametersUpdate :: ByronProtocolParametersUpdate -> ProtocolParametersUpdate
- newtype ByronVote = ByronVote {}
- makeByronVote :: NetworkId -> SomeByronSigningKey -> ByronUpdateProposal -> Bool -> ByronVote
- toByronLedgertoByronVote :: ByronVote -> GenTx ByronBlock
- fromByronTxIn :: TxIn -> TxIn
- toByronLovelace :: Lovelace -> Maybe Lovelace
- toByronNetworkMagic :: NetworkId -> NetworkMagic
- toByronProtocolMagicId :: NetworkId -> ProtocolMagicId
- toByronRequiresNetworkMagic :: NetworkId -> RequiresNetworkMagic
- applicationName :: ApplicationName
- applicationVersion :: NumSoftwareVersion
- softwareVersion :: SoftwareVersion
- serializeByronTx :: ATxAux ByteString -> TextEnvelope
- writeByronTxFileTextEnvelopeCddl :: File content 'Out -> ATxAux ByteString -> IO (Either (FileError ()) ())
- data AddrAttributes = AddrAttributes {}
- data Address
- data KeyHash
- addressDetailedF :: Format r (Address -> r)
- addressF :: Format r (Address -> r)
- addressHash :: EncCBOR a => a -> AddressHash a
- checkVerKeyAddress :: VerificationKey -> Address -> Bool
- decodeAddressBase58 :: Text -> Either DecoderError Address
- mkAttributes :: h -> Attributes h
- data Lovelace
- data LovelacePortion
- lovelacePortionToRational :: LovelacePortion -> Rational
- mkKnownLovelace :: forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace
- rationalToLovelacePortion :: Rational -> LovelacePortion
- data Config = Config {}
- data FakeAvvmOptions = FakeAvvmOptions {
- faoCount :: !Word
- faoOneBalance :: !Lovelace
- data GeneratedSecrets = GeneratedSecrets {
- gsDlgIssuersSecrets :: ![SigningKey]
- gsRichSecrets :: ![SigningKey]
- gsPoorSecrets :: ![PoorSecret]
- gsFakeAvvmSecrets :: ![RedeemSigningKey]
- newtype GenesisAvvmBalances = GenesisAvvmBalances {}
- data GenesisData = GenesisData {}
- data GenesisDataError
- = GenesisDataParseError Text
- | GenesisDataSchemaError SchemaError
- | GenesisDataIOError IOException
- data GenesisDataGenerationError
- newtype GenesisDelegation = UnsafeGenesisDelegation {}
- data GenesisDelegationError
- newtype GenesisHash = GenesisHash {
- unGenesisHash :: Hash Raw
- data GenesisInitializer = GenesisInitializer {}
- data GenesisSpec = UnsafeGenesisSpec {}
- data NetworkMagic
- newtype PoorSecret = PoorSecret {}
- data TestnetBalanceOptions = TestnetBalanceOptions {
- tboPoors :: !Word
- tboRichmen :: !Word
- tboTotalBalance :: !Lovelace
- tboRichmenShare :: !Rational
- data TxFeePolicy = TxFeePolicyTxSizeLinear !TxSizeLinear
- data TxSizeLinear = TxSizeLinear !Lovelace !Rational
- generateGenesisData :: UTCTime -> GenesisSpec -> ExceptT GenesisDataGenerationError IO (GenesisData, GeneratedSecrets)
- mkGenesisDelegation :: MonadError GenesisDelegationError m => [Certificate] -> m GenesisDelegation
- mkGenesisSpec :: GenesisAvvmBalances -> GenesisDelegation -> ProtocolParameters -> BlockCount -> ProtocolMagic -> GenesisInitializer -> Either Text GenesisSpec
- readGenesisData :: (MonadError GenesisDataError m, MonadIO m) => FilePath -> m (GenesisData, GenesisHash)
- newtype ApplicationName = ApplicationName {}
- newtype InstallerHash = InstallerHash {}
- type NumSoftwareVersion = Word32
- type Proposal = AProposal ()
- data ProtocolParameters = ProtocolParameters {
- ppScriptVersion :: !Word16
- ppSlotDuration :: !Natural
- ppMaxBlockSize :: !Natural
- ppMaxHeaderSize :: !Natural
- ppMaxTxSize :: !Natural
- ppMaxProposalSize :: !Natural
- ppMpcThd :: !LovelacePortion
- ppHeavyDelThd :: !LovelacePortion
- ppUpdateVoteThd :: !LovelacePortion
- ppUpdateProposalThd :: !LovelacePortion
- ppUpdateProposalTTL :: !SlotNumber
- ppSoftforkRule :: !SoftforkRule
- ppTxFeePolicy :: !TxFeePolicy
- ppUnlockStakeEpoch :: !EpochNumber
- data ProtocolVersion = ProtocolVersion {}
- data SoftforkRule = SoftforkRule {}
- data SoftwareVersion = SoftwareVersion {}
- newtype SystemTag = SystemTag {
- getSystemTag :: Text
- type Vote = AVote ()
- checkApplicationName :: MonadError ApplicationNameError m => ApplicationName -> m ()
- checkSystemTag :: MonadError SystemTagError m => SystemTag -> m ()
- newtype BlockCount = BlockCount {}
- newtype EpochNumber = EpochNumber {}
- newtype SlotNumber = SlotNumber {}
- decCBORABlockOrBoundary :: EpochSlots -> Decoder s (ABlockOrBoundary ByteSpan)
- data ATxAux a = ATxAux {
- aTaTx :: !(Annotated Tx a)
- aTaWitness :: !(Annotated TxWitness a)
- aTaAnnotation :: !a
- data CompactTxIn
- data CompactTxOut
- data Tx = UnsafeTx {
- txInputs :: !(NonEmpty TxIn)
- txOutputs :: !(NonEmpty TxOut)
- txAttributes :: !TxAttributes
- data TxIn = TxInUtxo TxId Word16
- data TxOut = TxOut {
- txOutAddress :: !Address
- txOutValue :: !Lovelace
- newtype UTxO = UTxO {}
- defaultUTxOConfiguration :: UTxOConfiguration
- fromCompactTxIn :: CompactTxIn -> TxIn
- fromCompactTxOut :: CompactTxOut -> TxOut
- genesisUtxo :: Config -> UTxO
- data ACertificate a = UnsafeACertificate {
- aEpoch :: !(Annotated EpochNumber a)
- issuerVK :: !VerificationKey
- delegateVK :: !VerificationKey
- signature :: !(Signature EpochNumber)
- annotation :: !a
- type Certificate = ACertificate ()
- isValid :: Annotated ProtocolMagicId ByteString -> ACertificate ByteString -> Bool
- signCertificate :: ProtocolMagicId -> VerificationKey -> EpochNumber -> SafeSigner -> Certificate
Documentation
Minimal complete definition
Instances
class Monad m => MonadIO (m :: Type -> Type) where Source #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Methods
liftIO :: IO a -> m a Source #
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
Instances
class (forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (t :: (Type -> Type) -> Type -> Type) where Source #
The class of monad transformers.
For any monad m
, the result t m
should also be a monad,
and lift
should be a monad transformation from m
to t m
,
i.e. it should satisfy the following laws:
Since 0.6.0.0 and for GHC 8.6 and later, the requirement that t m
be a Monad
is enforced by the implication constraint
forall m.
enabled by the
Monad
m => Monad
(t m)QuantifiedConstraints
extension.
Ambiguity error with GHC 9.0 to 9.2.2
These versions of GHC have a bug (https://gitlab.haskell.org/ghc/ghc/-/issues/20582) which causes constraints like
(MonadTrans t, forall m. Monad m => Monad (t m)) => ...
to be reported as ambiguous. For transformers 0.6 and later, this can be fixed by removing the second constraint, which is implied by the first.
Methods
lift :: Monad m => m a -> t m a Source #
Lift a computation from the argument monad to the constructed monad.
Instances
class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where Source #
An interface for cryptographic keys used for signatures with a SigningKey
and a VerificationKey
key.
This interface does not provide actual signing or verifying functions since this API is concerned with the management of keys: generating and serialising.
Associated Types
data VerificationKey keyrole Source #
The type of cryptographic verification key, for each key role.
data SigningKey keyrole Source #
The type of cryptographic signing key, for each key role.
Methods
getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole Source #
Get the corresponding verification key from a signing key.
deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole Source #
Generate a SigningKey
deterministically, given a Seed
. The
required size of the seed is given by deterministicSigningKeySeedSize
.
deterministicSigningKeySeedSize :: AsType keyrole -> Word Source #
verificationKeyHash :: VerificationKey keyrole -> Hash keyrole Source #
Instances
Deprecated: Use getBlockHeader instead
A blockchain block in a particular Cardano era.
Constructors
ByronBlock :: ByronBlock -> Block ByronEra | |
ShelleyBlock :: forall era. ShelleyBasedEra era -> ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) -> Block era |
pattern Block :: BlockHeader -> [Tx era] -> Block era Source #
Deprecated: Use getBlockHeader instead
A block consists of a header and a body containing transactions.
data BlockHeader Source #
Constructors
BlockHeader !SlotNo !(Hash BlockHeader) !BlockNo |
Instances
HasTypeProxy BlockHeader Source # | |||||
Defined in Cardano.Api.Internal.Block Associated Types
Methods proxyToAsType :: Proxy BlockHeader -> AsType BlockHeader Source # | |||||
FromJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods parseJSON :: Value -> Parser (Hash BlockHeader) parseJSONList :: Value -> Parser [Hash BlockHeader] omittedField :: Maybe (Hash BlockHeader) | |||||
ToJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods toJSON :: Hash BlockHeader -> Value toEncoding :: Hash BlockHeader -> Encoding toJSONList :: [Hash BlockHeader] -> Value toEncodingList :: [Hash BlockHeader] -> Encoding omitField :: Hash BlockHeader -> Bool | |||||
IsString (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods fromString :: String -> Hash BlockHeader Source # | |||||
Show (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block | |||||
SerialiseAsRawBytes (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods serialiseToRawBytes :: Hash BlockHeader -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash BlockHeader) -> ByteString -> Either SerialiseAsRawBytesError (Hash BlockHeader) Source # | |||||
Eq (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods (==) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (/=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # | |||||
Ord (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods compare :: Hash BlockHeader -> Hash BlockHeader -> Ordering Source # (<) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (<=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # max :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # min :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # | |||||
data AsType BlockHeader Source # | |||||
Defined in Cardano.Api.Internal.Block | |||||
newtype Hash BlockHeader Source # | For now at least we use a fixed concrete hash type for all modes and era. The different eras do use different types, but it's all the same underlying representation. | ||||
Defined in Cardano.Api.Internal.Block |
data family Hash keyrole Source #
Instances
FromJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods parseJSON :: Value -> Parser (Hash BlockHeader) parseJSONList :: Value -> Parser [Hash BlockHeader] omittedField :: Maybe (Hash BlockHeader) | |||||
FromJSON (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash DRepKey) parseJSONList :: Value -> Parser [Hash DRepKey] omittedField :: Maybe (Hash DRepKey) | |||||
FromJSON (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash GenesisKey) parseJSONList :: Value -> Parser [Hash GenesisKey] omittedField :: Maybe (Hash GenesisKey) | |||||
FromJSON (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash PaymentKey) parseJSONList :: Value -> Parser [Hash PaymentKey] omittedField :: Maybe (Hash PaymentKey) | |||||
FromJSON (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash StakePoolExtendedKey) parseJSONList :: Value -> Parser [Hash StakePoolExtendedKey] | |||||
FromJSON (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash StakePoolKey) parseJSONList :: Value -> Parser [Hash StakePoolKey] | |||||
FromJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods parseJSON :: Value -> Parser (Hash ScriptData) parseJSONList :: Value -> Parser [Hash ScriptData] omittedField :: Maybe (Hash ScriptData) | |||||
FromJSONKey (Hash ScriptData) | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromJSONKey :: FromJSONKeyFunction (Hash ScriptData) fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData] | |||||
ToJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods toJSON :: Hash BlockHeader -> Value toEncoding :: Hash BlockHeader -> Encoding toJSONList :: [Hash BlockHeader] -> Value toEncodingList :: [Hash BlockHeader] -> Encoding omitField :: Hash BlockHeader -> Bool | |||||
ToJSON (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToJSON (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash GenesisKey -> Value toEncoding :: Hash GenesisKey -> Encoding toJSONList :: [Hash GenesisKey] -> Value toEncodingList :: [Hash GenesisKey] -> Encoding omitField :: Hash GenesisKey -> Bool | |||||
ToJSON (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash PaymentKey -> Value toEncoding :: Hash PaymentKey -> Encoding toJSONList :: [Hash PaymentKey] -> Value toEncodingList :: [Hash PaymentKey] -> Encoding omitField :: Hash PaymentKey -> Bool | |||||
ToJSON (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash StakePoolExtendedKey -> Value toEncoding :: Hash StakePoolExtendedKey -> Encoding toJSONList :: [Hash StakePoolExtendedKey] -> Value toEncodingList :: [Hash StakePoolExtendedKey] -> Encoding | |||||
ToJSON (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash StakePoolKey -> Value toEncoding :: Hash StakePoolKey -> Encoding toJSONList :: [Hash StakePoolKey] -> Value toEncodingList :: [Hash StakePoolKey] -> Encoding omitField :: Hash StakePoolKey -> Bool | |||||
ToJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSON :: Hash ScriptData -> Value toEncoding :: Hash ScriptData -> Encoding toJSONList :: [Hash ScriptData] -> Value toEncodingList :: [Hash ScriptData] -> Encoding omitField :: Hash ScriptData -> Bool | |||||
ToJSONKey (Hash DRepKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToJSONKey (Hash GenesisKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash GenesisKey) toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey] | |||||
ToJSONKey (Hash PaymentKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash PaymentKey) toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey] | |||||
ToJSONKey (Hash StakePoolExtendedKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash StakePoolExtendedKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolExtendedKey] | |||||
ToJSONKey (Hash StakePoolKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey] | |||||
ToJSONKey (Hash ScriptData) | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSONKey :: ToJSONKeyFunction (Hash ScriptData) toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData] | |||||
IsString (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods fromString :: String -> Hash BlockHeader Source # | |||||
IsString (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods fromString :: String -> Hash GovernancePoll Source # | |||||
IsString (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
IsString (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> Hash ByronKeyLegacy Source # | |||||
IsString (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
IsString (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
IsString (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeColdExtendedKey Source # | |||||
IsString (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeColdKey Source # | |||||
IsString (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeHotExtendedKey Source # | |||||
IsString (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeHotKey Source # | |||||
IsString (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash DRepExtendedKey Source # | |||||
IsString (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
IsString (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisDelegateExtendedKey Source # | |||||
IsString (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisKey Source # | |||||
IsString (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisUTxOKey Source # | |||||
IsString (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash PaymentKey Source # | |||||
IsString (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakeExtendedKey Source # | |||||
IsString (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
IsString (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakePoolKey Source # | |||||
IsString (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromString :: String -> Hash ScriptData Source # | |||||
Show (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block | |||||
Show (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
Show (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
Show (Hash ByronKey) Source # | |||||
Show (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (Hash KesKey) Source # | |||||
Show (Hash VrfKey) Source # | |||||
Show (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash DRepKey) Source # | |||||
Show (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakeKey) Source # | |||||
Show (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
Show (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
HasTypeProxy a => HasTypeProxy (Hash a) Source # | |||||
Defined in Cardano.Api.Internal.Hash Associated Types
| |||||
SerialiseAsCBOR (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKey) -> ByteString -> Either DecoderError (Hash ByronKey) Source # | |||||
SerialiseAsCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKeyLegacy) -> ByteString -> Either DecoderError (Hash ByronKeyLegacy) Source # | |||||
SerialiseAsCBOR (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash KesKey) -> ByteString -> Either DecoderError (Hash KesKey) Source # | |||||
SerialiseAsCBOR (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash VrfKey) -> ByteString -> Either DecoderError (Hash VrfKey) Source # | |||||
SerialiseAsCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeColdKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeColdKey) -> ByteString -> Either DecoderError (Hash CommitteeColdKey) Source # | |||||
SerialiseAsCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeHotKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeHotKey) -> ByteString -> Either DecoderError (Hash CommitteeHotKey) Source # | |||||
SerialiseAsCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepExtendedKey) -> ByteString -> Either DecoderError (Hash DRepExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepKey) -> ByteString -> Either DecoderError (Hash DRepKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisDelegateKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisDelegateKey) -> ByteString -> Either DecoderError (Hash GenesisDelegateKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisExtendedKey) -> ByteString -> Either DecoderError (Hash GenesisExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisKey) -> ByteString -> Either DecoderError (Hash GenesisKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisUTxOKey) -> ByteString -> Either DecoderError (Hash GenesisUTxOKey) Source # | |||||
SerialiseAsCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentExtendedKey) -> ByteString -> Either DecoderError (Hash PaymentExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentKey) -> ByteString -> Either DecoderError (Hash PaymentKey) Source # | |||||
SerialiseAsCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeExtendedKey) -> ByteString -> Either DecoderError (Hash StakeExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeKey) -> ByteString -> Either DecoderError (Hash StakeKey) Source # | |||||
SerialiseAsCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakePoolKey) -> ByteString -> Either DecoderError (Hash StakePoolKey) Source # | |||||
SerialiseAsBech32 (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash DRepKey -> Text bech32PrefixesPermitted :: AsType (Hash DRepKey) -> [Text] | |||||
SerialiseAsBech32 (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash StakePoolExtendedKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash StakePoolKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text] | |||||
SerialiseAsRawBytes (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods serialiseToRawBytes :: Hash BlockHeader -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash BlockHeader) -> ByteString -> Either SerialiseAsRawBytesError (Hash BlockHeader) Source # | |||||
SerialiseAsRawBytes (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods serialiseToRawBytes :: Hash DRepMetadata -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepMetadata) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepMetadata) Source # | |||||
SerialiseAsRawBytes (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
SerialiseAsRawBytes (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToRawBytes :: Hash ByronKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ByronKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash ByronKey) Source # | |||||
SerialiseAsRawBytes (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash KesKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash KesKey) Source # | |||||
SerialiseAsRawBytes (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash VrfKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash DRepKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash GenesisKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash GenesisKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash GenesisKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash PaymentKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash PaymentKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash PaymentKey) Source # | |||||
SerialiseAsRawBytes (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakeKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakeKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakeKey) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakePoolKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakePoolKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakePoolKey) Source # | |||||
SerialiseAsRawBytes (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods serialiseToRawBytes :: Hash ScriptData -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ScriptData) -> ByteString -> Either SerialiseAsRawBytesError (Hash ScriptData) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolMetadata) Source # | |||||
FromCBOR (Hash ByronKey) Source # | |||||
FromCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (Hash KesKey) Source # | |||||
FromCBOR (Hash VrfKey) Source # | |||||
FromCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash DRepKey) Source # | |||||
FromCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash StakeKey) Source # | |||||
FromCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash ByronKey) Source # | |||||
ToCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (Hash KesKey) Source # | |||||
ToCBOR (Hash VrfKey) Source # | |||||
ToCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash DRepKey) Source # | |||||
ToCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods (==) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (/=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # | |||||
Eq (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods (==) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # (/=) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # | |||||
Eq (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods (==) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (/=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # | |||||
Eq (Hash ByronKey) Source # | |||||
Eq (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (/=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # | |||||
Eq (Hash KesKey) Source # | |||||
Eq (Hash VrfKey) Source # | |||||
Eq (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (/=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # | |||||
Eq (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (/=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # | |||||
Eq (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (/=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # | |||||
Eq (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (/=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # | |||||
Eq (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (/=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # | |||||
Eq (Hash DRepKey) Source # | |||||
Eq (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (/=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # | |||||
Eq (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (/=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # | |||||
Eq (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (/=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # | |||||
Eq (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (/=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # | |||||
Eq (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (/=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # | |||||
Eq (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (/=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # | |||||
Eq (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (/=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # | |||||
Eq (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (/=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # | |||||
Eq (Hash StakeKey) Source # | |||||
Eq (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (/=) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # | |||||
Eq (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (/=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # | |||||
Eq (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (/=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # | |||||
Eq (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods (==) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # (/=) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # | |||||
Ord (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods compare :: Hash BlockHeader -> Hash BlockHeader -> Ordering Source # (<) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (<=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # max :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # min :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # | |||||
Ord (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods compare :: Hash GovernancePoll -> Hash GovernancePoll -> Ordering Source # (<) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (<=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # max :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # min :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # | |||||
Ord (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKey -> Hash ByronKey -> Ordering Source # (<) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (<=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # max :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # min :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # | |||||
Ord (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Ordering Source # (<) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (<=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # max :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # min :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # | |||||
Ord (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash KesKey -> Hash KesKey -> Ordering Source # (<) :: Hash KesKey -> Hash KesKey -> Bool Source # (<=) :: Hash KesKey -> Hash KesKey -> Bool Source # (>) :: Hash KesKey -> Hash KesKey -> Bool Source # (>=) :: Hash KesKey -> Hash KesKey -> Bool Source # | |||||
Ord (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash VrfKey -> Hash VrfKey -> Ordering Source # (<) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (<=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # | |||||
Ord (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Ordering Source # (<) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (<=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (>) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (>=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # max :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # min :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # | |||||
Ord (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Ordering Source # (<) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (<=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (>) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (>=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # max :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Hash CommitteeColdKey Source # min :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Hash CommitteeColdKey Source # | |||||
Ord (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Ordering Source # (<) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (<=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (>) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (>=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # max :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # min :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # | |||||
Ord (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Ordering Source # (<) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (<=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (>) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (>=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # max :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Hash CommitteeHotKey Source # min :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Hash CommitteeHotKey Source # | |||||
Ord (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Ordering Source # (<) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (<=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (>) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (>=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # max :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Hash DRepExtendedKey Source # min :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Hash DRepExtendedKey Source # | |||||
Ord (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash DRepKey -> Hash DRepKey -> Ordering Source # (<) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (<=) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (>) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (>=) :: Hash DRepKey -> Hash DRepKey -> Bool Source # max :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey Source # min :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey Source # | |||||
Ord (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Ordering Source # (<) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (<=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (>) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (>=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # max :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # min :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # | |||||
Ord (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering Source # (<) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (<=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (>) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (>=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # max :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey Source # min :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey Source # | |||||
Ord (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering Source # (<) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (<=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (>) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (>=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # max :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey Source # min :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey Source # | |||||
Ord (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisKey -> Hash GenesisKey -> Ordering Source # (<) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (<=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (>) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (>=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # max :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey Source # min :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey Source # | |||||
Ord (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering Source # (<) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (<=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (>) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (>=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # max :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey Source # min :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey Source # | |||||
Ord (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering Source # (<) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (<=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # max :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # min :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # | |||||
Ord (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentKey -> Hash PaymentKey -> Ordering Source # (<) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (<=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # max :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # min :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # | |||||
Ord (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering Source # (<) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (<=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # max :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # min :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # | |||||
Ord (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeKey -> Hash StakeKey -> Ordering Source # (<) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (<=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # max :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # min :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # | |||||
Ord (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Ordering Source # (<) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (<=) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (>) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (>=) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # max :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey Source # min :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey Source # | |||||
Ord (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering Source # (<) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (<=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # max :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # min :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # | |||||
Ord (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods compare :: Hash ScriptData -> Hash ScriptData -> Ordering Source # (<) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (<=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # max :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # min :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # | |||||
newtype Hash BlockHeader Source # | For now at least we use a fixed concrete hash type for all modes and era. The different eras do use different types, but it's all the same underlying representation. | ||||
Defined in Cardano.Api.Internal.Block | |||||
newtype Hash DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
newtype Hash GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
newtype Hash ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype Hash ByronKeyLegacy Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype Hash KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype Hash VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype Hash CommitteeColdExtendedKey Source # | |||||
newtype Hash CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash CommitteeHotExtendedKey Source # | |||||
newtype Hash CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisDelegateExtendedKey Source # | |||||
newtype Hash GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakePoolExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
newtype Hash StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
data AsType (Hash a) Source # | |||||
Defined in Cardano.Api.Internal.Hash |
data TxBody era where Source #
Constructors
ShelleyTxBody | |
Fields
|
Bundled Patterns
pattern TxBody :: TxBodyContent ViewTx era -> TxBody era | Deprecated: Use getTxBodyContent $ getTxBody instead |
Instances
Show (TxBody era) Source # | |||||
HasTypeProxy era => HasTypeProxy (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
| |||||
IsShelleyBasedEra era => SerialiseAsCBOR (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods serialiseToCBOR :: TxBody era -> ByteString Source # deserialiseFromCBOR :: AsType (TxBody era) -> ByteString -> Either DecoderError (TxBody era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods textEnvelopeType :: AsType (TxBody era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: TxBody era -> TextEnvelopeDescr Source # | |||||
Eq (TxBody era) Source # | |||||
data AsType (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign |
Constructors
TxId (Hash HASH EraIndependentTxBody) |
Instances
FromJSON TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSONKey TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxId -> Encoding toJSONList :: [TxId] -> Value toEncodingList :: [TxId] -> Encoding | |
ToJSONKey TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
IsString TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods fromString :: String -> TxId Source # | |
Show TxId Source # | |
HasTypeProxy TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
SerialiseAsRawBytes TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods serialiseToRawBytes :: TxId -> ByteString Source # deserialiseFromRawBytes :: AsType TxId -> ByteString -> Either SerialiseAsRawBytesError TxId Source # | |
Eq TxId Source # | |
Ord TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
data AsType TxId Source # | |
Defined in Cardano.Api.Internal.TxIn |
class Typeable a => FromCBOR a Source #
Minimal complete definition
Instances
FromCBOR Void | |
FromCBOR Int32 | |
FromCBOR Int64 | |
FromCBOR Rational | |
FromCBOR Word16 | |
FromCBOR Word32 | |
FromCBOR Word64 | |
FromCBOR Word8 | |
FromCBOR ByteString | |
Defined in Cardano.Binary.FromCBOR | |
FromCBOR ByteString | |
Defined in Cardano.Binary.FromCBOR | |
FromCBOR ShortByteString | |
Defined in Cardano.Binary.FromCBOR | |
FromCBOR OperationalCertificate Source # | |
Defined in Cardano.Api.Internal.OperationalCertificate | |
FromCBOR OperationalCertificateIssueCounter Source # | |
Defined in Cardano.Api.Internal.OperationalCertificate | |
FromCBOR CostModel Source # | |
FromCBOR ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromCBOR PraosNonce Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromCBOR ProtocolParametersUpdate Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromCBOR UpdateProposal Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromCBOR AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script | |
FromCBOR ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script | |
FromCBOR ScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
FromCBOR Point | |
FromCBOR Proof | |
FromCBOR SignKey | |
FromCBOR VerKey | |
FromCBOR Proof | |
FromCBOR SignKey | |
FromCBOR VerKey | |
FromCBOR ProtocolMagicId | |
Defined in Cardano.Crypto.ProtocolMagic | |
FromCBOR RequiresNetworkMagic | |
Defined in Cardano.Crypto.ProtocolMagic | |
FromCBOR Raw | |
FromCBOR CompactRedeemVerificationKey | |
Defined in Cardano.Crypto.Signing.Redeem.Compact | |
FromCBOR RedeemSigningKey | |
Defined in Cardano.Crypto.Signing.Redeem.SigningKey | |
FromCBOR RedeemVerificationKey | |
FromCBOR SigningKey | |
Defined in Cardano.Crypto.Signing.SigningKey | |
FromCBOR VerificationKey | |
Defined in Cardano.Crypto.Signing.VerificationKey | |
FromCBOR AlonzoGenesis | |
Defined in Cardano.Ledger.Alonzo.Genesis | |
FromCBOR Version | |
FromCBOR Body | |
FromCBOR BlockSignature | |
Defined in Cardano.Chain.Block.Header | |
FromCBOR ToSign | |
FromCBOR Proof | |
FromCBOR ChainValidationState | |
Defined in Cardano.Chain.Block.Validation | |
FromCBOR ApplyMempoolPayloadErr | |
Defined in Cardano.Chain.Byron.API.Mempool | |
FromCBOR HDAddressPayload | |
Defined in Cardano.Chain.Common.AddrAttributes | |
FromCBOR AddrSpendingData | |
Defined in Cardano.Chain.Common.AddrSpendingData | |
FromCBOR AddrType | |
FromCBOR Address | |
FromCBOR Address' | |
FromCBOR BlockCount | |
Defined in Cardano.Chain.Common.BlockCount | |
FromCBOR ChainDifficulty | |
Defined in Cardano.Chain.Common.ChainDifficulty | |
FromCBOR CompactAddress | |
Defined in Cardano.Chain.Common.Compact | |
FromCBOR Lovelace | |
FromCBOR LovelaceError | |
Defined in Cardano.Chain.Common.Lovelace | |
FromCBOR LovelacePortion | |
Defined in Cardano.Chain.Common.LovelacePortion | |
FromCBOR NetworkMagic | |
Defined in Cardano.Chain.Common.NetworkMagic | |
FromCBOR TxFeePolicy | |
Defined in Cardano.Chain.Common.TxFeePolicy | |
FromCBOR TxSizeLinear | |
Defined in Cardano.Chain.Common.TxSizeLinear | |
FromCBOR Certificate | |
Defined in Cardano.Chain.Delegation.Certificate | |
FromCBOR Map | |
FromCBOR Payload | |
FromCBOR State | |
FromCBOR State | |
FromCBOR Error | |
FromCBOR ScheduledDelegation | |
FromCBOR State | |
FromCBOR GenesisAvvmBalances | |
Defined in Cardano.Chain.Genesis.AvvmBalances | |
FromCBOR Config | |
FromCBOR GenesisData | |
Defined in Cardano.Chain.Genesis.Data | |
FromCBOR GenesisDelegation | |
Defined in Cardano.Chain.Genesis.Delegation | |
FromCBOR GenesisKeyHashes | |
Defined in Cardano.Chain.Genesis.KeyHashes | |
FromCBOR GenesisNonAvvmBalances | |
Defined in Cardano.Chain.Genesis.NonAvvmBalances | |
FromCBOR MempoolPayload | |
Defined in Cardano.Chain.MempoolPayload | |
FromCBOR EpochAndSlotCount | |
Defined in Cardano.Chain.Slotting.EpochAndSlotCount | |
FromCBOR EpochNumber | |
Defined in Cardano.Chain.Slotting.EpochNumber | |
FromCBOR EpochSlots | |
Defined in Cardano.Chain.Slotting.EpochSlots | |
FromCBOR SlotCount | |
FromCBOR SlotNumber | |
Defined in Cardano.Chain.Slotting.SlotNumber | |
FromCBOR SscPayload | |
Defined in Cardano.Chain.Ssc | |
FromCBOR SscProof | |
FromCBOR CompactTxId | |
Defined in Cardano.Chain.UTxO.Compact | |
FromCBOR CompactTxIn | |
Defined in Cardano.Chain.UTxO.Compact | |
FromCBOR CompactTxOut | |
Defined in Cardano.Chain.UTxO.Compact | |
FromCBOR Tx | |
FromCBOR TxIn | |
FromCBOR TxOut | |
FromCBOR TxAux | |
FromCBOR TxPayload | |
FromCBOR TxProof | |
FromCBOR TxInWitness | |
Defined in Cardano.Chain.UTxO.TxWitness | |
FromCBOR TxSigData | |
FromCBOR UTxO | |
FromCBOR UTxOError | |
FromCBOR UTxOConfiguration | |
Defined in Cardano.Chain.UTxO.UTxOConfiguration | |
FromCBOR TxValidationError | |
Defined in Cardano.Chain.UTxO.Validation | |
FromCBOR UTxOValidationError | |
Defined in Cardano.Chain.UTxO.Validation | |
FromCBOR ApplicationName | |
Defined in Cardano.Chain.Update.ApplicationName | |
FromCBOR ApplicationNameError | |
Defined in Cardano.Chain.Update.ApplicationName | |
FromCBOR InstallerHash | |
Defined in Cardano.Chain.Update.InstallerHash | |
FromCBOR Payload | |
FromCBOR Proposal | |
FromCBOR ProposalBody | |
Defined in Cardano.Chain.Update.Proposal | |
FromCBOR ProtocolParameters | |
Defined in Cardano.Chain.Update.ProtocolParameters | |
FromCBOR ProtocolParametersUpdate | |
FromCBOR ProtocolVersion | |
Defined in Cardano.Chain.Update.ProtocolVersion | |
FromCBOR SoftforkRule | |
Defined in Cardano.Chain.Update.SoftforkRule | |
FromCBOR SoftwareVersion | |
Defined in Cardano.Chain.Update.SoftwareVersion | |
FromCBOR SoftwareVersionError | |
Defined in Cardano.Chain.Update.SoftwareVersion | |
FromCBOR SystemTag | |
FromCBOR SystemTagError | |
Defined in Cardano.Chain.Update.SystemTag | |
FromCBOR CandidateProtocolUpdate | |
Defined in Cardano.Chain.Update.Validation.Endorsement | |
FromCBOR Endorsement | |
Defined in Cardano.Chain.Update.Validation.Endorsement | |
FromCBOR Error | |
FromCBOR Error | |
FromCBOR State | |
FromCBOR Adopted | |
FromCBOR ApplicationVersion | |
Defined in Cardano.Chain.Update.Validation.Registration | |
FromCBOR Error | |
FromCBOR ProtocolUpdateProposal | |
Defined in Cardano.Chain.Update.Validation.Registration | |
FromCBOR SoftwareUpdateProposal | |
Defined in Cardano.Chain.Update.Validation.Registration | |
FromCBOR Error | |
FromCBOR Vote | |
FromCBOR ConwayGenesis | Genesis are always encoded with the version of era they are defined in. |
Defined in Cardano.Ledger.Conway.Genesis | |
FromCBOR DefaultVote | |
Defined in Cardano.Ledger.Conway.Governance | |
FromCBOR ActiveSlotCoeff | |
Defined in Cardano.Ledger.BaseTypes | |
FromCBOR CertIx | |
FromCBOR Network | |
FromCBOR Nonce | |
FromCBOR PositiveUnitInterval | |
Defined in Cardano.Ledger.BaseTypes | |
FromCBOR ProtVer | |
FromCBOR TxIx | |
FromCBOR Coin | |
FromCBOR Ptr | |
FromCBOR SlotNo32 | |
FromCBOR ScriptHash | |
Defined in Cardano.Ledger.Hashes | |
FromCBOR PlutusWithContext | |
Defined in Cardano.Ledger.Plutus.Evaluate | |
FromCBOR Language | |
FromCBOR PlutusBinary | |
Defined in Cardano.Ledger.Plutus.Language | |
FromCBOR ShelleyGenesis | |
Defined in Cardano.Ledger.Shelley.Genesis | |
FromCBOR FromByronTranslationContext | |
Defined in Cardano.Ledger.Shelley.Translation | |
FromCBOR ChainDepState | |
Defined in Cardano.Protocol.TPraos.API | |
FromCBOR KESPeriod | |
FromCBOR PrtclState | |
Defined in Cardano.Protocol.TPraos.Rules.Prtcl | |
FromCBOR TicknState | |
Defined in Cardano.Protocol.TPraos.Rules.Tickn | |
FromCBOR BlockNo | |
FromCBOR EpochInterval | |
Defined in Cardano.Slotting.Slot | |
FromCBOR EpochNo | |
FromCBOR EpochSize | |
FromCBOR SlotNo | |
FromCBOR RelativeTime | |
Defined in Cardano.Slotting.Time | |
FromCBOR SlotLength | |
Defined in Cardano.Slotting.Time | |
FromCBOR SystemStart | |
Defined in Cardano.Slotting.Time | |
FromCBOR TermToken | |
FromCBOR Term | |
FromCBOR SecurityParam | |
Defined in Ouroboros.Consensus.Config.SecurityParam | |
FromCBOR CoreNodeId | |
Defined in Ouroboros.Consensus.NodeId | |
FromCBOR NodeId | |
FromCBOR CompactGenesis | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Config | |
FromCBOR NonMyopicMemberRewards | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query | |
FromCBOR StakeSnapshot | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query | |
FromCBOR StakeSnapshots | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query | |
FromCBOR ShelleyHash | |
FromCBOR PraosState | |
Defined in Ouroboros.Consensus.Protocol.Praos | |
FromCBOR TPraosState | |
Defined in Ouroboros.Consensus.Protocol.TPraos | |
FromCBOR AccPoolStakeCoded | |
FromCBOR LedgerPeerSnapshot | |
FromCBOR PoolStakeCoded | |
FromCBOR WithOriginCoded | |
FromCBOR RelayAccessPointCoded | |
FromCBOR Text | |
FromCBOR UTCTime | |
FromCBOR Integer | |
FromCBOR Natural | |
FromCBOR () | |
FromCBOR Bool | |
FromCBOR Double | |
FromCBOR Float | |
FromCBOR Int | |
FromCBOR Word | |
FromCBOR a => FromCBOR (NonEmpty a) | |
IsShelleyBasedEra era => FromCBOR (Certificate era) Source # | |
Defined in Cardano.Api.Internal.Certificate | |
IsShelleyBasedEra era => FromCBOR (Proposal era) Source # | |
IsShelleyBasedEra era => FromCBOR (VotingProcedure era) Source # | |
IsShelleyBasedEra era => FromCBOR (VotingProcedures era) Source # | |
FromCBOR (Hash ByronKey) Source # | |
FromCBOR (Hash ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
FromCBOR (Hash KesKey) Source # | |
FromCBOR (Hash VrfKey) Source # | |
FromCBOR (Hash CommitteeColdExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash CommitteeHotExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash DRepKey) Source # | |
FromCBOR (Hash GenesisDelegateExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (Hash StakeKey) Source # | |
FromCBOR (Hash StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (SigningKey ByronKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
FromCBOR (SigningKey ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (SigningKey ByronKeyLegacy) Source # label :: Proxy (SigningKey ByronKeyLegacy) -> Text Source # | |
FromCBOR (SigningKey KesKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
FromCBOR (SigningKey VrfKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
FromCBOR (SigningKey CommitteeColdExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdExtendedKey) Source # label :: Proxy (SigningKey CommitteeColdExtendedKey) -> Text Source # | |
FromCBOR (SigningKey CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdKey) Source # label :: Proxy (SigningKey CommitteeColdKey) -> Text Source # | |
FromCBOR (SigningKey CommitteeHotExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotExtendedKey) Source # label :: Proxy (SigningKey CommitteeHotExtendedKey) -> Text Source # | |
FromCBOR (SigningKey CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotKey) Source # label :: Proxy (SigningKey CommitteeHotKey) -> Text Source # | |
FromCBOR (SigningKey DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey DRepExtendedKey) Source # label :: Proxy (SigningKey DRepExtendedKey) -> Text Source # | |
FromCBOR (SigningKey DRepKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateExtendedKey) Source # label :: Proxy (SigningKey GenesisDelegateExtendedKey) -> Text Source # | |
FromCBOR (SigningKey GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateKey) Source # label :: Proxy (SigningKey GenesisDelegateKey) -> Text Source # | |
FromCBOR (SigningKey GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisExtendedKey) Source # label :: Proxy (SigningKey GenesisExtendedKey) -> Text Source # | |
FromCBOR (SigningKey GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisKey) Source # label :: Proxy (SigningKey GenesisKey) -> Text Source # | |
FromCBOR (SigningKey GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisUTxOKey) Source # label :: Proxy (SigningKey GenesisUTxOKey) -> Text Source # | |
FromCBOR (SigningKey PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentExtendedKey) Source # label :: Proxy (SigningKey PaymentExtendedKey) -> Text Source # | |
FromCBOR (SigningKey PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentKey) Source # label :: Proxy (SigningKey PaymentKey) -> Text Source # | |
FromCBOR (SigningKey StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakeExtendedKey) Source # label :: Proxy (SigningKey StakeExtendedKey) -> Text Source # | |
FromCBOR (SigningKey StakeKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (SigningKey StakePoolExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolExtendedKey) Source # label :: Proxy (SigningKey StakePoolExtendedKey) -> Text Source # | |
FromCBOR (SigningKey StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolKey) Source # label :: Proxy (SigningKey StakePoolKey) -> Text Source # | |
FromCBOR (VerificationKey ByronKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
FromCBOR (VerificationKey ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (VerificationKey ByronKeyLegacy) Source # label :: Proxy (VerificationKey ByronKeyLegacy) -> Text Source # | |
FromCBOR (VerificationKey KesKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
FromCBOR (VerificationKey VrfKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
FromCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdExtendedKey) Source # label :: Proxy (VerificationKey CommitteeColdExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdKey) Source # label :: Proxy (VerificationKey CommitteeColdKey) -> Text Source # | |
FromCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotExtendedKey) Source # label :: Proxy (VerificationKey CommitteeHotExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotKey) Source # label :: Proxy (VerificationKey CommitteeHotKey) -> Text Source # | |
FromCBOR (VerificationKey DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey DRepExtendedKey) Source # label :: Proxy (VerificationKey DRepExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey DRepKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateExtendedKey) Source # label :: Proxy (VerificationKey GenesisDelegateExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateKey) Source # label :: Proxy (VerificationKey GenesisDelegateKey) -> Text Source # | |
FromCBOR (VerificationKey GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisExtendedKey) Source # label :: Proxy (VerificationKey GenesisExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisKey) Source # label :: Proxy (VerificationKey GenesisKey) -> Text Source # | |
FromCBOR (VerificationKey GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisUTxOKey) Source # label :: Proxy (VerificationKey GenesisUTxOKey) -> Text Source # | |
FromCBOR (VerificationKey PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentExtendedKey) Source # label :: Proxy (VerificationKey PaymentExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentKey) Source # label :: Proxy (VerificationKey PaymentKey) -> Text Source # | |
FromCBOR (VerificationKey StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakeExtendedKey) Source # label :: Proxy (VerificationKey StakeExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey StakeKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
FromCBOR (VerificationKey StakePoolExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolExtendedKey) Source # label :: Proxy (VerificationKey StakePoolExtendedKey) -> Text Source # | |
FromCBOR (VerificationKey StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolKey) Source # label :: Proxy (VerificationKey StakePoolKey) -> Text Source # | |
IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Internal.Query.Types | |
SerialiseAsRawBytes a => FromCBOR (UsingRawBytes a) Source # | |
Defined in Cardano.Api.Internal.SerialiseUsing | |
FromCBOR (SigDSIGN Ed25519Bip32DSIGN) Source # | |
Defined in Cardano.Api.Crypto.Ed25519Bip32 | |
FromCBOR (SigDSIGN EcdsaSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 | |
FromCBOR (SigDSIGN Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 | |
FromCBOR (SigDSIGN Ed448DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed448 | |
FromCBOR (SigDSIGN MockDSIGN) | |
FromCBOR (SigDSIGN SchnorrSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 | |
FromCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) Source # | |
Defined in Cardano.Api.Crypto.Ed25519Bip32 Methods fromCBOR :: Decoder s (SignKeyDSIGN Ed25519Bip32DSIGN) Source # label :: Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> Text Source # | |
FromCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Methods fromCBOR :: Decoder s (SignKeyDSIGN EcdsaSecp256k1DSIGN) Source # label :: Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> Text Source # | |
FromCBOR (SignKeyDSIGN Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 Methods fromCBOR :: Decoder s (SignKeyDSIGN Ed25519DSIGN) Source # label :: Proxy (SignKeyDSIGN Ed25519DSIGN) -> Text Source # | |
FromCBOR (SignKeyDSIGN Ed448DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed448 Methods fromCBOR :: Decoder s (SignKeyDSIGN Ed448DSIGN) Source # label :: Proxy (SignKeyDSIGN Ed448DSIGN) -> Text Source # | |
FromCBOR (SignKeyDSIGN MockDSIGN) | |
Defined in Cardano.Crypto.DSIGN.Mock | |
FromCBOR (SignKeyDSIGN SchnorrSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Methods fromCBOR :: Decoder s (SignKeyDSIGN SchnorrSecp256k1DSIGN) Source # label :: Proxy (SignKeyDSIGN SchnorrSecp256k1DSIGN) -> Text Source # | |
(TypeError ('Text "CBOR decoding would violate mlocking guarantees") :: Constraint) => FromCBOR (SignKeyDSIGNM Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 Methods fromCBOR :: Decoder s (SignKeyDSIGNM Ed25519DSIGN) Source # label :: Proxy (SignKeyDSIGNM Ed25519DSIGN) -> Text Source # | |
FromCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) Source # | |
Defined in Cardano.Api.Crypto.Ed25519Bip32 Methods fromCBOR :: Decoder s (VerKeyDSIGN Ed25519Bip32DSIGN) Source # label :: Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> Text Source # | |
FromCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Methods fromCBOR :: Decoder s (VerKeyDSIGN EcdsaSecp256k1DSIGN) Source # label :: Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> Text Source # | |
FromCBOR (VerKeyDSIGN Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 Methods fromCBOR :: Decoder s (VerKeyDSIGN Ed25519DSIGN) Source # label :: Proxy (VerKeyDSIGN Ed25519DSIGN) -> Text Source # | |
FromCBOR (VerKeyDSIGN Ed448DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed448 Methods fromCBOR :: Decoder s (VerKeyDSIGN Ed448DSIGN) Source # label :: Proxy (VerKeyDSIGN Ed448DSIGN) -> Text Source # | |
FromCBOR (VerKeyDSIGN MockDSIGN) | |
Defined in Cardano.Crypto.DSIGN.Mock | |
FromCBOR (VerKeyDSIGN SchnorrSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Methods fromCBOR :: Decoder s (VerKeyDSIGN SchnorrSecp256k1DSIGN) Source # label :: Proxy (VerKeyDSIGN SchnorrSecp256k1DSIGN) -> Text Source # | |
(DSIGNMAlgorithm d, KnownNat (SizeSigKES (CompactSingleKES d))) => FromCBOR (SigKES (CompactSingleKES d)) | |
Defined in Cardano.Crypto.KES.CompactSingle | |
(OptimizedKESAlgorithm d, SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d, NoThunks (VerKeyKES (CompactSumKES h d)), KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) => FromCBOR (SigKES (CompactSumKES h d)) | |
Defined in Cardano.Crypto.KES.CompactSum | |
KnownNat t => FromCBOR (SigKES (MockKES t)) | |
(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => FromCBOR (SigKES (SimpleKES d t)) | |
DSIGNMAlgorithm d => FromCBOR (SigKES (SingleKES d)) | |
(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => FromCBOR (SigKES (SumKES h d)) | |
(UnsoundDSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => FromCBOR (UnsoundPureSignKeyKES (CompactSingleKES d)) | |
Defined in Cardano.Crypto.KES.CompactSingle Methods fromCBOR :: Decoder s (UnsoundPureSignKeyKES (CompactSingleKES d)) Source # label :: Proxy (UnsoundPureSignKeyKES (CompactSingleKES d)) -> Text Source # | |
(SizeHash h ~ SeedSizeKES d, OptimizedKESAlgorithm d, UnsoundPureKESAlgorithm d, SodiumHashAlgorithm h, KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) => FromCBOR (UnsoundPureSignKeyKES (CompactSumKES h d)) | |
Defined in Cardano.Crypto.KES.CompactSum Methods fromCBOR :: Decoder s (UnsoundPureSignKeyKES (CompactSumKES h d)) Source # label :: Proxy (UnsoundPureSignKeyKES (CompactSumKES h d)) -> Text Source # | |
KnownNat t => FromCBOR (UnsoundPureSignKeyKES (MockKES t)) | |
Defined in Cardano.Crypto.KES.Mock | |
UnsoundDSIGNMAlgorithm d => FromCBOR (UnsoundPureSignKeyKES (SingleKES d)) | |
Defined in Cardano.Crypto.KES.Single | |
(SizeHash h ~ SeedSizeKES d, UnsoundPureKESAlgorithm d, SodiumHashAlgorithm h, KnownNat (SizeVerKeyKES (SumKES h d)), KnownNat (SizeSignKeyKES (SumKES h d)), KnownNat (SizeSigKES (SumKES h d))) => FromCBOR (UnsoundPureSignKeyKES (SumKES h d)) | |
Defined in Cardano.Crypto.KES.Sum | |
(DSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => FromCBOR (VerKeyKES (CompactSingleKES d)) | |
Defined in Cardano.Crypto.KES.CompactSingle | |
(OptimizedKESAlgorithm d, SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d, NoThunks (VerKeyKES (CompactSumKES h d)), KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) => FromCBOR (VerKeyKES (CompactSumKES h d)) | |
Defined in Cardano.Crypto.KES.CompactSum | |
KnownNat t => FromCBOR (VerKeyKES (MockKES t)) | |
(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => FromCBOR (VerKeyKES (SimpleKES d t)) | |
DSIGNMAlgorithm d => FromCBOR (VerKeyKES (SingleKES d)) | |
(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => FromCBOR (VerKeyKES (SumKES h d)) | |
FromCBOR (CertVRF MockVRF) | |
FromCBOR (CertVRF SimpleVRF) | |
FromCBOR (CertVRF PraosVRF) | |
FromCBOR (CertVRF PraosBatchCompatVRF) | |
Defined in Cardano.Crypto.VRF.PraosBatchCompat | |
Typeable v => FromCBOR (OutputVRF v) | |
FromCBOR (SignKeyVRF MockVRF) | |
Defined in Cardano.Crypto.VRF.Mock | |
FromCBOR (SignKeyVRF SimpleVRF) | |
Defined in Cardano.Crypto.VRF.Simple | |
FromCBOR (SignKeyVRF PraosVRF) | |
Defined in Cardano.Crypto.VRF.Praos | |
FromCBOR (SignKeyVRF PraosBatchCompatVRF) | |
Defined in Cardano.Crypto.VRF.PraosBatchCompat Methods fromCBOR :: Decoder s (SignKeyVRF PraosBatchCompatVRF) Source # label :: Proxy (SignKeyVRF PraosBatchCompatVRF) -> Text Source # | |
FromCBOR (VerKeyVRF MockVRF) | |
FromCBOR (VerKeyVRF SimpleVRF) | |
FromCBOR (VerKeyVRF PraosVRF) | |
FromCBOR (VerKeyVRF PraosBatchCompatVRF) | |
Defined in Cardano.Crypto.VRF.PraosBatchCompat | |
DecCBOR a => FromCBOR (RedeemSignature a) | |
Defined in Cardano.Crypto.Signing.Redeem.Signature | |
Typeable a => FromCBOR (Signature a) | |
(Era era, Val (Value era)) => FromCBOR (AlonzoTxOut era) | |
Defined in Cardano.Ledger.Alonzo.TxOut | |
(EraScript era, Val (Value era)) => FromCBOR (BabbageTxOut era) | |
Defined in Cardano.Ledger.Babbage.TxOut | |
FromCBOR (ABody ByteSpan) | |
FromCBOR (ABlockSignature ByteSpan) | |
Defined in Cardano.Chain.Block.Header | |
FromCBOR (Attributes AddrAttributes) | |
Defined in Cardano.Chain.Common.AddrAttributes Methods fromCBOR :: Decoder s (Attributes AddrAttributes) Source # label :: Proxy (Attributes AddrAttributes) -> Text Source # | |
FromCBOR (Attributes ()) | |
Defined in Cardano.Chain.Common.Attributes | |
DecCBOR a => FromCBOR (MerkleRoot a) | |
Defined in Cardano.Chain.Common.Merkle | |
(DecCBOR a, EncCBOR a) => FromCBOR (MerkleTree a) | |
Defined in Cardano.Chain.Common.Merkle | |
FromCBOR (ACertificate ByteSpan) | |
Defined in Cardano.Chain.Delegation.Certificate | |
FromCBOR (APayload ByteSpan) | |
FromCBOR (AMempoolPayload ByteSpan) | |
Defined in Cardano.Chain.MempoolPayload | |
FromCBOR (ATxAux ByteSpan) | |
FromCBOR (ATxPayload ByteSpan) | |
Defined in Cardano.Chain.UTxO.TxPayload | |
FromCBOR (APayload ByteSpan) | |
FromCBOR (AProposal ByteSpan) | |
DecCBOR n => FromCBOR (TooLarge n) | |
FromCBOR (AVote ByteSpan) | |
EraPParams era => FromCBOR (ConwayGovState era) | |
Defined in Cardano.Ledger.Conway.Governance | |
EraPParams era => FromCBOR (PulsingSnapshot era) | |
Defined in Cardano.Ledger.Conway.Governance.DRepPulser | |
EraPParams era => FromCBOR (EnactState era) | |
Defined in Cardano.Ledger.Conway.Governance.Internal | |
Era era => FromCBOR (Constitution era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures | |
EraPParams era => FromCBOR (ConwayGovPredFailure era) | |
Defined in Cardano.Ledger.Conway.Rules.Gov | |
(ShelleyEraTxCert era, TxCert era ~ ConwayTxCert era) => FromCBOR (ConwayTxCert era) | |
Defined in Cardano.Ledger.Conway.TxCert | |
(HasZero a, FromCBOR a) => FromCBOR (NonZero a) | |
(Typeable era, FromCBOR (PParamsHKD Identity era)) => FromCBOR (PParams era) | |
(Typeable era, FromCBOR (PParamsHKD StrictMaybe era)) => FromCBOR (PParamsUpdate era) | |
Defined in Cardano.Ledger.Core.PParams | |
Typeable kr => FromCBOR (Credential kr) | |
Defined in Cardano.Ledger.Credential | |
Era era => FromCBOR (NoGenesis era) | |
Typeable r => FromCBOR (KeyHash r) | |
Typeable i => FromCBOR (SafeHash i) | |
Typeable r => FromCBOR (VRFVerKeyHash r) | |
Defined in Cardano.Ledger.Hashes | |
Typeable kd => FromCBOR (VKey kd) | |
PlutusLanguage l => FromCBOR (SLanguage l) | |
(DecCBOR (TxOut era), Era era) => FromCBOR (UTxO era) | |
(Era era, DecCBOR (PredicateFailure (EraRule "LEDGER" era))) => FromCBOR (ApplyTxError era) | |
Defined in Cardano.Ledger.Shelley.API.Mempool | |
(Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) => FromCBOR (ShelleyGovState era) | |
Defined in Cardano.Ledger.Shelley.Governance | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era) => FromCBOR (EpochState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era) => FromCBOR (LedgerState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era, DecCBOR (StashedAVVMAddresses era)) => FromCBOR (NewEpochState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |
(EraTxOut era, EraGov era, EraStake era) => FromCBOR (UTxOState era) | |
(Era era, FromCBOR (PParamsUpdate era)) => FromCBOR (ProposedPPUpdates era) | |
Defined in Cardano.Ledger.Shelley.PParams | |
(ShelleyEraTxCert era, TxCert era ~ ShelleyTxCert era) => FromCBOR (ShelleyTxCert era) | |
Defined in Cardano.Ledger.Shelley.TxCert | |
(Era era, DecCBOR (CompactForm (Value era))) => FromCBOR (ShelleyTxOut era) | |
Defined in Cardano.Ledger.Shelley.TxOut | |
Crypto c => FromCBOR (OCert c) | |
(Serialise t, Typeable t) => FromCBOR (WithOrigin t) | |
Defined in Cardano.Slotting.Slot | |
FromCBOR a => FromCBOR (StrictMaybe a) | |
Defined in Data.Maybe.Strict | |
FromCBOR a => FromCBOR (StrictSeq a) | |
FromCBOR a => FromCBOR (Seq a) | |
(Ord a, FromCBOR a) => FromCBOR (Set a) | |
FromCBOR a => FromCBOR (Vector a) | |
FromCBOR a => FromCBOR (Maybe a) | |
FromCBOR a => FromCBOR [a] | |
(FromCBOR a, FromCBOR b) => FromCBOR (Either a b) | |
Typeable a => FromCBOR (Fixed a) | |
(HashAlgorithm h, Typeable a) => FromCBOR (Hash h a) | |
(VRFAlgorithm v, Typeable a) => FromCBOR (CertifiedVRF v a) | |
Defined in Cardano.Crypto.VRF.Class | |
(Typeable algo, Typeable a, HashAlgorithm algo) => FromCBOR (AbstractHash algo a) | |
Defined in Cardano.Crypto.Hashing | |
Era era => FromCBOR (AlonzoPParams Identity era) | |
Defined in Cardano.Ledger.Alonzo.PParams | |
Era era => FromCBOR (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods fromCBOR :: Decoder s (AlonzoPParams StrictMaybe era) Source # label :: Proxy (AlonzoPParams StrictMaybe era) -> Text Source # | |
Era era => FromCBOR (BabbagePParams Identity era) | |
Defined in Cardano.Ledger.Babbage.PParams | |
Era era => FromCBOR (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods fromCBOR :: Decoder s (BabbagePParams StrictMaybe era) Source # label :: Proxy (BabbagePParams StrictMaybe era) -> Text Source # | |
Era era => FromCBOR (ConwayPParams Identity era) | |
Defined in Cardano.Ledger.Conway.PParams | |
Era era => FromCBOR (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods fromCBOR :: Decoder s (ConwayPParams StrictMaybe era) Source # label :: Proxy (ConwayPParams StrictMaybe era) -> Text Source # | |
(FromCBOR a, Bounded (BoundedRatio b a), Bounded a, Integral a, Typeable b, Show a) => FromCBOR (BoundedRatio b a) | |
(KnownSymbol rule, Era era) => FromCBOR (VoidEraRule rule era) | |
Defined in Cardano.Ledger.Core.Era | |
Era era => FromCBOR (ShelleyPParams Identity era) | |
Defined in Cardano.Ledger.Shelley.PParams | |
Era era => FromCBOR (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods fromCBOR :: Decoder s (ShelleyPParams StrictMaybe era) Source # label :: Proxy (ShelleyPParams StrictMaybe era) -> Text Source # | |
(Ord k, FromCBOR k, FromCBOR v) => FromCBOR (Map k v) | |
(FromCBOR a, FromCBOR b) => FromCBOR (a, b) | |
(Typeable s, FromCBOR a) => FromCBOR (Tagged s a) | |
(FromCBOR a, FromCBOR b, FromCBOR c) => FromCBOR (a, b, c) | |
(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d) => FromCBOR (a, b, c, d) | |
(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d, FromCBOR e) => FromCBOR (a, b, c, d, e) | |
(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d, FromCBOR e, FromCBOR f) => FromCBOR (a, b, c, d, e, f) | |
(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d, FromCBOR e, FromCBOR f, FromCBOR g) => FromCBOR (a, b, c, d, e, f, g) | |
(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d, FromCBOR e, FromCBOR f, FromCBOR g, FromCBOR h) => FromCBOR (a, b, c, d, e, f, g, h) | |
class Typeable a => ToCBOR a Source #
Minimal complete definition
Instances
ToCBOR Void | |
ToCBOR Int32 | |
ToCBOR Int64 | |
ToCBOR Word16 | |
ToCBOR Word32 | |
ToCBOR Word64 | |
ToCBOR Word8 | |
ToCBOR ByteString | |
Defined in Cardano.Binary.ToCBOR Methods toCBOR :: ByteString -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ByteString -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ByteString] -> Size Source # | |
ToCBOR ByteString | |
Defined in Cardano.Binary.ToCBOR Methods toCBOR :: ByteString -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ByteString -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ByteString] -> Size Source # | |
ToCBOR ShortByteString | |
Defined in Cardano.Binary.ToCBOR Methods toCBOR :: ShortByteString -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ShortByteString -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShortByteString] -> Size Source # | |
ToCBOR OperationalCertificate Source # | |
Defined in Cardano.Api.Internal.OperationalCertificate Methods toCBOR :: OperationalCertificate -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy OperationalCertificate -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [OperationalCertificate] -> Size Source # | |
ToCBOR OperationalCertificateIssueCounter Source # | |
Defined in Cardano.Api.Internal.OperationalCertificate Methods toCBOR :: OperationalCertificateIssueCounter -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy OperationalCertificateIssueCounter -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [OperationalCertificateIssueCounter] -> Size Source # | |
ToCBOR CostModel Source # | |
ToCBOR ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toCBOR :: ExecutionUnitPrices -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ExecutionUnitPrices -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ExecutionUnitPrices] -> Size Source # | |
ToCBOR PraosNonce Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toCBOR :: PraosNonce -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy PraosNonce -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PraosNonce] -> Size Source # | |
ToCBOR ProtocolParametersUpdate Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toCBOR :: ProtocolParametersUpdate -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtocolParametersUpdate -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtocolParametersUpdate] -> Size Source # | |
ToCBOR UpdateProposal Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toCBOR :: UpdateProposal -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy UpdateProposal -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UpdateProposal] -> Size Source # | |
ToCBOR AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods toCBOR :: AnyPlutusScriptVersion -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy AnyPlutusScriptVersion -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AnyPlutusScriptVersion] -> Size Source # | |
ToCBOR ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script Methods toCBOR :: ExecutionUnits -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ExecutionUnits -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ExecutionUnits] -> Size Source # | |
ToCBOR ScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods toCBOR :: ScriptData -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ScriptData -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ScriptData] -> Size Source # | |
ToCBOR Point | |
ToCBOR Proof | |
ToCBOR SignKey | |
ToCBOR VerKey | |
ToCBOR Proof | |
ToCBOR SignKey | |
ToCBOR VerKey | |
ToCBOR ProtocolMagicId | |
Defined in Cardano.Crypto.ProtocolMagic Methods toCBOR :: ProtocolMagicId -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtocolMagicId -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtocolMagicId] -> Size Source # | |
ToCBOR RequiresNetworkMagic | |
Defined in Cardano.Crypto.ProtocolMagic Methods toCBOR :: RequiresNetworkMagic -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy RequiresNetworkMagic -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [RequiresNetworkMagic] -> Size Source # | |
ToCBOR Raw | |
ToCBOR CompactRedeemVerificationKey | |
Defined in Cardano.Crypto.Signing.Redeem.Compact Methods toCBOR :: CompactRedeemVerificationKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CompactRedeemVerificationKey -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactRedeemVerificationKey] -> Size Source # | |
ToCBOR RedeemSigningKey | |
Defined in Cardano.Crypto.Signing.Redeem.SigningKey Methods toCBOR :: RedeemSigningKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy RedeemSigningKey -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [RedeemSigningKey] -> Size Source # | |
ToCBOR RedeemVerificationKey | |
Defined in Cardano.Crypto.Signing.Redeem.VerificationKey Methods toCBOR :: RedeemVerificationKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy RedeemVerificationKey -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [RedeemVerificationKey] -> Size Source # | |
ToCBOR SigningKey | |
Defined in Cardano.Crypto.Signing.SigningKey Methods toCBOR :: SigningKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SigningKey -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey] -> Size Source # | |
ToCBOR VerificationKey | |
Defined in Cardano.Crypto.Signing.VerificationKey Methods toCBOR :: VerificationKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy VerificationKey -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey] -> Size Source # | |
ToCBOR AlonzoGenesis | |
Defined in Cardano.Ledger.Alonzo.Genesis Methods toCBOR :: AlonzoGenesis -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy AlonzoGenesis -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoGenesis] -> Size Source # | |
ToCBOR IsValid | |
ToCBOR Version | |
ToCBOR Body | |
ToCBOR BlockSignature | |
Defined in Cardano.Chain.Block.Header Methods toCBOR :: BlockSignature -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockSignature -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BlockSignature] -> Size Source # | |
ToCBOR ToSign | |
ToCBOR Proof | |
ToCBOR ChainValidationState | |
Defined in Cardano.Chain.Block.Validation Methods toCBOR :: ChainValidationState -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ChainValidationState -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ChainValidationState] -> Size Source # | |
ToCBOR ApplyMempoolPayloadErr | |
Defined in Cardano.Chain.Byron.API.Mempool Methods toCBOR :: ApplyMempoolPayloadErr -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ApplyMempoolPayloadErr -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ApplyMempoolPayloadErr] -> Size Source # | |
ToCBOR HDAddressPayload | |
Defined in Cardano.Chain.Common.AddrAttributes Methods toCBOR :: HDAddressPayload -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy HDAddressPayload -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [HDAddressPayload] -> Size Source # | |
ToCBOR AddrSpendingData | |
Defined in Cardano.Chain.Common.AddrSpendingData Methods toCBOR :: AddrSpendingData -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy AddrSpendingData -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AddrSpendingData] -> Size Source # | |
ToCBOR AddrType | |
ToCBOR Address | |
ToCBOR Address' | |
ToCBOR BlockCount | |
Defined in Cardano.Chain.Common.BlockCount Methods toCBOR :: BlockCount -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockCount -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BlockCount] -> Size Source # | |
ToCBOR ChainDifficulty | |
Defined in Cardano.Chain.Common.ChainDifficulty Methods toCBOR :: ChainDifficulty -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ChainDifficulty -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ChainDifficulty] -> Size Source # | |
ToCBOR CompactAddress | |
Defined in Cardano.Chain.Common.Compact Methods toCBOR :: CompactAddress -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CompactAddress -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactAddress] -> Size Source # | |
ToCBOR Lovelace | |
ToCBOR LovelaceError | |
Defined in Cardano.Chain.Common.Lovelace Methods toCBOR :: LovelaceError -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy LovelaceError -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LovelaceError] -> Size Source # | |
ToCBOR LovelacePortion | |
Defined in Cardano.Chain.Common.LovelacePortion Methods toCBOR :: LovelacePortion -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy LovelacePortion -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LovelacePortion] -> Size Source # | |
ToCBOR NetworkMagic | |
Defined in Cardano.Chain.Common.NetworkMagic Methods toCBOR :: NetworkMagic -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy NetworkMagic -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NetworkMagic] -> Size Source # | |
ToCBOR TxFeePolicy | |
Defined in Cardano.Chain.Common.TxFeePolicy Methods toCBOR :: TxFeePolicy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxFeePolicy -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxFeePolicy] -> Size Source # | |
ToCBOR TxSizeLinear | |
Defined in Cardano.Chain.Common.TxSizeLinear Methods toCBOR :: TxSizeLinear -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxSizeLinear -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxSizeLinear] -> Size Source # | |
ToCBOR Certificate | |
Defined in Cardano.Chain.Delegation.Certificate Methods toCBOR :: Certificate -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Certificate -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Certificate] -> Size Source # | |
ToCBOR Map | |
ToCBOR Payload | |
ToCBOR State | |
ToCBOR State | |
ToCBOR Error | |
ToCBOR ScheduledDelegation | |
Defined in Cardano.Chain.Delegation.Validation.Scheduling Methods toCBOR :: ScheduledDelegation -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ScheduledDelegation -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ScheduledDelegation] -> Size Source # | |
ToCBOR State | |
ToCBOR GenesisAvvmBalances | |
Defined in Cardano.Chain.Genesis.AvvmBalances Methods toCBOR :: GenesisAvvmBalances -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy GenesisAvvmBalances -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [GenesisAvvmBalances] -> Size Source # | |
ToCBOR Config | |
ToCBOR GenesisData | |
Defined in Cardano.Chain.Genesis.Data Methods toCBOR :: GenesisData -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy GenesisData -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [GenesisData] -> Size Source # | |
ToCBOR GenesisDelegation | |
Defined in Cardano.Chain.Genesis.Delegation Methods toCBOR :: GenesisDelegation -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy GenesisDelegation -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [GenesisDelegation] -> Size Source # | |
ToCBOR GenesisKeyHashes | |
Defined in Cardano.Chain.Genesis.KeyHashes Methods toCBOR :: GenesisKeyHashes -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy GenesisKeyHashes -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [GenesisKeyHashes] -> Size Source # | |
ToCBOR GenesisNonAvvmBalances | |
Defined in Cardano.Chain.Genesis.NonAvvmBalances Methods toCBOR :: GenesisNonAvvmBalances -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy GenesisNonAvvmBalances -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [GenesisNonAvvmBalances] -> Size Source # | |
ToCBOR MempoolPayload | |
Defined in Cardano.Chain.MempoolPayload Methods toCBOR :: MempoolPayload -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy MempoolPayload -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [MempoolPayload] -> Size Source # | |
ToCBOR EpochAndSlotCount | |
Defined in Cardano.Chain.Slotting.EpochAndSlotCount Methods toCBOR :: EpochAndSlotCount -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochAndSlotCount -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochAndSlotCount] -> Size Source # | |
ToCBOR EpochNumber | |
Defined in Cardano.Chain.Slotting.EpochNumber Methods toCBOR :: EpochNumber -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochNumber -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochNumber] -> Size Source # | |
ToCBOR EpochSlots | |
Defined in Cardano.Chain.Slotting.EpochSlots Methods toCBOR :: EpochSlots -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochSlots -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochSlots] -> Size Source # | |
ToCBOR SlotCount | |
ToCBOR SlotNumber | |
Defined in Cardano.Chain.Slotting.SlotNumber Methods toCBOR :: SlotNumber -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotNumber -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SlotNumber] -> Size Source # | |
ToCBOR SscPayload | |
Defined in Cardano.Chain.Ssc Methods toCBOR :: SscPayload -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SscPayload -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SscPayload] -> Size Source # | |
ToCBOR SscProof | |
ToCBOR CompactTxId | |
Defined in Cardano.Chain.UTxO.Compact Methods toCBOR :: CompactTxId -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CompactTxId -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactTxId] -> Size Source # | |
ToCBOR CompactTxIn | |
Defined in Cardano.Chain.UTxO.Compact Methods toCBOR :: CompactTxIn -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CompactTxIn -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactTxIn] -> Size Source # | |
ToCBOR CompactTxOut | |
Defined in Cardano.Chain.UTxO.Compact Methods toCBOR :: CompactTxOut -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CompactTxOut -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactTxOut] -> Size Source # | |
ToCBOR Tx | |
ToCBOR TxIn | |
ToCBOR TxOut | |
ToCBOR TxAux | |
ToCBOR TxPayload | |
ToCBOR TxProof | |
ToCBOR TxInWitness | |
Defined in Cardano.Chain.UTxO.TxWitness Methods toCBOR :: TxInWitness -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxInWitness -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxInWitness] -> Size Source # | |
ToCBOR TxSigData | |
ToCBOR UTxO | |
ToCBOR UTxOError | |
ToCBOR UTxOConfiguration | |
Defined in Cardano.Chain.UTxO.UTxOConfiguration Methods toCBOR :: UTxOConfiguration -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy UTxOConfiguration -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTxOConfiguration] -> Size Source # | |
ToCBOR TxValidationError | |
Defined in Cardano.Chain.UTxO.Validation Methods toCBOR :: TxValidationError -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxValidationError -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxValidationError] -> Size Source # | |
ToCBOR UTxOValidationError | |
Defined in Cardano.Chain.UTxO.Validation Methods toCBOR :: UTxOValidationError -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy UTxOValidationError -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTxOValidationError] -> Size Source # | |
ToCBOR ApplicationName | |
Defined in Cardano.Chain.Update.ApplicationName Methods toCBOR :: ApplicationName -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ApplicationName -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ApplicationName] -> Size Source # | |
ToCBOR ApplicationNameError | |
Defined in Cardano.Chain.Update.ApplicationName Methods toCBOR :: ApplicationNameError -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ApplicationNameError -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ApplicationNameError] -> Size Source # | |
ToCBOR InstallerHash | |
Defined in Cardano.Chain.Update.InstallerHash Methods toCBOR :: InstallerHash -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy InstallerHash -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [InstallerHash] -> Size Source # | |
ToCBOR Payload | |
ToCBOR Proposal | |
ToCBOR ProposalBody | |
Defined in Cardano.Chain.Update.Proposal Methods toCBOR :: ProposalBody -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProposalBody -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProposalBody] -> Size Source # | |
ToCBOR ProtocolParameters | |
Defined in Cardano.Chain.Update.ProtocolParameters Methods toCBOR :: ProtocolParameters -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtocolParameters -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtocolParameters] -> Size Source # | |
ToCBOR ProtocolParametersUpdate | |
Defined in Cardano.Chain.Update.ProtocolParametersUpdate Methods toCBOR :: ProtocolParametersUpdate -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtocolParametersUpdate -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtocolParametersUpdate] -> Size Source # | |
ToCBOR ProtocolVersion | |
Defined in Cardano.Chain.Update.ProtocolVersion Methods toCBOR :: ProtocolVersion -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtocolVersion -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtocolVersion] -> Size Source # | |
ToCBOR SoftforkRule | |
Defined in Cardano.Chain.Update.SoftforkRule Methods toCBOR :: SoftforkRule -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SoftforkRule -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SoftforkRule] -> Size Source # | |
ToCBOR SoftwareVersion | |
Defined in Cardano.Chain.Update.SoftwareVersion Methods toCBOR :: SoftwareVersion -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SoftwareVersion -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SoftwareVersion] -> Size Source # | |
ToCBOR SoftwareVersionError | |
Defined in Cardano.Chain.Update.SoftwareVersion Methods toCBOR :: SoftwareVersionError -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SoftwareVersionError -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SoftwareVersionError] -> Size Source # | |
ToCBOR SystemTag | |
ToCBOR SystemTagError | |
Defined in Cardano.Chain.Update.SystemTag Methods toCBOR :: SystemTagError -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SystemTagError -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SystemTagError] -> Size Source # | |
ToCBOR CandidateProtocolUpdate | |
Defined in Cardano.Chain.Update.Validation.Endorsement Methods toCBOR :: CandidateProtocolUpdate -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CandidateProtocolUpdate -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CandidateProtocolUpdate] -> Size Source # | |
ToCBOR Endorsement | |
Defined in Cardano.Chain.Update.Validation.Endorsement Methods toCBOR :: Endorsement -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Endorsement -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Endorsement] -> Size Source # | |
ToCBOR Error | |
ToCBOR Error | |
ToCBOR State | |
ToCBOR Adopted | |
ToCBOR ApplicationVersion | |
Defined in Cardano.Chain.Update.Validation.Registration Methods toCBOR :: ApplicationVersion -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ApplicationVersion -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ApplicationVersion] -> Size Source # | |
ToCBOR Error | |
ToCBOR ProtocolUpdateProposal | |
Defined in Cardano.Chain.Update.Validation.Registration Methods toCBOR :: ProtocolUpdateProposal -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtocolUpdateProposal -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtocolUpdateProposal] -> Size Source # | |
ToCBOR SoftwareUpdateProposal | |
Defined in Cardano.Chain.Update.Validation.Registration Methods toCBOR :: SoftwareUpdateProposal -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SoftwareUpdateProposal -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SoftwareUpdateProposal] -> Size Source # | |
ToCBOR Error | |
ToCBOR Vote | |
ToCBOR ConwayGenesis | |
Defined in Cardano.Ledger.Conway.Genesis Methods toCBOR :: ConwayGenesis -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ConwayGenesis -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayGenesis] -> Size Source # | |
ToCBOR DefaultVote | |
Defined in Cardano.Ledger.Conway.Governance Methods toCBOR :: DefaultVote -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy DefaultVote -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [DefaultVote] -> Size Source # | |
ToCBOR ActiveSlotCoeff | |
Defined in Cardano.Ledger.BaseTypes Methods toCBOR :: ActiveSlotCoeff -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ActiveSlotCoeff -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ActiveSlotCoeff] -> Size Source # | |
ToCBOR CertIx | |
ToCBOR Network | |
ToCBOR Nonce | |
ToCBOR PositiveUnitInterval | |
Defined in Cardano.Ledger.BaseTypes Methods toCBOR :: PositiveUnitInterval -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy PositiveUnitInterval -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PositiveUnitInterval] -> Size Source # | |
ToCBOR ProtVer | |
ToCBOR TxIx | |
ToCBOR Coin | |
ToCBOR DeltaCoin | |
ToCBOR Ptr | |
ToCBOR SlotNo32 | |
ToCBOR ScriptHash | |
Defined in Cardano.Ledger.Hashes Methods toCBOR :: ScriptHash -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ScriptHash -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ScriptHash] -> Size Source # | |
ToCBOR BootstrapWitness | |
Defined in Cardano.Ledger.Keys.Bootstrap Methods toCBOR :: BootstrapWitness -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BootstrapWitness -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BootstrapWitness] -> Size Source # | |
ToCBOR PlutusWithContext | |
Defined in Cardano.Ledger.Plutus.Evaluate Methods toCBOR :: PlutusWithContext -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy PlutusWithContext -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PlutusWithContext] -> Size Source # | |
ToCBOR Language | |
ToCBOR PlutusBinary | |
Defined in Cardano.Ledger.Plutus.Language Methods toCBOR :: PlutusBinary -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy PlutusBinary -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PlutusBinary] -> Size Source # | |
ToCBOR ShelleyGenesis | |
Defined in Cardano.Ledger.Shelley.Genesis Methods toCBOR :: ShelleyGenesis -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ShelleyGenesis -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesis] -> Size Source # | |
ToCBOR FromByronTranslationContext | |
Defined in Cardano.Ledger.Shelley.Translation Methods toCBOR :: FromByronTranslationContext -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy FromByronTranslationContext -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [FromByronTranslationContext] -> Size Source # | |
ToCBOR ChainDepState | |
Defined in Cardano.Protocol.TPraos.API Methods toCBOR :: ChainDepState -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ChainDepState -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ChainDepState] -> Size Source # | |
ToCBOR KESPeriod | |
ToCBOR PrtclState | |
Defined in Cardano.Protocol.TPraos.Rules.Prtcl Methods toCBOR :: PrtclState -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy PrtclState -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PrtclState] -> Size Source # | |
ToCBOR TicknState | |
Defined in Cardano.Protocol.TPraos.Rules.Tickn Methods toCBOR :: TicknState -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TicknState -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TicknState] -> Size Source # | |
ToCBOR BlockNo | |
ToCBOR EpochInterval | |
Defined in Cardano.Slotting.Slot Methods toCBOR :: EpochInterval -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochInterval -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochInterval] -> Size Source # | |
ToCBOR EpochNo | |
ToCBOR EpochSize | |
ToCBOR SlotNo | |
ToCBOR RelativeTime | |
Defined in Cardano.Slotting.Time Methods toCBOR :: RelativeTime -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy RelativeTime -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [RelativeTime] -> Size Source # | |
ToCBOR SlotLength | |
Defined in Cardano.Slotting.Time Methods toCBOR :: SlotLength -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotLength -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SlotLength] -> Size Source # | |
ToCBOR SystemStart | |
Defined in Cardano.Slotting.Time Methods toCBOR :: SystemStart -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size Source # | |
ToCBOR Encoding | |
ToCBOR Term | |
ToCBOR SecurityParam | |
Defined in Ouroboros.Consensus.Config.SecurityParam Methods toCBOR :: SecurityParam -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SecurityParam -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SecurityParam] -> Size Source # | |
ToCBOR CoreNodeId | |
Defined in Ouroboros.Consensus.NodeId Methods toCBOR :: CoreNodeId -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CoreNodeId -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CoreNodeId] -> Size Source # | |
ToCBOR NodeId | |
ToCBOR CompactGenesis | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Config Methods toCBOR :: CompactGenesis -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CompactGenesis -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactGenesis] -> Size Source # | |
ToCBOR NonMyopicMemberRewards | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods toCBOR :: NonMyopicMemberRewards -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy NonMyopicMemberRewards -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NonMyopicMemberRewards] -> Size Source # | |
ToCBOR StakeSnapshot | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods toCBOR :: StakeSnapshot -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy StakeSnapshot -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshot] -> Size Source # | |
ToCBOR StakeSnapshots | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods toCBOR :: StakeSnapshots -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy StakeSnapshots -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshots] -> Size Source # | |
ToCBOR ShelleyHash | |
Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract Methods toCBOR :: ShelleyHash -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ShelleyHash -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyHash] -> Size Source # | |
ToCBOR PraosState | |
Defined in Ouroboros.Consensus.Protocol.Praos Methods toCBOR :: PraosState -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy PraosState -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PraosState] -> Size Source # | |
ToCBOR InputVRF | |
ToCBOR TPraosState | |
Defined in Ouroboros.Consensus.Protocol.TPraos Methods toCBOR :: TPraosState -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TPraosState -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TPraosState] -> Size Source # | |
ToCBOR AccPoolStakeCoded | |
ToCBOR LedgerPeerSnapshot | |
Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type Methods toCBOR :: LedgerPeerSnapshot -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy LedgerPeerSnapshot -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LedgerPeerSnapshot] -> Size Source # | |
ToCBOR PoolStakeCoded | |
ToCBOR WithOriginCoded | Hand cranked CBOR instances to facilitate CDDL spec |
ToCBOR RelayAccessPointCoded | These instances are used to serialize |
Defined in Ouroboros.Network.PeerSelection.RelayAccessPoint Methods toCBOR :: RelayAccessPointCoded -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy RelayAccessPointCoded -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [RelayAccessPointCoded] -> Size Source # | |
ToCBOR Text | |
ToCBOR UTCTime | |
ToCBOR Integer | |
ToCBOR Natural | |
ToCBOR () | |
ToCBOR Bool | |
ToCBOR Double | |
ToCBOR Float | |
ToCBOR Int | |
ToCBOR Word | |
ToCBOR a => ToCBOR (NonEmpty a) | |
ToCBOR a => ToCBOR (Ratio a) | |
IsShelleyBasedEra era => ToCBOR (Certificate era) Source # | |
Defined in Cardano.Api.Internal.Certificate Methods toCBOR :: Certificate era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Certificate era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Certificate era] -> Size Source # | |
IsShelleyBasedEra era => ToCBOR (Proposal era) Source # | |
IsShelleyBasedEra era => ToCBOR (VotingProcedure era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods toCBOR :: VotingProcedure era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VotingProcedure era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VotingProcedure era] -> Size Source # | |
IsShelleyBasedEra era => ToCBOR (VotingProcedures era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods toCBOR :: VotingProcedures era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VotingProcedures era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VotingProcedures era] -> Size Source # | |
ToCBOR (Hash ByronKey) Source # | |
ToCBOR (Hash ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
ToCBOR (Hash KesKey) Source # | |
ToCBOR (Hash VrfKey) Source # | |
ToCBOR (Hash CommitteeColdExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeColdExtendedKey] -> Size Source # | |
ToCBOR (Hash CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash CommitteeHotExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeHotExtendedKey] -> Size Source # | |
ToCBOR (Hash CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash DRepKey) Source # | |
ToCBOR (Hash GenesisDelegateExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash GenesisDelegateExtendedKey] -> Size Source # | |
ToCBOR (Hash GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash StakeKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (Hash StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (SigningKey ByronKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
ToCBOR (SigningKey ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: SigningKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size Source # | |
ToCBOR (SigningKey KesKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
ToCBOR (SigningKey VrfKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
ToCBOR (SigningKey CommitteeColdExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdExtendedKey] -> Size Source # | |
ToCBOR (SigningKey CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdKey] -> Size Source # | |
ToCBOR (SigningKey CommitteeHotExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotExtendedKey] -> Size Source # | |
ToCBOR (SigningKey CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotKey] -> Size Source # | |
ToCBOR (SigningKey DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey DRepExtendedKey] -> Size Source # | |
ToCBOR (SigningKey DRepKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateExtendedKey] -> Size Source # | |
ToCBOR (SigningKey GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateKey] -> Size Source # | |
ToCBOR (SigningKey GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisExtendedKey] -> Size Source # | |
ToCBOR (SigningKey GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisKey] -> Size Source # | |
ToCBOR (SigningKey GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisUTxOKey] -> Size Source # | |
ToCBOR (SigningKey PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size Source # | |
ToCBOR (SigningKey PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size Source # | |
ToCBOR (SigningKey StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size Source # | |
ToCBOR (SigningKey StakeKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (SigningKey StakePoolExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolExtendedKey] -> Size Source # | |
ToCBOR (SigningKey StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolKey] -> Size Source # | |
ToCBOR (VerificationKey ByronKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
ToCBOR (VerificationKey ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: VerificationKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size Source # | |
ToCBOR (VerificationKey KesKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
ToCBOR (VerificationKey VrfKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
ToCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdKey] -> Size Source # | |
ToCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotKey] -> Size Source # | |
ToCBOR (VerificationKey DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey DRepExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey DRepKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateKey] -> Size Source # | |
ToCBOR (VerificationKey GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisKey] -> Size Source # | |
ToCBOR (VerificationKey GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisUTxOKey] -> Size Source # | |
ToCBOR (VerificationKey PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size Source # | |
ToCBOR (VerificationKey StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey StakeKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
ToCBOR (VerificationKey StakePoolExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolExtendedKey] -> Size Source # | |
ToCBOR (VerificationKey StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolKey] -> Size Source # | |
SerialiseAsRawBytes a => ToCBOR (UsingRawBytes a) Source # | |
Defined in Cardano.Api.Internal.SerialiseUsing Methods toCBOR :: UsingRawBytes a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UsingRawBytes a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UsingRawBytes a] -> Size Source # | |
Typeable xs => ToCBOR (LengthOf xs) | |
ToCBOR (SigDSIGN Ed25519Bip32DSIGN) Source # | |
Defined in Cardano.Api.Crypto.Ed25519Bip32 | |
ToCBOR (SigDSIGN EcdsaSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Methods toCBOR :: SigDSIGN EcdsaSecp256k1DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigDSIGN EcdsaSecp256k1DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigDSIGN EcdsaSecp256k1DSIGN] -> Size Source # | |
ToCBOR (SigDSIGN Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 | |
ToCBOR (SigDSIGN Ed448DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed448 | |
ToCBOR (SigDSIGN MockDSIGN) | |
Defined in Cardano.Crypto.DSIGN.Mock | |
ToCBOR (SigDSIGN SchnorrSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Methods toCBOR :: SigDSIGN SchnorrSecp256k1DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigDSIGN SchnorrSecp256k1DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigDSIGN SchnorrSecp256k1DSIGN] -> Size Source # | |
ToCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) Source # | |
Defined in Cardano.Api.Crypto.Ed25519Bip32 Methods toCBOR :: SignKeyDSIGN Ed25519Bip32DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyDSIGN Ed25519Bip32DSIGN] -> Size Source # | |
ToCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Methods toCBOR :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyDSIGN EcdsaSecp256k1DSIGN] -> Size Source # | |
ToCBOR (SignKeyDSIGN Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 Methods toCBOR :: SignKeyDSIGN Ed25519DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyDSIGN Ed25519DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyDSIGN Ed25519DSIGN] -> Size Source # | |
ToCBOR (SignKeyDSIGN Ed448DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed448 Methods toCBOR :: SignKeyDSIGN Ed448DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyDSIGN Ed448DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyDSIGN Ed448DSIGN] -> Size Source # | |
ToCBOR (SignKeyDSIGN MockDSIGN) | |
Defined in Cardano.Crypto.DSIGN.Mock | |
ToCBOR (SignKeyDSIGN SchnorrSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Methods toCBOR :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyDSIGN SchnorrSecp256k1DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyDSIGN SchnorrSecp256k1DSIGN] -> Size Source # | |
(TypeError ('Text "CBOR encoding would violate mlocking guarantees") :: Constraint) => ToCBOR (SignKeyDSIGNM Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 Methods toCBOR :: SignKeyDSIGNM Ed25519DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyDSIGNM Ed25519DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyDSIGNM Ed25519DSIGN] -> Size Source # | |
ToCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) Source # | |
Defined in Cardano.Api.Crypto.Ed25519Bip32 Methods toCBOR :: VerKeyDSIGN Ed25519Bip32DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyDSIGN Ed25519Bip32DSIGN] -> Size Source # | |
ToCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1 Methods toCBOR :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyDSIGN EcdsaSecp256k1DSIGN] -> Size Source # | |
ToCBOR (VerKeyDSIGN Ed25519DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed25519 Methods toCBOR :: VerKeyDSIGN Ed25519DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyDSIGN Ed25519DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyDSIGN Ed25519DSIGN] -> Size Source # | |
ToCBOR (VerKeyDSIGN Ed448DSIGN) | |
Defined in Cardano.Crypto.DSIGN.Ed448 Methods toCBOR :: VerKeyDSIGN Ed448DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyDSIGN Ed448DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyDSIGN Ed448DSIGN] -> Size Source # | |
ToCBOR (VerKeyDSIGN MockDSIGN) | |
Defined in Cardano.Crypto.DSIGN.Mock | |
ToCBOR (VerKeyDSIGN SchnorrSecp256k1DSIGN) | |
Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1 Methods toCBOR :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyDSIGN SchnorrSecp256k1DSIGN) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyDSIGN SchnorrSecp256k1DSIGN] -> Size Source # | |
(DSIGNMAlgorithm d, KnownNat (SizeSigKES (CompactSingleKES d))) => ToCBOR (SigKES (CompactSingleKES d)) | |
Defined in Cardano.Crypto.KES.CompactSingle | |
(OptimizedKESAlgorithm d, SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d, NoThunks (VerKeyKES (CompactSumKES h d)), KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) => ToCBOR (SigKES (CompactSumKES h d)) | |
Defined in Cardano.Crypto.KES.CompactSum | |
KnownNat t => ToCBOR (SigKES (MockKES t)) | |
Defined in Cardano.Crypto.KES.Mock | |
(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => ToCBOR (SigKES (SimpleKES d t)) | |
Defined in Cardano.Crypto.KES.Simple | |
DSIGNMAlgorithm d => ToCBOR (SigKES (SingleKES d)) | |
Defined in Cardano.Crypto.KES.Single | |
(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => ToCBOR (SigKES (SumKES h d)) | |
Defined in Cardano.Crypto.KES.Sum | |
(UnsoundDSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => ToCBOR (UnsoundPureSignKeyKES (CompactSingleKES d)) | |
Defined in Cardano.Crypto.KES.CompactSingle Methods toCBOR :: UnsoundPureSignKeyKES (CompactSingleKES d) -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UnsoundPureSignKeyKES (CompactSingleKES d)) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UnsoundPureSignKeyKES (CompactSingleKES d)] -> Size Source # | |
(SizeHash h ~ SeedSizeKES d, OptimizedKESAlgorithm d, UnsoundPureKESAlgorithm d, SodiumHashAlgorithm h, KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) => ToCBOR (UnsoundPureSignKeyKES (CompactSumKES h d)) | |
Defined in Cardano.Crypto.KES.CompactSum Methods toCBOR :: UnsoundPureSignKeyKES (CompactSumKES h d) -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UnsoundPureSignKeyKES (CompactSumKES h d)) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UnsoundPureSignKeyKES (CompactSumKES h d)] -> Size Source # | |
KnownNat t => ToCBOR (UnsoundPureSignKeyKES (MockKES t)) | |
Defined in Cardano.Crypto.KES.Mock Methods toCBOR :: UnsoundPureSignKeyKES (MockKES t) -> Encoding Source # encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (UnsoundPureSignKeyKES (MockKES t)) -> Size Source # encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [UnsoundPureSignKeyKES (MockKES t)] -> Size Source # | |
UnsoundDSIGNMAlgorithm d => ToCBOR (UnsoundPureSignKeyKES (SingleKES d)) | |
Defined in Cardano.Crypto.KES.Single Methods toCBOR :: UnsoundPureSignKeyKES (SingleKES d) -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UnsoundPureSignKeyKES (SingleKES d)) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UnsoundPureSignKeyKES (SingleKES d)] -> Size Source # | |
(SizeHash h ~ SeedSizeKES d, UnsoundPureKESAlgorithm d, SodiumHashAlgorithm h, KnownNat (SizeVerKeyKES (SumKES h d)), KnownNat (SizeSignKeyKES (SumKES h d)), KnownNat (SizeSigKES (SumKES h d))) => ToCBOR (UnsoundPureSignKeyKES (SumKES h d)) | |
Defined in Cardano.Crypto.KES.Sum Methods toCBOR :: UnsoundPureSignKeyKES (SumKES h d) -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UnsoundPureSignKeyKES (SumKES h d)) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UnsoundPureSignKeyKES (SumKES h d)] -> Size Source # | |
(DSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => ToCBOR (VerKeyKES (CompactSingleKES d)) | |
Defined in Cardano.Crypto.KES.CompactSingle Methods toCBOR :: VerKeyKES (CompactSingleKES d) -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyKES (CompactSingleKES d)) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyKES (CompactSingleKES d)] -> Size Source # | |
(OptimizedKESAlgorithm d, SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d, NoThunks (VerKeyKES (CompactSumKES h d)), KnownNat (SizeVerKeyKES (CompactSumKES h d)), KnownNat (SizeSignKeyKES (CompactSumKES h d)), KnownNat (SizeSigKES (CompactSumKES h d))) => ToCBOR (VerKeyKES (CompactSumKES h d)) | |
Defined in Cardano.Crypto.KES.CompactSum Methods toCBOR :: VerKeyKES (CompactSumKES h d) -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyKES (CompactSumKES h d)) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyKES (CompactSumKES h d)] -> Size Source # | |
KnownNat t => ToCBOR (VerKeyKES (MockKES t)) | |
Defined in Cardano.Crypto.KES.Mock | |
(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => ToCBOR (VerKeyKES (SimpleKES d t)) | |
Defined in Cardano.Crypto.KES.Simple | |
DSIGNMAlgorithm d => ToCBOR (VerKeyKES (SingleKES d)) | |
Defined in Cardano.Crypto.KES.Single | |
(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => ToCBOR (VerKeyKES (SumKES h d)) | |
Defined in Cardano.Crypto.KES.Sum | |
ToCBOR (CertVRF MockVRF) | |
ToCBOR (CertVRF SimpleVRF) | |
Defined in Cardano.Crypto.VRF.Simple | |
ToCBOR (CertVRF PraosVRF) | |
Defined in Cardano.Crypto.VRF.Praos | |
ToCBOR (CertVRF PraosBatchCompatVRF) | |
Defined in Cardano.Crypto.VRF.PraosBatchCompat | |
Typeable v => ToCBOR (OutputVRF v) | |
ToCBOR (SignKeyVRF MockVRF) | |
Defined in Cardano.Crypto.VRF.Mock | |
ToCBOR (SignKeyVRF SimpleVRF) | |
Defined in Cardano.Crypto.VRF.Simple | |
ToCBOR (SignKeyVRF PraosVRF) | |
Defined in Cardano.Crypto.VRF.Praos | |
ToCBOR (SignKeyVRF PraosBatchCompatVRF) | |
Defined in Cardano.Crypto.VRF.PraosBatchCompat Methods toCBOR :: SignKeyVRF PraosBatchCompatVRF -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyVRF PraosBatchCompatVRF) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyVRF PraosBatchCompatVRF] -> Size Source # | |
ToCBOR (VerKeyVRF MockVRF) | |
Defined in Cardano.Crypto.VRF.Mock | |
ToCBOR (VerKeyVRF SimpleVRF) | |
Defined in Cardano.Crypto.VRF.Simple | |
ToCBOR (VerKeyVRF PraosVRF) | |
Defined in Cardano.Crypto.VRF.Praos | |
ToCBOR (VerKeyVRF PraosBatchCompatVRF) | |
Defined in Cardano.Crypto.VRF.PraosBatchCompat Methods toCBOR :: VerKeyVRF PraosBatchCompatVRF -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyVRF PraosBatchCompatVRF) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyVRF PraosBatchCompatVRF] -> Size Source # | |
EncCBOR a => ToCBOR (RedeemSignature a) | |
Defined in Cardano.Crypto.Signing.Redeem.Signature Methods toCBOR :: RedeemSignature a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (RedeemSignature a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [RedeemSignature a] -> Size Source # | |
Typeable a => ToCBOR (Signature a) | |
Typeable era => ToCBOR (AllegraTxAuxData era) | |
Defined in Cardano.Ledger.Allegra.TxAuxData Methods toCBOR :: AllegraTxAuxData era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AllegraTxAuxData era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AllegraTxAuxData era] -> Size Source # | |
Typeable e => ToCBOR (AllegraTxBody e) | |
Defined in Cardano.Ledger.Allegra.TxBody.Internal Methods toCBOR :: AllegraTxBody e -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AllegraTxBody e) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AllegraTxBody e] -> Size Source # | |
AlonzoEraScript era => ToCBOR (AlonzoScript era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods toCBOR :: AlonzoScript era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoScript era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoScript era] -> Size Source # | |
(Era era, EncCBOR (TxBody era), EncCBOR (TxAuxData era), EncCBOR (TxWits era)) => ToCBOR (AlonzoTx era) | |
Typeable era => ToCBOR (AlonzoTxAuxData era) | |
Defined in Cardano.Ledger.Alonzo.TxAuxData Methods toCBOR :: AlonzoTxAuxData era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxAuxData era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoTxAuxData era] -> Size Source # | |
Typeable era => ToCBOR (AlonzoTxBody era) | |
Defined in Cardano.Ledger.Alonzo.TxBody.Internal Methods toCBOR :: AlonzoTxBody era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxBody era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoTxBody era] -> Size Source # | |
(Era era, Val (Value era)) => ToCBOR (AlonzoTxOut era) | |
Defined in Cardano.Ledger.Alonzo.TxOut Methods toCBOR :: AlonzoTxOut era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxOut era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoTxOut era] -> Size Source # | |
Typeable era => ToCBOR (AlonzoTxWits era) | |
Defined in Cardano.Ledger.Alonzo.TxWits Methods toCBOR :: AlonzoTxWits era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxWits era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoTxWits era] -> Size Source # | |
Typeable era => ToCBOR (Redeemers era) | |
Typeable era => ToCBOR (TxDats era) | |
Typeable era => ToCBOR (BabbageTxBody era) | |
Defined in Cardano.Ledger.Babbage.TxBody.Internal Methods toCBOR :: BabbageTxBody era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbageTxBody era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BabbageTxBody era] -> Size Source # | |
(EraScript era, Val (Value era)) => ToCBOR (BabbageTxOut era) | |
Defined in Cardano.Ledger.Babbage.TxOut Methods toCBOR :: BabbageTxOut era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbageTxOut era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BabbageTxOut era] -> Size Source # | |
ToCBOR (Attributes AddrAttributes) | |
Defined in Cardano.Chain.Common.AddrAttributes Methods toCBOR :: Attributes AddrAttributes -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Attributes AddrAttributes) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Attributes AddrAttributes] -> Size Source # | |
ToCBOR (Attributes ()) | |
Defined in Cardano.Chain.Common.Attributes Methods toCBOR :: Attributes () -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Attributes ()) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Attributes ()] -> Size Source # | |
EncCBOR a => ToCBOR (MerkleRoot a) | |
Defined in Cardano.Chain.Common.Merkle Methods toCBOR :: MerkleRoot a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (MerkleRoot a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [MerkleRoot a] -> Size Source # | |
EncCBOR a => ToCBOR (MerkleTree a) | |
Defined in Cardano.Chain.Common.Merkle Methods toCBOR :: MerkleTree a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (MerkleTree a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [MerkleTree a] -> Size Source # | |
ToCBOR (AMempoolPayload ByteString) | |
Defined in Cardano.Chain.MempoolPayload Methods toCBOR :: AMempoolPayload ByteString -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AMempoolPayload ByteString) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AMempoolPayload ByteString] -> Size Source # | |
EncCBOR n => ToCBOR (TooLarge n) | |
Defined in Cardano.Chain.Update.Validation.Registration | |
(EraPParams era, EraStake era) => ToCBOR (ConwayGovState era) | |
Defined in Cardano.Ledger.Conway.Governance Methods toCBOR :: ConwayGovState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayGovState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayGovState era] -> Size Source # | |
EraPParams era => ToCBOR (PulsingSnapshot era) | |
Defined in Cardano.Ledger.Conway.Governance.DRepPulser Methods toCBOR :: PulsingSnapshot era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PulsingSnapshot era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PulsingSnapshot era] -> Size Source # | |
EraPParams era => ToCBOR (EnactState era) | |
Defined in Cardano.Ledger.Conway.Governance.Internal Methods toCBOR :: EnactState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (EnactState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EnactState era] -> Size Source # | |
Era era => ToCBOR (Constitution era) | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toCBOR :: Constitution era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Constitution era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Constitution era] -> Size Source # | |
EraPParams era => ToCBOR (ConwayGovPredFailure era) | |
Defined in Cardano.Ledger.Conway.Rules.Gov Methods toCBOR :: ConwayGovPredFailure era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayGovPredFailure era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayGovPredFailure era] -> Size Source # | |
Typeable era => ToCBOR (ConwayTxBody era) | |
Defined in Cardano.Ledger.Conway.TxBody.Internal Methods toCBOR :: ConwayTxBody era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayTxBody era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayTxBody era] -> Size Source # | |
(Era era, Val (Value era)) => ToCBOR (ConwayTxCert era) | |
Defined in Cardano.Ledger.Conway.TxCert Methods toCBOR :: ConwayTxCert era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayTxCert era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayTxCert era] -> Size Source # | |
ToCBOR a => ToCBOR (NonZero a) | |
Era era => ToCBOR (CommitteeState era) | |
Defined in Cardano.Ledger.CertState Methods toCBOR :: CommitteeState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CommitteeState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CommitteeState era] -> Size Source # | |
ToCBOR (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin | |
(Typeable era, ToCBOR (PParamsHKD Identity era)) => ToCBOR (PParams era) | |
(Typeable era, ToCBOR (PParamsHKD StrictMaybe era)) => ToCBOR (PParamsUpdate era) | |
Defined in Cardano.Ledger.Core.PParams Methods toCBOR :: PParamsUpdate era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PParamsUpdate era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PParamsUpdate era] -> Size Source # | |
Typeable kr => ToCBOR (Credential kr) | |
Defined in Cardano.Ledger.Credential Methods toCBOR :: Credential kr -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Credential kr) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Credential kr] -> Size Source # | |
Era era => ToCBOR (NoGenesis era) | |
Typeable r => ToCBOR (KeyHash r) | |
Typeable i => ToCBOR (SafeHash i) | |
Typeable r => ToCBOR (VRFVerKeyHash r) | |
Defined in Cardano.Ledger.Hashes Methods toCBOR :: VRFVerKeyHash r -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VRFVerKeyHash r) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VRFVerKeyHash r] -> Size Source # | |
Typeable kd => ToCBOR (VKey kd) | |
Typeable kr => ToCBOR (WitVKey kr) | |
Typeable t => ToCBOR (MemoBytes t) | |
Defined in Cardano.Ledger.MemoBytes.Internal | |
Typeable era => ToCBOR (Data era) | |
PlutusLanguage l => ToCBOR (SLanguage l) | |
(EncCBOR (TxOut era), Era era) => ToCBOR (UTxO era) | |
Typeable era => ToCBOR (MaryTxBody era) | |
Defined in Cardano.Ledger.Mary.TxBody.Internal Methods toCBOR :: MaryTxBody era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (MaryTxBody era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [MaryTxBody era] -> Size Source # | |
(Era era, EncCBOR (PredicateFailure (EraRule "LEDGER" era))) => ToCBOR (ApplyTxError era) | |
Defined in Cardano.Ledger.Shelley.API.Mempool Methods toCBOR :: ApplyTxError era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ApplyTxError era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ApplyTxError era] -> Size Source # | |
(Era era, EncCBOR (PParamsUpdate era), EncCBOR (PParams era)) => ToCBOR (ShelleyGovState era) | |
Defined in Cardano.Ledger.Shelley.Governance Methods toCBOR :: ShelleyGovState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyGovState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyGovState era] -> Size Source # | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era) => ToCBOR (EpochState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods toCBOR :: EpochState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (EpochState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochState era] -> Size Source # | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era) => ToCBOR (LedgerState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods toCBOR :: LedgerState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LedgerState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LedgerState era] -> Size Source # | |
(EraTxOut era, EraGov era, EraStake era, EraCertState era, EncCBOR (StashedAVVMAddresses era)) => ToCBOR (NewEpochState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods toCBOR :: NewEpochState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NewEpochState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NewEpochState era] -> Size Source # | |
(EraTxOut era, EraGov era, EraStake era) => ToCBOR (UTxOState era) | |
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |
(Era era, ToCBOR (PParamsUpdate era)) => ToCBOR (ProposedPPUpdates era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toCBOR :: ProposedPPUpdates era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ProposedPPUpdates era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProposedPPUpdates era] -> Size Source # | |
Typeable era => ToCBOR (MultiSig era) | |
Typeable era => ToCBOR (ShelleyTx era) | |
Defined in Cardano.Ledger.Shelley.Tx.Internal | |
Typeable era => ToCBOR (ShelleyTxAuxData era) | |
Defined in Cardano.Ledger.Shelley.TxAuxData Methods toCBOR :: ShelleyTxAuxData era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxAuxData era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxAuxData era] -> Size Source # | |
Typeable era => ToCBOR (ShelleyTxBody era) | |
Defined in Cardano.Ledger.Shelley.TxBody Methods toCBOR :: ShelleyTxBody era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxBody era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxBody era] -> Size Source # | |
Era era => ToCBOR (ShelleyTxCert era) | |
Defined in Cardano.Ledger.Shelley.TxCert Methods toCBOR :: ShelleyTxCert era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxCert era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxCert era] -> Size Source # | |
(Era era, EncCBOR (CompactForm (Value era))) => ToCBOR (ShelleyTxOut era) | |
Defined in Cardano.Ledger.Shelley.TxOut Methods toCBOR :: ShelleyTxOut era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxOut era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxOut era] -> Size Source # | |
Typeable era => ToCBOR (ShelleyTxWits era) | |
Defined in Cardano.Ledger.Shelley.TxWits Methods toCBOR :: ShelleyTxWits era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxWits era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxWits era] -> Size Source # | |
Typeable c => ToCBOR (BHeader c) | |
Crypto c => ToCBOR (OCert c) | |
(Serialise t, Typeable t) => ToCBOR (WithOrigin t) | |
Defined in Cardano.Slotting.Slot Methods toCBOR :: WithOrigin t -> Encoding Source # encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (WithOrigin t) -> Size Source # encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [WithOrigin t] -> Size Source # | |
ToCBOR a => ToCBOR (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods toCBOR :: StrictMaybe a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StrictMaybe a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StrictMaybe a] -> Size Source # | |
ToCBOR a => ToCBOR (StrictSeq a) | |
ToCBOR a => ToCBOR (Seq a) | |
(Ord a, ToCBOR a) => ToCBOR (Set a) | |
Crypto c => ToCBOR (Header c) | |
ToCBOR a => ToCBOR (Vector a) | |
ToCBOR a => ToCBOR (Maybe a) | |
ToCBOR a => ToCBOR [a] | |
(ToCBOR a, ToCBOR b) => ToCBOR (Either a b) | |
Typeable a => ToCBOR (Fixed a) | |
(HashAlgorithm h, Typeable a) => ToCBOR (Hash h a) | |
(VRFAlgorithm v, Typeable a) => ToCBOR (CertifiedVRF v a) | |
Defined in Cardano.Crypto.VRF.Class Methods toCBOR :: CertifiedVRF v a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CertifiedVRF v a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertifiedVRF v a] -> Size Source # | |
(Typeable algo, Typeable a, HashAlgorithm algo) => ToCBOR (AbstractHash algo a) | |
Defined in Cardano.Crypto.Hashing Methods toCBOR :: AbstractHash algo a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AbstractHash algo a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AbstractHash algo a] -> Size Source # | |
(Typeable era, Typeable k) => ToCBOR (Timelock era) | |
Era era => ToCBOR (AlonzoPParams Identity era) | |
Defined in Cardano.Ledger.Alonzo.PParams | |
Era era => ToCBOR (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toCBOR :: AlonzoPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoPParams StrictMaybe era] -> Size Source # | |
Era era => ToCBOR (BabbagePParams Identity era) | |
Defined in Cardano.Ledger.Babbage.PParams | |
Era era => ToCBOR (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods toCBOR :: BabbagePParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbagePParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BabbagePParams StrictMaybe era] -> Size Source # | |
Era era => ToCBOR (ConwayPParams Identity era) | |
Defined in Cardano.Ledger.Conway.PParams | |
Era era => ToCBOR (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods toCBOR :: ConwayPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayPParams StrictMaybe era] -> Size Source # | |
(ToCBOR a, Integral a, Bounded a, Typeable b) => ToCBOR (BoundedRatio b a) | |
Defined in Cardano.Ledger.BaseTypes | |
(EraTx era, Typeable h) => ToCBOR (Block h era) | |
(KnownSymbol rule, Era era) => ToCBOR (VoidEraRule rule era) | |
Defined in Cardano.Ledger.Core.Era Methods toCBOR :: VoidEraRule rule era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VoidEraRule rule era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VoidEraRule rule era] -> Size Source # | |
Era era => ToCBOR (ShelleyPParams Identity era) | |
Defined in Cardano.Ledger.Shelley.PParams | |
Era era => ToCBOR (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toCBOR :: ShelleyPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyPParams StrictMaybe era] -> Size Source # | |
(Ord k, ToCBOR k, ToCBOR v) => ToCBOR (Map k v) | |
(ToCBOR a, ToCBOR b) => ToCBOR (a, b) | |
ToCBOR (Tokens -> Tokens) | |
(Typeable s, ToCBOR a) => ToCBOR (Tagged s a) | |
(ToCBOR a, ToCBOR b, ToCBOR c) => ToCBOR (a, b, c) | |
(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d) => ToCBOR (a, b, c, d) | |
(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d, ToCBOR e) => ToCBOR (a, b, c, d, e) | |
(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d, ToCBOR e, ToCBOR f) => ToCBOR (a, b, c, d, e, f) | |
Defined in Cardano.Binary.ToCBOR | |
(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d, ToCBOR e, ToCBOR f, ToCBOR g) => ToCBOR (a, b, c, d, e, f, g) | |
Defined in Cardano.Binary.ToCBOR | |
(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d, ToCBOR e, ToCBOR f, ToCBOR g, ToCBOR h) => ToCBOR (a, b, c, d, e, f, g, h) | |
Defined in Cardano.Binary.ToCBOR |
data family VerificationKey keyrole Source #
The type of cryptographic verification key, for each key role.
Instances
IsString (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||
IsString (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> VerificationKey ByronKeyLegacy Source # | |||||
IsString (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey KesKey Source # | |||||
IsString (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey VrfKey Source # | |||||
IsString (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeColdExtendedKey Source # | |||||
IsString (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeColdKey Source # | |||||
IsString (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeHotExtendedKey Source # | |||||
IsString (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeHotKey Source # | |||||
IsString (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey DRepExtendedKey Source # | |||||
IsString (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateExtendedKey Source # | |||||
IsString (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateKey Source # | |||||
IsString (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisExtendedKey Source # | |||||
IsString (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisUTxOKey Source # | |||||
IsString (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey PaymentExtendedKey Source # | |||||
IsString (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakeExtendedKey Source # | |||||
IsString (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakePoolExtendedKey Source # | |||||
IsString (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakePoolKey Source # | |||||
Show (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> VerificationKey ByronKeyLegacy -> ShowS Source # show :: VerificationKey ByronKeyLegacy -> String Source # showList :: [VerificationKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeColdExtendedKey -> ShowS Source # show :: VerificationKey CommitteeColdExtendedKey -> String Source # showList :: [VerificationKey CommitteeColdExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeColdKey -> ShowS Source # show :: VerificationKey CommitteeColdKey -> String Source # showList :: [VerificationKey CommitteeColdKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeHotExtendedKey -> ShowS Source # show :: VerificationKey CommitteeHotExtendedKey -> String Source # showList :: [VerificationKey CommitteeHotExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeHotKey -> ShowS Source # show :: VerificationKey CommitteeHotKey -> String Source # showList :: [VerificationKey CommitteeHotKey] -> ShowS Source # | |||||
Show (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey DRepExtendedKey -> ShowS Source # show :: VerificationKey DRepExtendedKey -> String Source # showList :: [VerificationKey DRepExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS Source # show :: VerificationKey GenesisDelegateExtendedKey -> String Source # showList :: [VerificationKey GenesisDelegateExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisDelegateKey -> ShowS Source # show :: VerificationKey GenesisDelegateKey -> String Source # showList :: [VerificationKey GenesisDelegateKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisExtendedKey -> ShowS Source # show :: VerificationKey GenesisExtendedKey -> String Source # showList :: [VerificationKey GenesisExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisKey -> ShowS Source # show :: VerificationKey GenesisKey -> String Source # showList :: [VerificationKey GenesisKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS Source # show :: VerificationKey GenesisUTxOKey -> String Source # showList :: [VerificationKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS Source # show :: VerificationKey PaymentExtendedKey -> String Source # showList :: [VerificationKey PaymentExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentKey -> ShowS Source # show :: VerificationKey PaymentKey -> String Source # showList :: [VerificationKey PaymentKey] -> ShowS Source # | |||||
Show (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS Source # show :: VerificationKey StakeExtendedKey -> String Source # showList :: [VerificationKey StakeExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakePoolExtendedKey -> ShowS Source # show :: VerificationKey StakePoolExtendedKey -> String Source # showList :: [VerificationKey StakePoolExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS Source # show :: VerificationKey StakePoolKey -> String Source # showList :: [VerificationKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (VerificationKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (VerificationKey a) -> AsType (VerificationKey a) Source # | |||||
SerialiseAsCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: VerificationKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey ByronKey) -> ByteString -> Either DecoderError (VerificationKey ByronKey) Source # | |||||
SerialiseAsCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey KesKey) -> ByteString -> Either DecoderError (VerificationKey KesKey) Source # | |||||
SerialiseAsCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey VrfKey) -> ByteString -> Either DecoderError (VerificationKey VrfKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotKey) Source # | |||||
SerialiseAsCBOR (VerificationKey DRepExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey DRepKey) -> ByteString -> Either DecoderError (VerificationKey DRepKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey StakeExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey StakeKey) -> ByteString -> Either DecoderError (VerificationKey StakeKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakePoolExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey KesKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey KesKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey VrfKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey VrfKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey DRepExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey DRepExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey DRepKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey DRepKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakePoolKey) -> [Text] | |||||
SerialiseAsRawBytes (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) Source # | |||||
SerialiseAsRawBytes (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
SerialiseAsRawBytes (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey DRepExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey PaymentKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakeExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakeKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey StakePoolKey) Source # | |||||
HasTextEnvelope (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (VerificationKey ByronKeyLegacy) Source # | |||||
HasTextEnvelope (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
HasTextEnvelope (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeColdKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeHotKey) Source # | |||||
HasTextEnvelope (VerificationKey DRepExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisDelegateKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey GenesisUTxOKey) Source # | |||||
HasTextEnvelope (VerificationKey PaymentExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey StakeExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey StakePoolExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey StakePoolKey) Source # | |||||
FromCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (VerificationKey ByronKeyLegacy) Source # label :: Proxy (VerificationKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdExtendedKey) Source # label :: Proxy (VerificationKey CommitteeColdExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdKey) Source # label :: Proxy (VerificationKey CommitteeColdKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotExtendedKey) Source # label :: Proxy (VerificationKey CommitteeHotExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotKey) Source # label :: Proxy (VerificationKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey DRepExtendedKey) Source # label :: Proxy (VerificationKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateExtendedKey) Source # label :: Proxy (VerificationKey GenesisDelegateExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateKey) Source # label :: Proxy (VerificationKey GenesisDelegateKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisExtendedKey) Source # label :: Proxy (VerificationKey GenesisExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisKey) Source # label :: Proxy (VerificationKey GenesisKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisUTxOKey) Source # label :: Proxy (VerificationKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentExtendedKey) Source # label :: Proxy (VerificationKey PaymentExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentKey) Source # label :: Proxy (VerificationKey PaymentKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakeExtendedKey) Source # label :: Proxy (VerificationKey StakeExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolExtendedKey) Source # label :: Proxy (VerificationKey StakePoolExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolKey) Source # label :: Proxy (VerificationKey StakePoolKey) -> Text Source # | |||||
ToCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: VerificationKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size Source # | |||||
ToCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotKey] -> Size Source # | |||||
ToCBOR (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey DRepExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisUTxOKey] -> Size Source # | |||||
ToCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolKey] -> Size Source # | |||||
Eq (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # (/=) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # | |||||
Eq (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # (/=) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # | |||||
Eq (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # (/=) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # | |||||
Eq (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # (/=) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # | |||||
Eq (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Eq (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey CommitteeColdKey -> VerificationKey CommitteeColdKey -> Bool Source # (/=) :: VerificationKey CommitteeColdKey -> VerificationKey CommitteeColdKey -> Bool Source # | |||||
Eq (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Eq (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey CommitteeHotKey -> VerificationKey CommitteeHotKey -> Bool Source # (/=) :: VerificationKey CommitteeHotKey -> VerificationKey CommitteeHotKey -> Bool Source # | |||||
Eq (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey DRepExtendedKey -> VerificationKey DRepExtendedKey -> Bool Source # (/=) :: VerificationKey DRepExtendedKey -> VerificationKey DRepExtendedKey -> Bool Source # | |||||
Eq (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # (/=) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # | |||||
Eq (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Eq (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool Source # (/=) :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool Source # | |||||
Eq (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey -> Bool Source # (/=) :: VerificationKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey -> Bool Source # | |||||
Eq (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # (/=) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # | |||||
Eq (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # (/=) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # | |||||
Eq (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # (/=) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # | |||||
Eq (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # (/=) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # | |||||
newtype VerificationKey ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype VerificationKey ByronKeyLegacy Source # | |||||
newtype VerificationKey KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype VerificationKey VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype VerificationKey CommitteeColdExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeHotExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakePoolExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
data AsType (VerificationKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class |
data family SigningKey keyrole Source #
The type of cryptographic signing key, for each key role.
Instances
IsString (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> SigningKey ByronKey Source # | |||||
IsString (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||
IsString (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey KesKey Source # | |||||
IsString (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey VrfKey Source # | |||||
IsString (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeColdExtendedKey Source # | |||||
IsString (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeColdKey Source # | |||||
IsString (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeHotExtendedKey Source # | |||||
IsString (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey DRepKey Source # | |||||
IsString (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisDelegateExtendedKey Source # | |||||
IsString (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisDelegateKey Source # | |||||
IsString (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisExtendedKey Source # | |||||
IsString (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisKey Source # | |||||
IsString (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentExtendedKey Source # | |||||
IsString (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentKey Source # | |||||
IsString (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeExtendedKey Source # | |||||
IsString (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeKey Source # | |||||
IsString (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakePoolExtendedKey Source # | |||||
IsString (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
Show (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> SigningKey ByronKeyLegacy -> ShowS Source # show :: SigningKey ByronKeyLegacy -> String Source # showList :: [SigningKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeColdExtendedKey -> ShowS Source # show :: SigningKey CommitteeColdExtendedKey -> String Source # showList :: [SigningKey CommitteeColdExtendedKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeColdKey -> ShowS Source # show :: SigningKey CommitteeColdKey -> String Source # showList :: [SigningKey CommitteeColdKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeHotExtendedKey -> ShowS Source # show :: SigningKey CommitteeHotExtendedKey -> String Source # showList :: [SigningKey CommitteeHotExtendedKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeHotKey -> ShowS Source # show :: SigningKey CommitteeHotKey -> String Source # showList :: [SigningKey CommitteeHotKey] -> ShowS Source # | |||||
Show (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey DRepExtendedKey -> ShowS Source # show :: SigningKey DRepExtendedKey -> String Source # showList :: [SigningKey DRepExtendedKey] -> ShowS Source # | |||||
Show (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisDelegateExtendedKey -> ShowS Source # show :: SigningKey GenesisDelegateExtendedKey -> String Source # showList :: [SigningKey GenesisDelegateExtendedKey] -> ShowS Source # | |||||
Show (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS Source # show :: SigningKey GenesisDelegateKey -> String Source # showList :: [SigningKey GenesisDelegateKey] -> ShowS Source # | |||||
Show (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS Source # show :: SigningKey GenesisExtendedKey -> String Source # showList :: [SigningKey GenesisExtendedKey] -> ShowS Source # | |||||
Show (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisKey -> ShowS Source # show :: SigningKey GenesisKey -> String Source # showList :: [SigningKey GenesisKey] -> ShowS Source # | |||||
Show (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS Source # show :: SigningKey GenesisUTxOKey -> String Source # showList :: [SigningKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS Source # show :: SigningKey PaymentExtendedKey -> String Source # showList :: [SigningKey PaymentExtendedKey] -> ShowS Source # | |||||
Show (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentKey -> ShowS Source # show :: SigningKey PaymentKey -> String Source # showList :: [SigningKey PaymentKey] -> ShowS Source # | |||||
Show (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS Source # show :: SigningKey StakeExtendedKey -> String Source # showList :: [SigningKey StakeExtendedKey] -> ShowS Source # | |||||
Show (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakePoolExtendedKey -> ShowS Source # show :: SigningKey StakePoolExtendedKey -> String Source # showList :: [SigningKey StakePoolExtendedKey] -> ShowS Source # | |||||
Show (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakePoolKey -> ShowS Source # show :: SigningKey StakePoolKey -> String Source # showList :: [SigningKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (SigningKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (SigningKey a) -> AsType (SigningKey a) Source # | |||||
SerialiseAsCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKey) -> ByteString -> Either DecoderError (SigningKey ByronKey) Source # | |||||
SerialiseAsCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKeyLegacy) -> ByteString -> Either DecoderError (SigningKey ByronKeyLegacy) Source # | |||||
SerialiseAsCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey KesKey) -> ByteString -> Either DecoderError (SigningKey KesKey) Source # | |||||
SerialiseAsCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey VrfKey) -> ByteString -> Either DecoderError (SigningKey VrfKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey DRepKey) -> ByteString -> Either DecoderError (SigningKey DRepKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisKey) -> ByteString -> Either DecoderError (SigningKey GenesisKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey) -> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey) Source # | |||||
SerialiseAsCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey PaymentKey) -> ByteString -> Either DecoderError (SigningKey PaymentKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakeKey) -> ByteString -> Either DecoderError (SigningKey StakeKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakePoolExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakePoolKey) -> ByteString -> Either DecoderError (SigningKey StakePoolKey) Source # | |||||
SerialiseAsBech32 (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey KesKey -> Text bech32PrefixesPermitted :: AsType (SigningKey KesKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey VrfKey -> Text bech32PrefixesPermitted :: AsType (SigningKey VrfKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeColdExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeHotExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey DRepExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey DRepExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey DRepKey -> Text bech32PrefixesPermitted :: AsType (SigningKey DRepKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakePoolExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakePoolExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakePoolKey) -> [Text] | |||||
SerialiseAsRawBytes (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (SigningKey ByronKeyLegacy) Source # | |||||
SerialiseAsRawBytes (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey KesKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey KesKey) Source # | |||||
SerialiseAsRawBytes (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey VrfKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotKey) Source # | |||||
SerialiseAsRawBytes (SigningKey DRepExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: SigningKey DRepKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey DRepKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey DRepKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey GenesisUTxOKey) Source # | |||||
SerialiseAsRawBytes (SigningKey PaymentExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey StakeExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey StakePoolExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey KesKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey KesKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey VrfKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey VrfKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey CommitteeColdExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeColdKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeHotExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods textEnvelopeType :: AsType (SigningKey DRepKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey DRepKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisDelegateKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey PaymentExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey StakeExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey StakePoolExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (SigningKey ByronKeyLegacy) Source # label :: Proxy (SigningKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdExtendedKey) Source # label :: Proxy (SigningKey CommitteeColdExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdKey) Source # label :: Proxy (SigningKey CommitteeColdKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotExtendedKey) Source # label :: Proxy (SigningKey CommitteeHotExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotKey) Source # label :: Proxy (SigningKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey DRepExtendedKey) Source # label :: Proxy (SigningKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateExtendedKey) Source # label :: Proxy (SigningKey GenesisDelegateExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateKey) Source # label :: Proxy (SigningKey GenesisDelegateKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisExtendedKey) Source # label :: Proxy (SigningKey GenesisExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisKey) Source # label :: Proxy (SigningKey GenesisKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisUTxOKey) Source # label :: Proxy (SigningKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentExtendedKey) Source # label :: Proxy (SigningKey PaymentExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentKey) Source # label :: Proxy (SigningKey PaymentKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakeExtendedKey) Source # label :: Proxy (SigningKey StakeExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolExtendedKey) Source # label :: Proxy (SigningKey StakePoolExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolKey) Source # label :: Proxy (SigningKey StakePoolKey) -> Text Source # | |||||
ToCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: SigningKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size Source # | |||||
ToCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotKey] -> Size Source # | |||||
ToCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey DRepExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisUTxOKey] -> Size Source # | |||||
ToCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size Source # | |||||
ToCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolKey] -> Size Source # | |||||
newtype SigningKey ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype SigningKey ByronKeyLegacy Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype SigningKey KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype SigningKey VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype SigningKey CommitteeColdExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeHotExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakePoolExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
data AsType (SigningKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class |
data AllegraEra Source #
A type used as a tag to distinguish the Allegra era.
Instances
IsAllegraBasedEra AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsShelleyBasedEra AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy AllegraEra -> AsType AllegraEra Source # | |||||
data AsType AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data CardanoEra era where Source #
This GADT provides a value-level representation of all the Cardano eras. This enables pattern matching on the era to allow them to be treated in a non-uniform way.
This can be used in combination with the IsCardanoEra
class to get access
to this value.
In combination this can often enable code that handles all eras, and does so uniformly where possible, and non-uniformly where necessary.
Constructors
ByronEra :: CardanoEra ByronEra | |
ShelleyEra :: CardanoEra ShelleyEra | |
AllegraEra :: CardanoEra AllegraEra | |
MaryEra :: CardanoEra MaryEra | |
AlonzoEra :: CardanoEra AlonzoEra | |
BabbageEra :: CardanoEra BabbageEra | |
ConwayEra :: CardanoEra ConwayEra |
Instances
Eon CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods inEonForEra :: a -> (CardanoEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods toCardanoEra :: CardanoEra era -> CardanoEra era Source # | |
TestEquality CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods testEquality :: CardanoEra a -> CardanoEra b -> Maybe (a :~: b) Source # | |
Convert AllegraEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods convert :: AllegraEraOnwards era -> CardanoEra era Source # | |
Convert AlonzoEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods convert :: AlonzoEraOnwards era -> CardanoEra era Source # | |
Convert BabbageEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> CardanoEra era Source # | |
Convert ByronToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods convert :: ByronToAlonzoEra era -> CardanoEra era Source # | |
Convert ConwayEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> CardanoEra era Source # | |
Convert MaryEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods convert :: MaryEraOnwards era -> CardanoEra era Source # | |
Convert ShelleyBasedEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods convert :: ShelleyBasedEra era -> CardanoEra era Source # | |
Convert ShelleyEraOnly CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods convert :: ShelleyEraOnly era -> CardanoEra era Source # | |
Convert ShelleyToAllegraEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods convert :: ShelleyToAllegraEra era -> CardanoEra era Source # | |
Convert ShelleyToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods convert :: ShelleyToAlonzoEra era -> CardanoEra era Source # | |
Convert ShelleyToBabbageEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods convert :: ShelleyToBabbageEra era -> CardanoEra era Source # | |
Convert ShelleyToMaryEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods convert :: ShelleyToMaryEra era -> CardanoEra era Source # | |
Convert Era CardanoEra Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> CardanoEra era Source # | |
ToJSON (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods toJSON :: CardanoEra era -> Value toEncoding :: CardanoEra era -> Encoding toJSONList :: [CardanoEra era] -> Value toEncodingList :: [CardanoEra era] -> Encoding omitField :: CardanoEra era -> Bool | |
Show (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
Eq (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods (==) :: CardanoEra era -> CardanoEra era -> Bool Source # (/=) :: CardanoEra era -> CardanoEra era -> Bool Source # | |
Ord (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods compare :: CardanoEra era -> CardanoEra era -> Ordering Source # (<) :: CardanoEra era -> CardanoEra era -> Bool Source # (<=) :: CardanoEra era -> CardanoEra era -> Bool Source # (>) :: CardanoEra era -> CardanoEra era -> Bool Source # (>=) :: CardanoEra era -> CardanoEra era -> Bool Source # max :: CardanoEra era -> CardanoEra era -> CardanoEra era Source # min :: CardanoEra era -> CardanoEra era -> CardanoEra era Source # | |
Pretty (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core |
hashScript :: Script lang -> ScriptHash Source #
data Script lang where Source #
A script in a particular language.
See also ScriptInAnyLang
for a script in any of the known languages.
See also ScriptInEra
for a script in a language that is available within
a particular era.
Note that some but not all scripts have an external JSON syntax, hence this
type has no JSON serialisation instances. The SimpleScript
family of
languages do have a JSON syntax and thus have ToJSON
/FromJSON
instances.
Constructors
SimpleScript :: !SimpleScript -> Script SimpleScript' | |
PlutusScript :: forall lang. IsPlutusScriptLanguage lang => !(PlutusScriptVersion lang) -> !(PlutusScript lang) -> Script lang |
Instances
Show (Script lang) Source # | |||||
HasTypeProxy lang => HasTypeProxy (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
| |||||
IsScriptLanguage lang => SerialiseAsCBOR (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToCBOR :: Script lang -> ByteString Source # deserialiseFromCBOR :: AsType (Script lang) -> ByteString -> Either DecoderError (Script lang) Source # | |||||
IsScriptLanguage lang => HasTextEnvelope (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods textEnvelopeType :: AsType (Script lang) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Script lang -> TextEnvelopeDescr Source # | |||||
Eq (Script lang) Source # | |||||
data AsType (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script |
Instances
FromJSON Value Source # | |
Defined in Cardano.Api.Internal.Value | |
ToJSON Value Source # | |
Defined in Cardano.Api.Internal.Value Methods toEncoding :: Value -> Encoding toJSONList :: [Value] -> Value toEncodingList :: [Value] -> Encoding | |
Monoid Value Source # | |
Semigroup Value Source # | |
IsList Value Source # | |
Show Value Source # | |
Eq Value Source # | |
type Item Value Source # | |
Defined in Cardano.Api.Internal.Value |
A type used as a tag to distinguish the Byron era.
Instances
IsCardanoEra ByronEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy ByronEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
data AsType ByronEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
newtype ScriptHash Source #
We have this type separate from the Hash
type to avoid the script
hash type being parametrised by the era. The representation is era
independent, and there are many places where we want to use a script
hash where we don't want things to be era-parametrised.
Constructors
ScriptHash ScriptHash |
Instances
FromJSON ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToJSON ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toJSON :: ScriptHash -> Value toEncoding :: ScriptHash -> Encoding toJSONList :: [ScriptHash] -> Value toEncodingList :: [ScriptHash] -> Encoding omitField :: ScriptHash -> Bool | |||||
IsString ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods fromString :: String -> ScriptHash Source # | |||||
Show ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasTypeProxy ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy ScriptHash -> AsType ScriptHash Source # | |||||
SerialiseAsRawBytes ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
Eq ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptHash -> ScriptHash -> Bool Source # (/=) :: ScriptHash -> ScriptHash -> Bool Source # | |||||
Ord ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods compare :: ScriptHash -> ScriptHash -> Ordering Source # (<) :: ScriptHash -> ScriptHash -> Bool Source # (<=) :: ScriptHash -> ScriptHash -> Bool Source # (>) :: ScriptHash -> ScriptHash -> Bool Source # (>=) :: ScriptHash -> ScriptHash -> Bool Source # max :: ScriptHash -> ScriptHash -> ScriptHash Source # min :: ScriptHash -> ScriptHash -> ScriptHash Source # | |||||
data AsType ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script |
data Witness witctx era where Source #
Constructors
KeyWitness :: forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era | |
ScriptWitness :: forall witctx era. ScriptWitnessInCtx witctx -> ScriptWitness witctx era -> Witness witctx era |
Constructors
ReservesMIR | |
TreasuryMIR |
Instances
ToJSON MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toEncoding :: MIRPot -> Encoding toJSONList :: [MIRPot] -> Value toEncodingList :: [MIRPot] -> Encoding | |||||
Bounded MIRPot | |||||
Enum MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods succ :: MIRPot -> MIRPot Source # pred :: MIRPot -> MIRPot Source # toEnum :: Int -> MIRPot Source # fromEnum :: MIRPot -> Int Source # enumFrom :: MIRPot -> [MIRPot] Source # enumFromThen :: MIRPot -> MIRPot -> [MIRPot] Source # enumFromTo :: MIRPot -> MIRPot -> [MIRPot] Source # enumFromThenTo :: MIRPot -> MIRPot -> MIRPot -> [MIRPot] Source # | |||||
Generic MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Show MIRPot | |||||
DecCBOR MIRPot | |||||
EncCBOR MIRPot | |||||
NFData MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Eq MIRPot | |||||
Ord MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NoThunks MIRPot | |||||
type Rep MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep MIRPot = D1 ('MetaData "MIRPot" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-c94e4acbae2c451b736d7fa131482fce1d6ffd0e83dcc66450421e4714554169" 'False) (C1 ('MetaCons "ReservesMIR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TreasuryMIR" 'PrefixI 'False) (U1 :: Type -> Type)) |
MIRTarget specifies if funds from either the reserves or the treasury are to be handed out to a collection of reward accounts or instead transfered to the opposite pot.
Constructors
StakeAddressesMIR !(Map (Credential 'Staking) DeltaCoin) | |
SendToOppositePotMIR !Coin |
Instances
ToJSON MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toEncoding :: MIRTarget -> Encoding toJSONList :: [MIRTarget] -> Value toEncodingList :: [MIRTarget] -> Encoding | |||||
Generic MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Show MIRTarget | |||||
DecCBOR MIRTarget | |||||
EncCBOR MIRTarget | |||||
NFData MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Eq MIRTarget | |||||
Ord MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NoThunks MIRTarget | |||||
type Rep MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep MIRTarget = D1 ('MetaData "MIRTarget" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-c94e4acbae2c451b736d7fa131482fce1d6ffd0e83dcc66450421e4714554169" 'False) (C1 ('MetaCons "StakeAddressesMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking) DeltaCoin))) :+: C1 ('MetaCons "SendToOppositePotMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))) |
Instances
Data CostModel Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CostModel -> c CostModel Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CostModel Source # toConstr :: CostModel -> Constr Source # dataTypeOf :: CostModel -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CostModel) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CostModel) Source # gmapT :: (forall b. Data b => b -> b) -> CostModel -> CostModel Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CostModel -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CostModel -> r Source # gmapQ :: (forall d. Data d => d -> u) -> CostModel -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> CostModel -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CostModel -> m CostModel Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CostModel -> m CostModel Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CostModel -> m CostModel Source # | |
Show CostModel Source # | |
FromCBOR CostModel Source # | |
ToCBOR CostModel Source # | |
Eq CostModel Source # | |
A type used as a tag to distinguish the Alonzo era.
Instances
IsAllegraBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsAlonzoBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods | |||||
IsMaryBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |||||
IsShelleyBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasScriptLanguageInEra PlutusScriptV1 AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
data AsType AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data PlutusScript lang Source #
Plutus scripts.
Note that Plutus scripts have a binary serialisation but no JSON serialisation.
Instances
Show (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasTypeProxy lang => HasTypeProxy (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (PlutusScript lang) -> AsType (PlutusScript lang) Source # | |||||
HasTypeProxy lang => SerialiseAsCBOR (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToCBOR :: PlutusScript lang -> ByteString Source # deserialiseFromCBOR :: AsType (PlutusScript lang) -> ByteString -> Either DecoderError (PlutusScript lang) Source # | |||||
HasTypeProxy lang => SerialiseAsRawBytes (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToRawBytes :: PlutusScript lang -> ByteString Source # deserialiseFromRawBytes :: AsType (PlutusScript lang) -> ByteString -> Either SerialiseAsRawBytesError (PlutusScript lang) Source # | |||||
IsPlutusScriptLanguage lang => HasTextEnvelope (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods textEnvelopeType :: AsType (PlutusScript lang) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: PlutusScript lang -> TextEnvelopeDescr Source # | |||||
Eq (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (/=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # | |||||
Ord (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods compare :: PlutusScript lang -> PlutusScript lang -> Ordering Source # (<) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (<=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (>) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (>=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # max :: PlutusScript lang -> PlutusScript lang -> PlutusScript lang Source # min :: PlutusScript lang -> PlutusScript lang -> PlutusScript lang Source # | |||||
data AsType (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script |
data BabbageEra Source #
A type used as a tag to distinguish the Babbage era.
Instances
IsAllegraBasedEra BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsAlonzoBasedEra BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods | |||||
IsBabbageBasedEra BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods | |||||
IsMaryBasedEra BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |||||
IsShelleyBasedEra BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy BabbageEra -> AsType BabbageEra Source # | |||||
HasScriptLanguageInEra PlutusScriptV1 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV2 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToAlonzoScript PlutusScriptV1 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra BabbageEra) Source # | |||||
ToAlonzoScript PlutusScriptV2 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra BabbageEra) Source # | |||||
data AsType BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
A type used as a tag to distinguish the Conway era.
Instances
IsAllegraBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsAlonzoBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods | |||||
IsBabbageBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods | |||||
IsConwayBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods | |||||
IsMaryBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |||||
IsShelleyBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
IsEra ConwayEra Source # | |||||
HasTypeProxy ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasScriptLanguageInEra PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToAlonzoScript PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
ToAlonzoScript PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
ToAlonzoScript PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV3 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
data AsType ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
Instances
FromJSON TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxIx -> Encoding toJSONList :: [TxIx] -> Value toEncodingList :: [TxIx] -> Encoding | |
Enum TxIx Source # | |
Show TxIx Source # | |
Eq TxIx Source # | |
Ord TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn |
A type used as a tag to distinguish the Mary era.
Instances
IsAllegraBasedEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsMaryBasedEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |||||
IsShelleyBasedEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
data AsType MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data ShelleyEra Source #
A type used as a tag to distinguish the Shelley era.
Instances
IsShelleyBasedEra ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy ShelleyEra -> AsType ShelleyEra Source # | |||||
data AsType ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data CommitteeMembersState Source #
Constructors
CommitteeMembersState | |
Fields
|
Instances
ToJSON CommitteeMembersState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: CommitteeMembersState -> Value toEncoding :: CommitteeMembersState -> Encoding toJSONList :: [CommitteeMembersState] -> Value toEncodingList :: [CommitteeMembersState] -> Encoding | |||||
Generic CommitteeMembersState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
Methods from :: CommitteeMembersState -> Rep CommitteeMembersState x Source # to :: Rep CommitteeMembersState x -> CommitteeMembersState Source # | |||||
Show CommitteeMembersState | |||||
DecCBOR CommitteeMembersState | |||||
EncCBOR CommitteeMembersState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods encCBOR :: CommitteeMembersState -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CommitteeMembersState -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CommitteeMembersState] -> Size Source # | |||||
Eq CommitteeMembersState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods (==) :: CommitteeMembersState -> CommitteeMembersState -> Bool Source # (/=) :: CommitteeMembersState -> CommitteeMembersState -> Bool Source # | |||||
Ord CommitteeMembersState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods compare :: CommitteeMembersState -> CommitteeMembersState -> Ordering Source # (<) :: CommitteeMembersState -> CommitteeMembersState -> Bool Source # (<=) :: CommitteeMembersState -> CommitteeMembersState -> Bool Source # (>) :: CommitteeMembersState -> CommitteeMembersState -> Bool Source # (>=) :: CommitteeMembersState -> CommitteeMembersState -> Bool Source # max :: CommitteeMembersState -> CommitteeMembersState -> CommitteeMembersState Source # min :: CommitteeMembersState -> CommitteeMembersState -> CommitteeMembersState Source # | |||||
type Rep CommitteeMembersState | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState type Rep CommitteeMembersState = D1 ('MetaData "CommitteeMembersState" "Cardano.Ledger.Api.State.Query.CommitteeMembersState" "cardano-ledger-api-1.11.0.0-9852118f7dfe14ab1340be707d67c9317fb07912c1725cb4a7204d287e446e2f" 'False) (C1 ('MetaCons "CommitteeMembersState" 'PrefixI 'True) (S1 ('MetaSel ('Just "csCommittee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'ColdCommitteeRole) CommitteeMemberState)) :*: (S1 ('MetaSel ('Just "csThreshold") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UnitInterval)) :*: S1 ('MetaSel ('Just "csEpochNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo)))) |
data MemberStatus Source #
Constructors
Active | |
Expired | |
Unrecognized | This can happen when a hot credential for an unknown cold credential exists. Such Committee member will be either removed from the state at the next epoch boundary or enacted as a new member. |
Instances
ToJSON MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods toJSON :: MemberStatus -> Value toEncoding :: MemberStatus -> Encoding toJSONList :: [MemberStatus] -> Value toEncodingList :: [MemberStatus] -> Encoding omitField :: MemberStatus -> Bool | |||||
Bounded MemberStatus | |||||
Enum MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods succ :: MemberStatus -> MemberStatus Source # pred :: MemberStatus -> MemberStatus Source # toEnum :: Int -> MemberStatus Source # fromEnum :: MemberStatus -> Int Source # enumFrom :: MemberStatus -> [MemberStatus] Source # enumFromThen :: MemberStatus -> MemberStatus -> [MemberStatus] Source # enumFromTo :: MemberStatus -> MemberStatus -> [MemberStatus] Source # enumFromThenTo :: MemberStatus -> MemberStatus -> MemberStatus -> [MemberStatus] Source # | |||||
Generic MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Associated Types
Methods from :: MemberStatus -> Rep MemberStatus x Source # to :: Rep MemberStatus x -> MemberStatus Source # | |||||
Show MemberStatus | |||||
DecCBOR MemberStatus | |||||
EncCBOR MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods encCBOR :: MemberStatus -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy MemberStatus -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MemberStatus] -> Size Source # | |||||
Eq MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods (==) :: MemberStatus -> MemberStatus -> Bool Source # (/=) :: MemberStatus -> MemberStatus -> Bool Source # | |||||
Ord MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState Methods compare :: MemberStatus -> MemberStatus -> Ordering Source # (<) :: MemberStatus -> MemberStatus -> Bool Source # (<=) :: MemberStatus -> MemberStatus -> Bool Source # (>) :: MemberStatus -> MemberStatus -> Bool Source # (>=) :: MemberStatus -> MemberStatus -> Bool Source # max :: MemberStatus -> MemberStatus -> MemberStatus Source # min :: MemberStatus -> MemberStatus -> MemberStatus Source # | |||||
type Rep MemberStatus | |||||
Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState type Rep MemberStatus = D1 ('MetaData "MemberStatus" "Cardano.Ledger.Api.State.Query.CommitteeMembersState" "cardano-ledger-api-1.11.0.0-9852118f7dfe14ab1340be707d67c9317fb07912c1725cb4a7204d287e446e2f" 'False) (C1 ('MetaCons "Active" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Expired" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unrecognized" 'PrefixI 'False) (U1 :: Type -> Type))) |
queryAccountState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch AccountState)) Source #
queryCommitteeMembersState :: ConwayEraOnwards era -> Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch CommitteeMembersState)) Source #
Returns info about committee members filtered by: cold credentials, hot credentials and statuses. If empty sets are passed as filters, then no filtering is done.
queryConstitution :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Constitution (ShelleyLedgerEra era)))) Source #
queryConstitutionHash :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SafeHash AnchorData))) Source #
Arguments
:: ConwayEraOnwards era | |
-> Set (Credential 'DRepRole) | An empty credentials set means that states for all DReps will be returned |
-> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Credential 'DRepRole) DRepState))) |
queryFuturePParams :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))) Source #
queryGovState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GovState (ShelleyLedgerEra era)))) Source #
queryProposals :: ConwayEraOnwards era -> Set GovActionId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))) Source #
queryRatifyState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (RatifyState (ShelleyLedgerEra era)))) Source #
queryStakePoolDefaultVote :: ConwayEraOnwards era -> KeyHash 'StakePool -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch DefaultVote)) Source #
Ann
is the prettyprinter annotation for cardano-api and cardano-cli to enable the printing
of colored output. This is a type alias for AnsiStyle.
newtype EpochSlots Source #
The number of slots per epoch.
Constructors
EpochSlots | |
Fields |
Instances
Data EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpochSlots -> c EpochSlots Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpochSlots Source # toConstr :: EpochSlots -> Constr Source # dataTypeOf :: EpochSlots -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpochSlots) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpochSlots) Source # gmapT :: (forall b. Data b => b -> b) -> EpochSlots -> EpochSlots Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpochSlots -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpochSlots -> r Source # gmapQ :: (forall d. Data d => d -> u) -> EpochSlots -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpochSlots -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source # | |||||
Generic EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Associated Types
| |||||
Read EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
Show EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
FromCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
ToCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods toCBOR :: EpochSlots -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochSlots -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochSlots] -> Size Source # | |||||
DecCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
EncCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods encCBOR :: EpochSlots -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy EpochSlots -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [EpochSlots] -> Size Source # | |||||
Buildable EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods build :: EpochSlots -> Builder | |||||
Eq EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods (==) :: EpochSlots -> EpochSlots -> Bool Source # (/=) :: EpochSlots -> EpochSlots -> Bool Source # | |||||
Ord EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods compare :: EpochSlots -> EpochSlots -> Ordering Source # (<) :: EpochSlots -> EpochSlots -> Bool Source # (<=) :: EpochSlots -> EpochSlots -> Bool Source # (>) :: EpochSlots -> EpochSlots -> Bool Source # (>=) :: EpochSlots -> EpochSlots -> Bool Source # max :: EpochSlots -> EpochSlots -> EpochSlots Source # min :: EpochSlots -> EpochSlots -> EpochSlots Source # | |||||
NoThunks EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods noThunks :: Context -> EpochSlots -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> EpochSlots -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy EpochSlots -> String # | |||||
type Rep EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots type Rep EpochSlots = D1 ('MetaData "EpochSlots" "Cardano.Chain.Slotting.EpochSlots" "cardano-ledger-byron-1.1.0.0-7fb551a04b7ebd202180a636c363fd4c69d431c37908920ba820fedd2c0d0ade" 'True) (C1 ('MetaCons "EpochSlots" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochSlots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
Methods
prettyError :: e -> Doc ann Source #
Instances
Error IOException Source # | |
Defined in Cardano.Api.Internal.Error Methods prettyError :: IOException -> Doc ann Source # | |
Error AnchorDataFromCertificateError Source # | |
Defined in Cardano.Api.Internal.Certificate Methods prettyError :: AnchorDataFromCertificateError -> Doc ann Source # | |
Error InputDecodeError Source # | |
Defined in Cardano.Api.Internal.DeserialiseAnyOf Methods prettyError :: InputDecodeError -> Doc ann Source # | |
Error ErrorAsException Source # | |
Defined in Cardano.Api.Internal.Error Methods prettyError :: ErrorAsException -> Doc ann Source # | |
Error ScriptExecutionError Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: ScriptExecutionError -> Doc ann Source # | |
Error MnemonicToSigningKeyError Source # | |
Defined in Cardano.Api.Internal.Keys.Mnemonics Methods prettyError :: MnemonicToSigningKeyError -> Doc ann Source # | |
Error FoldBlocksError Source # | |
Defined in Cardano.Api.Internal.LedgerState Methods prettyError :: FoldBlocksError -> Doc ann Source # | |
Error GenesisConfigError Source # | |
Defined in Cardano.Api.Internal.LedgerState Methods prettyError :: GenesisConfigError -> Doc ann Source # | |
Error InitialLedgerStateError Source # | |
Defined in Cardano.Api.Internal.LedgerState Methods prettyError :: InitialLedgerStateError -> Doc ann Source # | |
Error LeadershipError Source # | |
Defined in Cardano.Api.Internal.LedgerState Methods prettyError :: LeadershipError -> Doc ann Source # | |
Error LedgerStateError Source # | |
Defined in Cardano.Api.Internal.LedgerState Methods prettyError :: LedgerStateError -> Doc ann Source # | |
Error OperationalCertIssueError Source # | |
Defined in Cardano.Api.Internal.OperationalCertificate Methods prettyError :: OperationalCertIssueError -> Doc ann Source # | |
Error ProtocolParametersConversionError Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods prettyError :: ProtocolParametersConversionError -> Doc ann Source # | |
Error ProtocolParametersError Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods prettyError :: ProtocolParametersError -> Doc ann Source # | |
Error ScriptDataJsonBytesError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataJsonBytesError -> Doc ann Source # | |
Error ScriptDataJsonError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataJsonError -> Doc ann Source # | |
Error ScriptDataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataJsonSchemaError -> Doc ann Source # | |
Error ScriptDataRangeError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataRangeError -> Doc ann Source # | |
Error Bech32DecodeError Source # | |
Defined in Cardano.Api.Internal.SerialiseBech32 Methods prettyError :: Bech32DecodeError -> Doc ann Source # | |
Error JsonDecodeError Source # | |
Defined in Cardano.Api.Internal.SerialiseJSON Methods prettyError :: JsonDecodeError -> Doc ann Source # | |
Error TextEnvelopeCddlError Source # | |
Defined in Cardano.Api.Internal.SerialiseLedgerCddl Methods prettyError :: TextEnvelopeCddlError -> Doc ann Source # | |
Error RawBytesHexError Source # | |
Defined in Cardano.Api.Internal.SerialiseRaw Methods prettyError :: RawBytesHexError -> Doc ann Source # | |
Error TextEnvelopeError Source # | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Methods prettyError :: TextEnvelopeError -> Doc ann Source # | |
Error StakePoolMetadataValidationError Source # | |
Defined in Cardano.Api.Internal.StakePoolMetadata Methods prettyError :: StakePoolMetadataValidationError -> Doc ann Source # | |
Error TxBodyError Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods prettyError :: TxBodyError -> Doc ann Source # | |
Error TxOutputError Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods prettyError :: TxOutputError -> Doc ann Source # | |
Error TxMetadataJsonError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods prettyError :: TxMetadataJsonError -> Doc ann Source # | |
Error TxMetadataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods prettyError :: TxMetadataJsonSchemaError -> Doc ann Source # | |
Error TxMetadataRangeError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods prettyError :: TxMetadataRangeError -> Doc ann Source # | |
Error () Source # | |
Defined in Cardano.Api.Internal.Error Methods prettyError :: () -> Doc ann Source # | |
Error e => Error (FileError e) Source # | |
Defined in Cardano.Api.Internal.Error Methods prettyError :: FileError e -> Doc ann Source # | |
Error (AutoBalanceError era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: AutoBalanceError era -> Doc ann Source # | |
Error (TransactionValidityError era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: TransactionValidityError era -> Doc ann Source # | |
Error (TxBodyErrorAutoBalance era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: TxBodyErrorAutoBalance era -> Doc ann Source # | |
Error (TxFeeEstimationError era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: TxFeeEstimationError era -> Doc ann Source # |
data ProtocolParametersUpdate Source #
The representation of a change in the ProtocolParameters
.
Constructors
ProtocolParametersUpdate | |
Fields
|
Instances
Monoid ProtocolParametersUpdate Source # | |
Semigroup ProtocolParametersUpdate Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
Show ProtocolParametersUpdate Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromCBOR ProtocolParametersUpdate Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
ToCBOR ProtocolParametersUpdate Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toCBOR :: ProtocolParametersUpdate -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtocolParametersUpdate -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtocolParametersUpdate] -> Size Source # | |
Eq ProtocolParametersUpdate Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods (==) :: ProtocolParametersUpdate -> ProtocolParametersUpdate -> Bool Source # (/=) :: ProtocolParametersUpdate -> ProtocolParametersUpdate -> Bool Source # |
data ValidationMode Source #
How to do validation when applying a block to a ledger state.
Constructors
FullValidation | Do all validation implied by the ledger layer's |
QuickValidation | Only check that the previous hash from the block matches the head hash of the ledger state. |
The 0-based index of the block in the blockchain. BlockNo is <= SlotNo and is only equal at slot N if there is a block for every slot where N <= SlotNo.
Instances
FromJSON BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
ToJSON BlockNo | |||||
Defined in Cardano.Slotting.Block Methods toEncoding :: BlockNo -> Encoding toJSONList :: [BlockNo] -> Value toEncodingList :: [BlockNo] -> Encoding | |||||
Bounded BlockNo | |||||
Enum BlockNo | |||||
Defined in Cardano.Slotting.Block Methods succ :: BlockNo -> BlockNo Source # pred :: BlockNo -> BlockNo Source # toEnum :: Int -> BlockNo Source # fromEnum :: BlockNo -> Int Source # enumFrom :: BlockNo -> [BlockNo] Source # enumFromThen :: BlockNo -> BlockNo -> [BlockNo] Source # enumFromTo :: BlockNo -> BlockNo -> [BlockNo] Source # enumFromThenTo :: BlockNo -> BlockNo -> BlockNo -> [BlockNo] Source # | |||||
Generic BlockNo | |||||
Defined in Cardano.Slotting.Block Associated Types
| |||||
Num BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
Show BlockNo | |||||
FromCBOR BlockNo | |||||
ToCBOR BlockNo | |||||
DecCBOR BlockNo | |||||
EncCBOR BlockNo | |||||
NFData BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
Eq BlockNo | |||||
Ord BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
NoThunks BlockNo | |||||
ChainOrder BlockNo | |||||
Defined in Ouroboros.Consensus.Protocol.Abstract Associated Types
Methods preferCandidate :: ChainOrderConfig BlockNo -> BlockNo -> BlockNo -> Bool Source # | |||||
Condense BlockNo | |||||
Serialise BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
type Rep BlockNo | |||||
Defined in Cardano.Slotting.Block type Rep BlockNo = D1 ('MetaData "BlockNo" "Cardano.Slotting.Block" "cardano-slotting-0.2.0.0-1062762da5e24b3256026b7bf7ed7ea570deea61ae8ec963e4334bb658f0121b" 'True) (C1 ('MetaCons "BlockNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) | |||||
type ChainOrderConfig BlockNo | |||||
Defined in Ouroboros.Consensus.Protocol.Abstract |
An epoch, i.e. the number of the epoch.
Instances
FromJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
ToJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot Methods toEncoding :: EpochNo -> Encoding toJSONList :: [EpochNo] -> Value toEncodingList :: [EpochNo] -> Encoding | |||||
Enum EpochNo | |||||
Defined in Cardano.Slotting.Slot Methods succ :: EpochNo -> EpochNo Source # pred :: EpochNo -> EpochNo Source # toEnum :: Int -> EpochNo Source # fromEnum :: EpochNo -> Int Source # enumFrom :: EpochNo -> [EpochNo] Source # enumFromThen :: EpochNo -> EpochNo -> [EpochNo] Source # enumFromTo :: EpochNo -> EpochNo -> [EpochNo] Source # enumFromThenTo :: EpochNo -> EpochNo -> EpochNo -> [EpochNo] Source # | |||||
Generic EpochNo | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Show EpochNo | |||||
FromCBOR EpochNo | |||||
ToCBOR EpochNo | |||||
DecCBOR EpochNo | |||||
EncCBOR EpochNo | |||||
NFData EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
Eq EpochNo | |||||
Ord EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
NoThunks EpochNo | |||||
Condense EpochNo | |||||
Serialise |