cardano-api
Safe HaskellNone
LanguageHaskell2010

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

Documentation

class Pretty a where #

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann #

prettyList :: [a] -> Doc ann #

Instances

Instances details
Pretty Void 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty AnyCardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Methods

pretty :: AnyCardanoEra -> Doc ann #

prettyList :: [AnyCardanoEra] -> Doc ann #

Pretty TxOutInAnyEra Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Output

Methods

pretty :: TxOutInAnyEra -> Doc ann #

prettyList :: [TxOutInAnyEra] -> Doc ann #

Pretty TxIn Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

pretty :: TxIn -> Doc ann #

prettyList :: [TxIn] -> Doc ann #

Pretty Url Source # 
Instance details

Defined in Cardano.Api.Internal.Pretty

Methods

pretty :: Url -> Doc ann #

prettyList :: [Url] -> Doc ann #

Pretty Coin Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

Methods

pretty :: Coin -> Doc ann #

prettyList :: [Coin] -> Doc ann #

Pretty AssetName Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

Methods

pretty :: AssetName -> Doc ann #

prettyList :: [AssetName] -> Doc ann #

Pretty MultiAsset Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

Methods

pretty :: MultiAsset -> Doc ann #

prettyList :: [MultiAsset] -> Doc ann #

Pretty PolicyID Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

Methods

pretty :: PolicyID -> Doc ann #

prettyList :: [PolicyID] -> Doc ann #

Pretty Error Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Misc

Methods

pretty :: Error -> Doc ann #

prettyList :: [Error] -> Doc ann #

Pretty Ann 
Instance details

Defined in PlutusCore.Annotation

Methods

pretty :: Ann -> Doc ann #

prettyList :: [Ann] -> Doc ann #

Pretty SrcSpan 
Instance details

Defined in PlutusCore.Annotation

Methods

pretty :: SrcSpan -> Doc ann #

prettyList :: [SrcSpan] -> Doc ann #

Pretty SrcSpans 
Instance details

Defined in PlutusCore.Annotation

Methods

pretty :: SrcSpans -> Doc ann #

prettyList :: [SrcSpans] -> Doc ann #

Pretty BuiltinError 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

pretty :: BuiltinError -> Doc ann #

prettyList :: [BuiltinError] -> Doc ann #

Pretty UnliftingError 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

pretty :: UnliftingError -> Doc ann #

prettyList :: [UnliftingError] -> Doc ann #

Pretty UnliftingEvaluationError 
Instance details

Defined in PlutusCore.Builtin.Result

Pretty Data 
Instance details

Defined in PlutusCore.Data

Methods

pretty :: Data -> Doc ann #

prettyList :: [Data] -> Doc ann #

Pretty FreeVariableError 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Pretty Index 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

pretty :: Index -> Doc ann #

prettyList :: [Index] -> Doc ann #

Pretty DefaultFun 
Instance details

Defined in PlutusCore.Default.Builtins

Methods

pretty :: DefaultFun -> Doc ann #

prettyList :: [DefaultFun] -> Doc ann #

Pretty ParserError 
Instance details

Defined in PlutusCore.Error

Methods

pretty :: ParserError -> Doc ann #

prettyList :: [ParserError] -> Doc ann #

Pretty ParserErrorBundle 
Instance details

Defined in PlutusCore.Error

Pretty CkUserError 
Instance details

Defined in PlutusCore.Evaluation.Machine.Ck

Methods

pretty :: CkUserError -> Doc ann #

prettyList :: [CkUserError] -> Doc ann #

Pretty CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Pretty CostModelApplyWarn 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Pretty ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

pretty :: ExBudget -> Doc ann #

prettyList :: [ExBudget] -> Doc ann #

Pretty ExRestrictingBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Pretty ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

pretty :: ExCPU -> Doc ann #

prettyList :: [ExCPU] -> Doc ann #

Pretty ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

pretty :: ExMemory -> Doc ann #

prettyList :: [ExMemory] -> Doc ann #

Pretty Unique 
Instance details

Defined in PlutusCore.Name.Unique

Methods

pretty :: Unique -> Doc ann #

prettyList :: [Unique] -> Doc ann #

Pretty Version 
Instance details

Defined in PlutusCore.Version

Methods

pretty :: Version -> Doc ann #

prettyList :: [Version] -> Doc ann #

Pretty CountingSt 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

pretty :: CountingSt -> Doc ann #

prettyList :: [CountingSt] -> Doc ann #

Pretty RestrictingSt 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

pretty :: RestrictingSt -> Doc ann #

prettyList :: [RestrictingSt] -> Doc ann #

Pretty CekUserError 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

pretty :: CekUserError -> Doc ann #

prettyList :: [CekUserError] -> Doc ann #

Pretty DatatypeComponent 
Instance details

Defined in PlutusIR.Compiler.Provenance

Methods

pretty :: DatatypeComponent -> Doc ann #

prettyList :: [DatatypeComponent] -> Doc ann #

Pretty GeneratedKind 
Instance details

Defined in PlutusIR.Compiler.Provenance

Methods

pretty :: GeneratedKind -> Doc ann #

prettyList :: [GeneratedKind] -> Doc ann #

Pretty EvaluationError 
Instance details

Defined in PlutusLedgerApi.Common.Eval

Pretty MajorProtocolVersion 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

Pretty ScriptDecodeError 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Pretty PlutusLedgerLanguage 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Pretty Address 
Instance details

Defined in PlutusLedgerApi.V1.Address

Methods

pretty :: Address -> Doc ann #

prettyList :: [Address] -> Doc ann #

Pretty LedgerBytes 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Methods

pretty :: LedgerBytes -> Doc ann #

prettyList :: [LedgerBytes] -> Doc ann #

Pretty ScriptContext 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Methods

pretty :: ScriptContext -> Doc ann #

prettyList :: [ScriptContext] -> Doc ann #

Pretty ScriptPurpose 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Methods

pretty :: ScriptPurpose -> Doc ann #

prettyList :: [ScriptPurpose] -> Doc ann #

Pretty TxInInfo 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Methods

pretty :: TxInInfo -> Doc ann #

prettyList :: [TxInInfo] -> Doc ann #

Pretty TxInfo 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Methods

pretty :: TxInfo -> Doc ann #

prettyList :: [TxInfo] -> Doc ann #

Pretty Credential 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

pretty :: Credential -> Doc ann #

prettyList :: [Credential] -> Doc ann #

Pretty StakingCredential 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Pretty PubKeyHash

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Crypto

Methods

pretty :: PubKeyHash -> Doc ann #

prettyList :: [PubKeyHash] -> Doc ann #

Pretty DCert 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Methods

pretty :: DCert -> Doc ann #

prettyList :: [DCert] -> Doc ann #

Pretty Address 
Instance details

Defined in PlutusLedgerApi.V1.Data.Address

Methods

pretty :: Address -> Doc ann #

prettyList :: [Address] -> Doc ann #

Pretty ScriptContext 
Instance details

Defined in PlutusLedgerApi.V1.Data.Contexts

Methods

pretty :: ScriptContext -> Doc ann #

prettyList :: [ScriptContext] -> Doc ann #

Pretty ScriptPurpose 
Instance details

Defined in PlutusLedgerApi.V1.Data.Contexts

Methods

pretty :: ScriptPurpose -> Doc ann #

prettyList :: [ScriptPurpose] -> Doc ann #

Pretty TxInInfo 
Instance details

Defined in PlutusLedgerApi.V1.Data.Contexts

Methods

pretty :: TxInInfo -> Doc ann #

prettyList :: [TxInInfo] -> Doc ann #

Pretty TxInfo 
Instance details

Defined in PlutusLedgerApi.V1.Data.Contexts

Methods

pretty :: TxInfo -> Doc ann #

prettyList :: [TxInfo] -> Doc ann #

Pretty Credential 
Instance details

Defined in PlutusLedgerApi.V1.Data.Credential

Methods

pretty :: Credential -> Doc ann #

prettyList :: [Credential] -> Doc ann #

Pretty StakingCredential 
Instance details

Defined in PlutusLedgerApi.V1.Data.Credential

Pretty DCert 
Instance details

Defined in PlutusLedgerApi.V1.Data.DCert

Methods

pretty :: DCert -> Doc ann #

prettyList :: [DCert] -> Doc ann #

Pretty POSIXTime 
Instance details

Defined in PlutusLedgerApi.V1.Data.Time

Methods

pretty :: POSIXTime -> Doc ann #

prettyList :: [POSIXTime] -> Doc ann #

Pretty TxId

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Data.Tx

Methods

pretty :: TxId -> Doc ann #

prettyList :: [TxId] -> Doc ann #

Pretty TxOut 
Instance details

Defined in PlutusLedgerApi.V1.Data.Tx

Methods

pretty :: TxOut -> Doc ann #

prettyList :: [TxOut] -> Doc ann #

Pretty TxOutRef 
Instance details

Defined in PlutusLedgerApi.V1.Data.Tx

Methods

pretty :: TxOutRef -> Doc ann #

prettyList :: [TxOutRef] -> Doc ann #

Pretty AssetClass 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: AssetClass -> Doc ann #

prettyList :: [AssetClass] -> Doc ann #

Pretty CurrencySymbol

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: CurrencySymbol -> Doc ann #

prettyList :: [CurrencySymbol] -> Doc ann #

Pretty Lovelace 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: Lovelace -> Doc ann #

prettyList :: [Lovelace] -> Doc ann #

Pretty TokenName 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: TokenName -> Doc ann #

prettyList :: [TokenName] -> Doc ann #

Pretty Value 
Instance details

Defined in PlutusLedgerApi.V1.Data.Value

Methods

pretty :: Value -> Doc ann #

prettyList :: [Value] -> Doc ann #

Pretty Context 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: Context -> Doc ann #

prettyList :: [Context] -> Doc ann #

Pretty Datum 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: Datum -> Doc ann #

prettyList :: [Datum] -> Doc ann #

Pretty DatumHash

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: DatumHash -> Doc ann #

prettyList :: [DatumHash] -> Doc ann #

Pretty Redeemer 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: Redeemer -> Doc ann #

prettyList :: [Redeemer] -> Doc ann #

Pretty RedeemerHash

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: RedeemerHash -> Doc ann #

prettyList :: [RedeemerHash] -> Doc ann #

Pretty ScriptHash

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: ScriptHash -> Doc ann #

prettyList :: [ScriptHash] -> Doc ann #

Pretty POSIXTime 
Instance details

Defined in PlutusLedgerApi.V1.Time

Methods

pretty :: POSIXTime -> Doc ann #

prettyList :: [POSIXTime] -> Doc ann #

Pretty TxId

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Tx

Methods

pretty :: TxId -> Doc ann #

prettyList :: [TxId] -> Doc ann #

Pretty TxOut 
Instance details

Defined in PlutusLedgerApi.V1.Tx

Methods

pretty :: TxOut -> Doc ann #

prettyList :: [TxOut] -> Doc ann #

Pretty TxOutRef 
Instance details

Defined in PlutusLedgerApi.V1.Tx

Methods

pretty :: TxOutRef -> Doc ann #

prettyList :: [TxOutRef] -> Doc ann #

Pretty AssetClass 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: AssetClass -> Doc ann #

prettyList :: [AssetClass] -> Doc ann #

Pretty CurrencySymbol

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: CurrencySymbol -> Doc ann #

prettyList :: [CurrencySymbol] -> Doc ann #

Pretty Lovelace 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: Lovelace -> Doc ann #

prettyList :: [Lovelace] -> Doc ann #

Pretty TokenName 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: TokenName -> Doc ann #

prettyList :: [TokenName] -> Doc ann #

Pretty Value 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

pretty :: Value -> Doc ann #

prettyList :: [Value] -> Doc ann #

Pretty ScriptContext 
Instance details

Defined in PlutusLedgerApi.V2.Contexts

Methods

pretty :: ScriptContext -> Doc ann #

prettyList :: [ScriptContext] -> Doc ann #

Pretty TxInInfo 
Instance details

Defined in PlutusLedgerApi.V2.Contexts

Methods

pretty :: TxInInfo -> Doc ann #

prettyList :: [TxInInfo] -> Doc ann #

Pretty TxInfo 
Instance details

Defined in PlutusLedgerApi.V2.Contexts

Methods

pretty :: TxInfo -> Doc ann #

prettyList :: [TxInfo] -> Doc ann #

Pretty ScriptContext 
Instance details

Defined in PlutusLedgerApi.V2.Data.Contexts

Methods

pretty :: ScriptContext -> Doc ann #

prettyList :: [ScriptContext] -> Doc ann #

Pretty TxInInfo 
Instance details

Defined in PlutusLedgerApi.V2.Data.Contexts

Methods

pretty :: TxInInfo -> Doc ann #

prettyList :: [TxInInfo] -> Doc ann #

Pretty TxInfo 
Instance details

Defined in PlutusLedgerApi.V2.Data.Contexts

Methods

pretty :: TxInfo -> Doc ann #

prettyList :: [TxInfo] -> Doc ann #

Pretty OutputDatum 
Instance details

Defined in PlutusLedgerApi.V2.Data.Tx

Methods

pretty :: OutputDatum -> Doc ann #

prettyList :: [OutputDatum] -> Doc ann #

Pretty TxOut 
Instance details

Defined in PlutusLedgerApi.V2.Data.Tx

Methods

pretty :: TxOut -> Doc ann #

prettyList :: [TxOut] -> Doc ann #

Pretty OutputDatum 
Instance details

Defined in PlutusLedgerApi.V2.Tx

Methods

pretty :: OutputDatum -> Doc ann #

prettyList :: [OutputDatum] -> Doc ann #

Pretty TxOut 
Instance details

Defined in PlutusLedgerApi.V2.Tx

Methods

pretty :: TxOut -> Doc ann #

prettyList :: [TxOut] -> Doc ann #

Pretty ChangedParameters 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Pretty ColdCommitteeCredential 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Pretty Committee 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: Committee -> Doc ann #

prettyList :: [Committee] -> Doc ann #

Pretty Constitution 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: Constitution -> Doc ann #

prettyList :: [Constitution] -> Doc ann #

Pretty DRep 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: DRep -> Doc ann #

prettyList :: [DRep] -> Doc ann #

Pretty DRepCredential 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: DRepCredential -> Doc ann #

prettyList :: [DRepCredential] -> Doc ann #

Pretty Delegatee 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: Delegatee -> Doc ann #

prettyList :: [Delegatee] -> Doc ann #

Pretty GovernanceAction 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Pretty GovernanceActionId 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Pretty HotCommitteeCredential 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Pretty ProposalProcedure 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Pretty ProtocolVersion 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Pretty ScriptContext 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: ScriptContext -> Doc ann #

prettyList :: [ScriptContext] -> Doc ann #

Pretty ScriptInfo 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: ScriptInfo -> Doc ann #

prettyList :: [ScriptInfo] -> Doc ann #

Pretty ScriptPurpose 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: ScriptPurpose -> Doc ann #

prettyList :: [ScriptPurpose] -> Doc ann #

Pretty TxCert 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: TxCert -> Doc ann #

prettyList :: [TxCert] -> Doc ann #

Pretty TxInInfo 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: TxInInfo -> Doc ann #

prettyList :: [TxInInfo] -> Doc ann #

Pretty TxInfo 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: TxInfo -> Doc ann #

prettyList :: [TxInfo] -> Doc ann #

Pretty Vote 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: Vote -> Doc ann #

prettyList :: [Vote] -> Doc ann #

Pretty Voter 
Instance details

Defined in PlutusLedgerApi.V3.Contexts

Methods

pretty :: Voter -> Doc ann #

prettyList :: [Voter] -> Doc ann #

Pretty ChangedParameters 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Pretty ColdCommitteeCredential 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Pretty Committee 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: Committee -> Doc ann #

prettyList :: [Committee] -> Doc ann #

Pretty Constitution 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: Constitution -> Doc ann #

prettyList :: [Constitution] -> Doc ann #

Pretty DRep 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: DRep -> Doc ann #

prettyList :: [DRep] -> Doc ann #

Pretty DRepCredential 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: DRepCredential -> Doc ann #

prettyList :: [DRepCredential] -> Doc ann #

Pretty Delegatee 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: Delegatee -> Doc ann #

prettyList :: [Delegatee] -> Doc ann #

Pretty GovernanceAction 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Pretty GovernanceActionId 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Pretty HotCommitteeCredential 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Pretty ProposalProcedure 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Pretty ProtocolVersion 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Pretty ScriptContext 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: ScriptContext -> Doc ann #

prettyList :: [ScriptContext] -> Doc ann #

Pretty ScriptInfo 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: ScriptInfo -> Doc ann #

prettyList :: [ScriptInfo] -> Doc ann #

Pretty ScriptPurpose 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: ScriptPurpose -> Doc ann #

prettyList :: [ScriptPurpose] -> Doc ann #

Pretty TxCert 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: TxCert -> Doc ann #

prettyList :: [TxCert] -> Doc ann #

Pretty TxInInfo 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: TxInInfo -> Doc ann #

prettyList :: [TxInInfo] -> Doc ann #

Pretty TxInfo 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: TxInfo -> Doc ann #

prettyList :: [TxInfo] -> Doc ann #

Pretty Vote 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: Vote -> Doc ann #

prettyList :: [Vote] -> Doc ann #

Pretty Voter 
Instance details

Defined in PlutusLedgerApi.V3.Data.Contexts

Methods

pretty :: Voter -> Doc ann #

prettyList :: [Voter] -> Doc ann #

Pretty MintValue 
Instance details

Defined in PlutusLedgerApi.V3.Data.MintValue

Methods

pretty :: MintValue -> Doc ann #

prettyList :: [MintValue] -> Doc ann #

Pretty TxId

using hex encoding

Instance details

Defined in PlutusLedgerApi.V3.Data.Tx

Methods

pretty :: TxId -> Doc ann #

prettyList :: [TxId] -> Doc ann #

Pretty TxOutRef 
Instance details

Defined in PlutusLedgerApi.V3.Data.Tx

Methods

pretty :: TxOutRef -> Doc ann #

prettyList :: [TxOutRef] -> Doc ann #

Pretty MintValue 
Instance details

Defined in PlutusLedgerApi.V3.MintValue

Methods

pretty :: MintValue -> Doc ann #

prettyList :: [MintValue] -> Doc ann #

Pretty TxId

using hex encoding

Instance details

Defined in PlutusLedgerApi.V3.Tx

Methods

pretty :: TxId -> Doc ann #

prettyList :: [TxId] -> Doc ann #

Pretty TxOutRef 
Instance details

Defined in PlutusLedgerApi.V3.Tx

Methods

pretty :: TxOutRef -> Doc ann #

prettyList :: [TxOutRef] -> Doc ann #

Pretty ScriptEvaluationData 
Instance details

Defined in PlutusLedgerApi.Test.EvaluationEvent

Methods

pretty :: ScriptEvaluationData -> Doc ann #

prettyList :: [ScriptEvaluationData] -> Doc ann #

Pretty ScriptEvaluationEvent 
Instance details

Defined in PlutusLedgerApi.Test.EvaluationEvent

Methods

pretty :: ScriptEvaluationEvent -> Doc ann #

prettyList :: [ScriptEvaluationEvent] -> Doc ann #

Pretty ScriptEvaluationResult 
Instance details

Defined in PlutusLedgerApi.Test.EvaluationEvent

Methods

pretty :: ScriptEvaluationResult -> Doc ann #

prettyList :: [ScriptEvaluationResult] -> Doc ann #

Pretty UnexpectedEvaluationResult 
Instance details

Defined in PlutusLedgerApi.Test.EvaluationEvent

Methods

pretty :: UnexpectedEvaluationResult -> Doc ann #

prettyList :: [UnexpectedEvaluationResult] -> Doc ann #

Pretty BuiltinByteStringHex 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

Pretty BuiltinByteStringUtf8 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

Pretty BuiltinBLS12_381_G1_Element 
Instance details

Defined in PlutusTx.Builtins.Internal

Pretty BuiltinBLS12_381_G2_Element 
Instance details

Defined in PlutusTx.Builtins.Internal

Pretty BuiltinBLS12_381_MlResult 
Instance details

Defined in PlutusTx.Builtins.Internal

Pretty BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Pretty BuiltinData 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinData -> Doc ann #

prettyList :: [BuiltinData] -> Doc ann #

Pretty CovLoc 
Instance details

Defined in PlutusTx.Coverage

Methods

pretty :: CovLoc -> Doc ann #

prettyList :: [CovLoc] -> Doc ann #

Pretty CoverageAnnotation 
Instance details

Defined in PlutusTx.Coverage

Pretty CoverageMetadata 
Instance details

Defined in PlutusTx.Coverage

Pretty CoverageReport 
Instance details

Defined in PlutusTx.Coverage

Methods

pretty :: CoverageReport -> Doc ann #

prettyList :: [CoverageReport] -> Doc ann #

Pretty Metadata 
Instance details

Defined in PlutusTx.Coverage

Methods

pretty :: Metadata -> Doc ann #

prettyList :: [Metadata] -> Doc ann #

Pretty Rational 
Instance details

Defined in PlutusTx.Ratio

Methods

pretty :: Rational -> Doc ann #

prettyList :: [Rational] -> Doc ann #

Pretty Text 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Integer 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty () 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Bool 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty a => Pretty (Identity a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

Pretty (ShelleyBasedEra era) Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra

Methods

pretty :: ShelleyBasedEra era -> Doc ann #

prettyList :: [ShelleyBasedEra era] -> Doc ann #

Pretty (CardanoEra era) Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Methods

pretty :: CardanoEra era -> Doc ann #

prettyList :: [CardanoEra era] -> Doc ann #

Pretty (DeprecatedEra era) Source # 
Instance details

Defined in Cardano.Api.Internal.Experimental.Eras

Methods

pretty :: DeprecatedEra era -> Doc ann #

prettyList :: [DeprecatedEra era] -> Doc ann #

Pretty (Era era) Source # 
Instance details

Defined in Cardano.Api.Internal.Experimental.Eras

Methods

pretty :: Era era -> Doc ann #

prettyList :: [Era era] -> Doc ann #

Show a => Pretty (ShowOf a) Source # 
Instance details

Defined in Cardano.Api.Internal.Via.ShowOf

Methods

pretty :: ShowOf a -> Doc ann #

prettyList :: [ShowOf a] -> Doc ann #

Pretty (PlutusScriptContext l) => Pretty (LegacyPlutusArgs l) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

pretty :: LegacyPlutusArgs l -> Doc ann #

prettyList :: [LegacyPlutusArgs l] -> Doc ann #

Pretty (PlutusArgs 'PlutusV1) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Pretty (PlutusArgs 'PlutusV2) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Pretty (PlutusArgs 'PlutusV3) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Pretty (BuiltinSemanticsVariant DefaultFun) 
Instance details

Defined in PlutusCore.Default.Builtins

Pretty a => Pretty (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

Methods

pretty :: Normalized a -> Doc ann #

prettyList :: [Normalized a] -> Doc ann #

Pretty (DefaultUni a)

This always pretty-prints parens around type applications (e.g. (list bool)) and doesn't pretty-print them otherwise (e.g. integer).

Instance details

Defined in PlutusCore.Default.Universe

Methods

pretty :: DefaultUni a -> Doc ann #

prettyList :: [DefaultUni a] -> Doc ann #

Pretty ann => Pretty (UniqueError ann) 
Instance details

Defined in PlutusCore.Error

Methods

pretty :: UniqueError ann -> Doc ann0 #

prettyList :: [UniqueError ann] -> Doc ann0 #

PrettyClassic a => Pretty (EvaluationResult a) 
Instance details

Defined in PlutusCore.Evaluation.Result

Methods

pretty :: EvaluationResult a -> Doc ann #

prettyList :: [EvaluationResult a] -> Doc ann #

PrettyReadable a => Pretty (AsReadable a) 
Instance details

Defined in PlutusCore.Pretty.Readable

Methods

pretty :: AsReadable a -> Doc ann #

prettyList :: [AsReadable a] -> Doc ann #

Pretty (SomeTypeIn DefaultUni) 
Instance details

Defined in PlutusCore.Default.Universe

(Show fun, Ord fun) => Pretty (CekExTally fun) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

pretty :: CekExTally fun -> Doc ann #

prettyList :: [CekExTally fun] -> Doc ann #

(Show fun, Ord fun) => Pretty (TallyingSt fun) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

pretty :: TallyingSt fun -> Doc ann #

prettyList :: [TallyingSt fun] -> Doc ann #

Show fun => Pretty (ExBudgetCategory fun) 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

pretty :: ExBudgetCategory fun -> Doc ann #

prettyList :: [ExBudgetCategory fun] -> Doc ann #

Pretty a => Pretty (Provenance a) 
Instance details

Defined in PlutusIR.Compiler.Provenance

Methods

pretty :: Provenance a -> Doc ann #

prettyList :: [Provenance a] -> Doc ann #

(Pretty a, ToData a, UnsafeFromData a) => Pretty (Extended a) 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: Extended a -> Doc ann #

prettyList :: [Extended a] -> Doc ann #

(Pretty a, ToData a, UnsafeFromData a) => Pretty (Interval a) 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: Interval a -> Doc ann #

prettyList :: [Interval a] -> Doc ann #

(Pretty a, ToData a, UnsafeFromData a) => Pretty (LowerBound a) 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: LowerBound a -> Doc ann #

prettyList :: [LowerBound a] -> Doc ann #

(Pretty a, ToData a, UnsafeFromData a) => Pretty (UpperBound a) 
Instance details

Defined in PlutusLedgerApi.V1.Data.Interval

Methods

pretty :: UpperBound a -> Doc ann #

prettyList :: [UpperBound a] -> Doc ann #

Pretty a => Pretty (Extended a) 
Instance details

Defined in PlutusLedgerApi.V1.Interval

Methods

pretty :: Extended a -> Doc ann #

prettyList :: [Extended a] -> Doc ann #

Pretty a => Pretty (Interval a) 
Instance details

Defined in PlutusLedgerApi.V1.Interval

Methods

pretty :: Interval a -> Doc ann #

prettyList :: [Interval a] -> Doc ann #

Pretty a => Pretty (LowerBound a) 
Instance details

Defined in PlutusLedgerApi.V1.Interval

Methods

pretty :: LowerBound a -> Doc ann #

prettyList :: [LowerBound a] -> Doc ann #

Pretty a => Pretty (UpperBound a) 
Instance details

Defined in PlutusLedgerApi.V1.Interval

Methods

pretty :: UpperBound a -> Doc ann #

prettyList :: [UpperBound a] -> Doc ann #

Show a => Pretty (PrettyShow a) 
Instance details

Defined in Prettyprinter.Extras

Methods

pretty :: PrettyShow a -> Doc ann #

prettyList :: [PrettyShow a] -> Doc ann #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty [a] 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

Pretty (Some Era) Source # 
Instance details

Defined in Cardano.Api.Internal.Experimental.Eras

Methods

pretty :: Some Era -> Doc ann #

prettyList :: [Some Era] -> Doc ann #

(Pretty structural, Pretty operational) => Pretty (EvaluationError structural operational) 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

pretty :: EvaluationError structural operational -> Doc ann #

prettyList :: [EvaluationError structural operational] -> Doc ann #

(Pretty err, Pretty cause) => Pretty (ErrorWithCause err cause) 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

pretty :: ErrorWithCause err cause -> Doc ann #

prettyList :: [ErrorWithCause err cause] -> Doc ann #

(Foldable f, Pretty a) => Pretty (PrettyFoldable f a) 
Instance details

Defined in Prettyprinter.Extras

Methods

pretty :: PrettyFoldable f a -> Doc ann #

prettyList :: [PrettyFoldable f a] -> Doc ann #

(Pretty k, Pretty v) => Pretty (Map k v) 
Instance details

Defined in PlutusTx.AssocMap

Methods

pretty :: Map k v -> Doc ann #

prettyList :: [Map k v] -> Doc ann #

DefaultPrettyBy config a => Pretty (AttachDefaultPrettyConfig config a) 
Instance details

Defined in Text.PrettyBy.Internal

Methods

pretty :: AttachDefaultPrettyConfig config a -> Doc ann #

prettyList :: [AttachDefaultPrettyConfig config a] -> Doc ann #

PrettyBy config a => Pretty (AttachPrettyConfig config a) 
Instance details

Defined in Text.PrettyBy.Internal

Methods

pretty :: AttachPrettyConfig config a -> Doc ann #

prettyList :: [AttachPrettyConfig config a] -> Doc ann #

(Pretty a1, Pretty a2) => Pretty (a1, a2) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

(PrettyUni uni, Pretty fun, Pretty ann) => Pretty (Error uni fun ann) 
Instance details

Defined in PlutusIR.Error

Methods

pretty :: Error uni fun ann -> Doc ann0 #

prettyList :: [Error uni fun ann] -> Doc ann0 #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

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

Expand
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 liftIO, we would have ended up with this error:

• 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 IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

Instances

Instances details
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a Source #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a Source #

MonadIO m => MonadIO (ZeptoT m) 
Instance details

Defined in Data.Attoparsec.Zepto

Methods

liftIO :: IO a -> ZeptoT m a Source #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Foundation.Monad.Identity

Methods

liftIO :: IO a -> IdentityT m a Source #

MonadIO m => MonadIO (GenT m) 
Instance details

Defined in Hedgehog.Internal.Gen

Methods

liftIO :: IO a -> GenT m a Source #

MonadIO m => MonadIO (PropertyT m) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftIO :: IO a -> PropertyT m a Source #

MonadIO m => MonadIO (TestT m) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

liftIO :: IO a -> TestT m a Source #

MonadIO m => MonadIO (TreeT m) 
Instance details

Defined in Hedgehog.Internal.Tree

Methods

liftIO :: IO a -> TreeT m a Source #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in ListT

Methods

liftIO :: IO a -> ListT m a Source #

MonadIO m => MonadIO (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

liftIO :: IO a -> ResourceT m a Source #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a Source #

MonadIO m => MonadIO (FailT e m) 
Instance details

Defined in Control.Monad.Trans.Fail

Methods

liftIO :: IO a -> FailT e m a Source #

MonadIO m => MonadIO (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

liftIO :: IO a -> RandT g m a Source #

MonadIO m => MonadIO (RandT g m) 
Instance details

Defined in Control.Monad.Trans.Random.Strict

Methods

liftIO :: IO a -> RandT g m a Source #

MonadIO m => MonadIO (ExceptRT r m) 
Instance details

Defined in Data.EitherR

Methods

liftIO :: IO a -> ExceptRT r m a Source #

(Functor m, MonadIO m) => MonadIO (StateT s m) 
Instance details

Defined in Foundation.Monad.State

Methods

liftIO :: IO a -> StateT s m a Source #

(Functor f, MonadIO m) => MonadIO (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

liftIO :: IO a -> FreeT f m a Source #

(Monoid w, Functor m, MonadIO m) => MonadIO (AccumT w m) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

liftIO :: IO a -> AccumT w m a Source #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a Source #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a Source #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a Source #

MonadIO m => MonadIO (SelectT r m) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

liftIO :: IO a -> SelectT r m a Source #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a Source #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a Source #

MonadIO m => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

liftIO :: IO a -> WriterT w m a Source #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

liftIO :: IO a -> WriterT w m a Source #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftIO :: IO a -> WriterT w m a Source #

MonadIO m => MonadIO (ConduitT i o m) 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

liftIO :: IO a -> ConduitT i o m a Source #

MonadIO m => MonadIO (ParsecT s u m) 
Instance details

Defined in Text.Parsec.Prim

Methods

liftIO :: IO a -> ParsecT s u m a Source #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a Source #

MonadIO m => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

liftIO :: IO a -> RWST r w s m a Source #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

liftIO :: IO a -> RWST r w s m a Source #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a Source #

MonadIO m => MonadIO (LocalStateQueryExpr block point query r m) Source # 
Instance details

Defined in Cardano.Api.Internal.IPC.Monad

Methods

liftIO :: IO a -> LocalStateQueryExpr block point query r m a Source #

MonadIO m => MonadIO (Pipe l i o u m) 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

liftIO :: IO a -> Pipe l i o u m a Source #

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. Monad m => Monad (t m) enabled by the QuantifiedConstraints extension.

Ambiguity error with GHC 9.0 to 9.2.2

Expand

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

Instances details
MonadTrans Free 
Instance details

Defined in Control.Monad.Free

Methods

lift :: Monad m => m a -> Free m a Source #

MonadTrans GenT 
Instance details

Defined in Hedgehog.Internal.Gen

Methods

lift :: Monad m => m a -> GenT m a Source #

MonadTrans PropertyT 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: Monad m => m a -> PropertyT m a Source #

MonadTrans TestT 
Instance details

Defined in Hedgehog.Internal.Property

Methods

lift :: Monad m => m a -> TestT m a Source #

MonadTrans TreeT 
Instance details

Defined in Hedgehog.Internal.Tree

Methods

lift :: Monad m => m a -> TreeT m a Source #

MonadTrans Yoneda 
Instance details

Defined in Data.Functor.Yoneda

Methods

lift :: Monad m => m a -> Yoneda m a Source #

MonadTrans ListT 
Instance details

Defined in ListT

Methods

lift :: Monad m => m a -> ListT m a Source #

MonadTrans WithEarlyExit 
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

lift :: Monad m => m a -> WithEarlyExit m a Source #

MonadTrans ResourceT 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

lift :: Monad m => m a -> ResourceT m a Source #

MonadTrans MaybeT 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

lift :: Monad m => m a -> MaybeT m a Source #

MonadTrans (FailT e) 
Instance details

Defined in Control.Monad.Trans.Fail

Methods

lift :: Monad m => m a -> FailT e m a Source #

MonadTrans (RandT g) 
Instance details

Defined in Control.Monad.Trans.Random.Lazy

Methods

lift :: Monad m => m a -> RandT g m a Source #

MonadTrans (RandT g) 
Instance details

Defined in Control.Monad.Trans.Random.Strict

Methods

lift :: Monad m => m a -> RandT g m a Source #

MonadTrans (ExceptRT r) 
Instance details

Defined in Data.EitherR

Methods

lift :: Monad m => m a -> ExceptRT r m a Source #

Alternative f => MonadTrans (CofreeT f) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

lift :: Monad m => m a -> CofreeT f m a Source #

Functor f => MonadTrans (FreeT f) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

lift :: Monad m => m a -> FreeT f m a Source #

MonadTrans (Electric :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

lift :: Monad m => m a -> Electric m a Source #

MonadTrans (WithTempRegistry st) 
Instance details

Defined in Control.ResourceRegistry

Methods

lift :: Monad m => m a -> WithTempRegistry st m a Source #

MonadTrans (ProvM t) 
Instance details

Defined in Control.Provenance

Methods

lift :: Monad m => m a -> ProvM t m a Source #

Monoid w => MonadTrans (AccumT w) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

lift :: Monad m => m a -> AccumT w m a Source #

MonadTrans (ExceptT e) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a Source #

MonadTrans (IdentityT :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

lift :: Monad m => m a -> IdentityT m a Source #

MonadTrans (ReaderT r) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

lift :: Monad m => m a -> ReaderT r m a Source #

MonadTrans (SelectT r) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

lift :: Monad m => m a -> SelectT r m a Source #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

lift :: Monad m => m a -> StateT s m a Source #

MonadTrans (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

lift :: Monad m => m a -> StateT s m a Source #

MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

lift :: Monad m => m a -> WriterT w m a Source #

Monoid w => MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

lift :: Monad m => m a -> WriterT w m a Source #

Monoid w => MonadTrans (WriterT w) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

lift :: Monad m => m a -> WriterT w m a Source #

MonadTrans (ConduitT i o) 
Instance details

Defined in Data.Conduit.Internal.Conduit

Methods

lift :: Monad m => m a -> ConduitT i o m a Source #

MonadTrans (ParsecT s u) 
Instance details

Defined in Text.Parsec.Prim

Methods

lift :: Monad m => m a -> ParsecT s u m a Source #

MonadTrans (ContT r) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

lift :: Monad m => m a -> ContT r m a Source #

MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

lift :: Monad m => m a -> RWST r w s m a Source #

Monoid w => MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

lift :: Monad m => m a -> RWST r w s m a Source #

Monoid w => MonadTrans (RWST r w s) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

lift :: Monad m => m a -> RWST r w s m a Source #

MonadTrans (Pipe l i o u) 
Instance details

Defined in Data.Conduit.Internal.Pipe

Methods

lift :: Monad m => m a -> Pipe l i o u m a Source #

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 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

Instances details
Key ByronKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Key ByronKeyLegacy Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Key KesKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Key VrfKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Key CommitteeColdExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key CommitteeColdKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key CommitteeHotExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key CommitteeHotKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key DRepExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key DRepKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key GenesisDelegateExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key GenesisDelegateKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key GenesisExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key GenesisKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key GenesisUTxOKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key PaymentExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key PaymentKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key StakeExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key StakeKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key StakePoolExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Key StakePoolKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

data Block era where Source #

Deprecated: Use getBlockHeader instead

A blockchain block in a particular Cardano era.

Instances

Instances details
Show (Block era) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Methods

showsPrec :: Int -> Block era -> ShowS Source #

show :: Block era -> String Source #

showList :: [Block era] -> ShowS Source #

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 #

Instances

Instances details
HasTypeProxy BlockHeader Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Associated Types

data AsType BlockHeader 
Instance details

Defined in Cardano.Api.Internal.Block

FromJSON (Hash BlockHeader) Source # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.Block

IsString (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Show (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

SerialiseAsRawBytes (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Eq (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Ord (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

data AsType BlockHeader Source # 
Instance details

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.

Instance details

Defined in Cardano.Api.Internal.Block

data family Hash keyrole Source #

Instances

Instances details
FromJSON (Hash BlockHeader) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromJSON (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash StakePoolKey)

parseJSONList :: Value -> Parser [Hash StakePoolKey]

omittedField :: Maybe (Hash StakePoolKey)

FromJSON (Hash ScriptData) Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Methods

parseJSON :: Value -> Parser (Hash ScriptData)

parseJSONList :: Value -> Parser [Hash ScriptData]

omittedField :: Maybe (Hash ScriptData)

FromJSONKey (Hash ScriptData) 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Methods

fromJSONKey :: FromJSONKeyFunction (Hash ScriptData)

fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData]

ToJSON (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

ToJSON (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toJSON :: Hash DRepKey -> Value

toEncoding :: Hash DRepKey -> Encoding

toJSONList :: [Hash DRepKey] -> Value

toEncodingList :: [Hash DRepKey] -> Encoding

omitField :: Hash DRepKey -> Bool

ToJSON (Hash GenesisKey) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToJSON (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToJSON (Hash ScriptData) Source # 
Instance details

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) 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash DRepKey)

toJSONKeyList :: ToJSONKeyFunction [Hash DRepKey]

ToJSONKey (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash GenesisKey)

toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey]

ToJSONKey (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash PaymentKey)

toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey]

ToJSONKey (Hash StakePoolExtendedKey) 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash StakePoolExtendedKey)

toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolExtendedKey]

ToJSONKey (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey)

toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey]

ToJSONKey (Hash ScriptData) 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Methods

toJSONKey :: ToJSONKeyFunction (Hash ScriptData)

toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData]

IsString (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

IsString (Hash GovernancePoll) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Poll

IsString (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

IsString (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

IsString (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

IsString (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

IsString (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (Hash ScriptData) Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Show (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Show (Hash DRepMetadata) Source # 
Instance details

Defined in Cardano.Api.Internal.DRepMetadata

Show (Hash GovernancePoll) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Poll

Show (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Show (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Show (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Show (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Show (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (Hash ScriptData) Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Show (Hash StakePoolMetadata) Source # 
Instance details

Defined in Cardano.Api.Internal.StakePoolMetadata

HasTypeProxy a => HasTypeProxy (Hash a) Source # 
Instance details

Defined in Cardano.Api.Internal.Hash

Associated Types

data AsType (Hash a) 
Instance details

Defined in Cardano.Api.Internal.Hash

data AsType (Hash a) = AsHash (AsType a)

Methods

proxyToAsType :: Proxy (Hash a) -> AsType (Hash a) Source #

SerialiseAsCBOR (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsCBOR (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsCBOR (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsCBOR (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsCBOR (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (Hash StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

SerialiseAsRawBytes (Hash DRepMetadata) Source # 
Instance details

Defined in Cardano.Api.Internal.DRepMetadata

SerialiseAsRawBytes (Hash GovernancePoll) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Poll

SerialiseAsRawBytes (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsRawBytes (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsRawBytes (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsRawBytes (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (Hash ScriptData) Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

SerialiseAsRawBytes (Hash StakePoolMetadata) Source # 
Instance details

Defined in Cardano.Api.Internal.StakePoolMetadata

FromCBOR (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Methods

toCBOR :: Hash ByronKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash ByronKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash ByronKey] -> Size Source #

ToCBOR (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Methods

toCBOR :: Hash KesKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash KesKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash KesKey] -> Size Source #

ToCBOR (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Methods

toCBOR :: Hash VrfKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash VrfKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash VrfKey] -> Size Source #

ToCBOR (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toCBOR :: Hash DRepKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash DRepKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash DRepKey] -> Size Source #

ToCBOR (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toCBOR :: Hash StakeKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash StakeKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash StakeKey] -> Size Source #

ToCBOR (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Eq (Hash DRepMetadata) Source # 
Instance details

Defined in Cardano.Api.Internal.DRepMetadata

Eq (Hash GovernancePoll) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Poll

Eq (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Eq (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Eq (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Eq (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Eq (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (Hash ScriptData) Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Eq (Hash StakePoolMetadata) Source # 
Instance details

Defined in Cardano.Api.Internal.StakePoolMetadata

Ord (Hash BlockHeader) Source # 
Instance details

Defined in Cardano.Api.Internal.Block

Ord (Hash GovernancePoll) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Poll

Ord (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Ord (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Ord (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Ord (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Ord (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Ord (Hash ScriptData) Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

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.

Instance details

Defined in Cardano.Api.Internal.Block

newtype Hash DRepMetadata Source # 
Instance details

Defined in Cardano.Api.Internal.DRepMetadata

newtype Hash GovernancePoll Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Poll

newtype Hash ByronKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

newtype Hash ByronKeyLegacy Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

newtype Hash KesKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

newtype Hash VrfKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

newtype Hash CommitteeColdExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash CommitteeColdKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash CommitteeHotExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash CommitteeHotKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash DRepExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash DRepKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash GenesisDelegateExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash GenesisDelegateKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash GenesisExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash GenesisKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash GenesisUTxOKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash PaymentExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash PaymentKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash StakeExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash StakeKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash StakePoolExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash StakePoolKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype Hash ScriptData Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

newtype Hash StakePoolMetadata Source # 
Instance details

Defined in Cardano.Api.Internal.StakePoolMetadata

data AsType (Hash a) Source # 
Instance details

Defined in Cardano.Api.Internal.Hash

data AsType (Hash a) = AsHash (AsType a)

data TxBody era where Source #

Constructors

ShelleyTxBody 

Fields

Bundled Patterns

pattern TxBody :: TxBodyContent ViewTx era -> TxBody era

Deprecated: Use getTxBodyContent $ getTxBody instead

Instances

Instances details
Show (TxBody era) Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Sign

Methods

showsPrec :: Int -> TxBody era -> ShowS Source #

show :: TxBody era -> String Source #

showList :: [TxBody era] -> ShowS Source #

HasTypeProxy era => HasTypeProxy (TxBody era) Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Sign

Associated Types

data AsType (TxBody era) 
Instance details

Defined in Cardano.Api.Internal.Tx.Sign

data AsType (TxBody era) = AsTxBody (AsType era)

Methods

proxyToAsType :: Proxy (TxBody era) -> AsType (TxBody era) Source #

IsShelleyBasedEra era => SerialiseAsCBOR (TxBody era) Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Sign

IsShelleyBasedEra era => HasTextEnvelope (TxBody era) Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Sign

Eq (TxBody era) Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Sign

Methods

(==) :: TxBody era -> TxBody era -> Bool Source #

(/=) :: TxBody era -> TxBody era -> Bool Source #

data AsType (TxBody era) Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Sign

data AsType (TxBody era) = AsTxBody (AsType era)

newtype TxId Source #

Instances

Instances details
FromJSON TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

parseJSON :: Value -> Parser TxId

parseJSONList :: Value -> Parser [TxId]

omittedField :: Maybe TxId

FromJSONKey TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

fromJSONKey :: FromJSONKeyFunction TxId

fromJSONKeyList :: FromJSONKeyFunction [TxId]

ToJSON TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

toJSON :: TxId -> Value

toEncoding :: TxId -> Encoding

toJSONList :: [TxId] -> Value

toEncodingList :: [TxId] -> Encoding

omitField :: TxId -> Bool

ToJSONKey TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

toJSONKey :: ToJSONKeyFunction TxId

toJSONKeyList :: ToJSONKeyFunction [TxId]

IsString TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Show TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

HasTypeProxy TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Associated Types

data AsType TxId 
Instance details

Defined in Cardano.Api.Internal.TxIn

SerialiseAsRawBytes TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Eq TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

(==) :: TxId -> TxId -> Bool Source #

(/=) :: TxId -> TxId -> Bool Source #

Ord TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

data AsType TxId Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

getTxId :: TxBody era -> TxId Source #

Calculate the transaction identifier for a TxBody.

class Typeable a => FromCBOR a Source #

Minimal complete definition

fromCBOR

Instances

Instances details
FromCBOR Void 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Int32 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Int64 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Rational 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Word16 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Word32 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Word64 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Word8 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR ByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR ByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR ShortByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR OperationalCertificate Source # 
Instance details

Defined in Cardano.Api.Internal.OperationalCertificate

FromCBOR OperationalCertificateIssueCounter Source # 
Instance details

Defined in Cardano.Api.Internal.OperationalCertificate

FromCBOR CostModel Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

FromCBOR ExecutionUnitPrices Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

FromCBOR PraosNonce Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

FromCBOR ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

FromCBOR UpdateProposal Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

FromCBOR AnyPlutusScriptVersion Source # 
Instance details

Defined in Cardano.Api.Internal.Script

FromCBOR ExecutionUnits Source # 
Instance details

Defined in Cardano.Api.Internal.Script

FromCBOR ScriptData Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

FromCBOR Point 
Instance details

Defined in Cardano.Crypto.VRF.Simple

Methods

fromCBOR :: Decoder s Point Source #

label :: Proxy Point -> Text Source #

FromCBOR Proof 
Instance details

Defined in Cardano.Crypto.VRF.Praos

FromCBOR SignKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

FromCBOR VerKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

FromCBOR Proof 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

FromCBOR SignKey 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

fromCBOR :: Decoder s SignKey Source #

label :: Proxy SignKey -> Text Source #

FromCBOR VerKey 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

fromCBOR :: Decoder s VerKey Source #

label :: Proxy VerKey -> Text Source #

FromCBOR ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

FromCBOR RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

FromCBOR Raw 
Instance details

Defined in Cardano.Crypto.Raw

FromCBOR CompactRedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Compact

FromCBOR RedeemSigningKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.SigningKey

FromCBOR RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

FromCBOR SigningKey 
Instance details

Defined in Cardano.Crypto.Signing.SigningKey

FromCBOR VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

FromCBOR AlonzoGenesis 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

FromCBOR Version 
Instance details

Defined in Cardano.Ledger.Binary.Version

FromCBOR Body 
Instance details

Defined in Cardano.Chain.Block.Body

FromCBOR BlockSignature 
Instance details

Defined in Cardano.Chain.Block.Header

FromCBOR ToSign 
Instance details

Defined in Cardano.Chain.Block.Header

FromCBOR Proof 
Instance details

Defined in Cardano.Chain.Block.Proof

FromCBOR ChainValidationState 
Instance details

Defined in Cardano.Chain.Block.Validation

FromCBOR ApplyMempoolPayloadErr 
Instance details

Defined in Cardano.Chain.Byron.API.Mempool

FromCBOR HDAddressPayload 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

FromCBOR AddrSpendingData 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

FromCBOR AddrType 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

FromCBOR Address 
Instance details

Defined in Cardano.Chain.Common.Address

FromCBOR Address' 
Instance details

Defined in Cardano.Chain.Common.Address

FromCBOR BlockCount 
Instance details

Defined in Cardano.Chain.Common.BlockCount

FromCBOR ChainDifficulty 
Instance details

Defined in Cardano.Chain.Common.ChainDifficulty

FromCBOR CompactAddress 
Instance details

Defined in Cardano.Chain.Common.Compact

FromCBOR Lovelace 
Instance details

Defined in Cardano.Chain.Common.Lovelace

FromCBOR LovelaceError 
Instance details

Defined in Cardano.Chain.Common.Lovelace

FromCBOR LovelacePortion 
Instance details

Defined in Cardano.Chain.Common.LovelacePortion

FromCBOR NetworkMagic 
Instance details

Defined in Cardano.Chain.Common.NetworkMagic

FromCBOR TxFeePolicy 
Instance details

Defined in Cardano.Chain.Common.TxFeePolicy

FromCBOR TxSizeLinear 
Instance details

Defined in Cardano.Chain.Common.TxSizeLinear

FromCBOR Certificate 
Instance details

Defined in Cardano.Chain.Delegation.Certificate

FromCBOR Map 
Instance details

Defined in Cardano.Chain.Delegation.Map

FromCBOR Payload 
Instance details

Defined in Cardano.Chain.Delegation.Payload

FromCBOR State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Activation

FromCBOR State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Interface

FromCBOR Error 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

FromCBOR ScheduledDelegation 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

FromCBOR State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

FromCBOR GenesisAvvmBalances 
Instance details

Defined in Cardano.Chain.Genesis.AvvmBalances

FromCBOR Config 
Instance details

Defined in Cardano.Chain.Genesis.Config

FromCBOR GenesisData 
Instance details

Defined in Cardano.Chain.Genesis.Data

FromCBOR GenesisDelegation 
Instance details

Defined in Cardano.Chain.Genesis.Delegation

FromCBOR GenesisKeyHashes 
Instance details

Defined in Cardano.Chain.Genesis.KeyHashes

FromCBOR GenesisNonAvvmBalances 
Instance details

Defined in Cardano.Chain.Genesis.NonAvvmBalances

FromCBOR MempoolPayload 
Instance details

Defined in Cardano.Chain.MempoolPayload

FromCBOR EpochAndSlotCount 
Instance details

Defined in Cardano.Chain.Slotting.EpochAndSlotCount

FromCBOR EpochNumber 
Instance details

Defined in Cardano.Chain.Slotting.EpochNumber

FromCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

FromCBOR SlotCount 
Instance details

Defined in Cardano.Chain.Slotting.SlotCount

FromCBOR SlotNumber 
Instance details

Defined in Cardano.Chain.Slotting.SlotNumber

FromCBOR SscPayload 
Instance details

Defined in Cardano.Chain.Ssc

FromCBOR SscProof 
Instance details

Defined in Cardano.Chain.Ssc

FromCBOR CompactTxId 
Instance details

Defined in Cardano.Chain.UTxO.Compact

FromCBOR CompactTxIn 
Instance details

Defined in Cardano.Chain.UTxO.Compact

FromCBOR CompactTxOut 
Instance details

Defined in Cardano.Chain.UTxO.Compact

FromCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

FromCBOR TxIn 
Instance details

Defined in Cardano.Chain.UTxO.Tx

FromCBOR TxOut 
Instance details

Defined in Cardano.Chain.UTxO.Tx

FromCBOR TxAux 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

FromCBOR TxPayload 
Instance details

Defined in Cardano.Chain.UTxO.TxPayload

FromCBOR TxProof 
Instance details

Defined in Cardano.Chain.UTxO.TxProof

FromCBOR TxInWitness 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

FromCBOR TxSigData 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

FromCBOR UTxO 
Instance details

Defined in Cardano.Chain.UTxO.UTxO

FromCBOR UTxOError 
Instance details

Defined in Cardano.Chain.UTxO.UTxO

FromCBOR UTxOConfiguration 
Instance details

Defined in Cardano.Chain.UTxO.UTxOConfiguration

FromCBOR TxValidationError 
Instance details

Defined in Cardano.Chain.UTxO.Validation

FromCBOR UTxOValidationError 
Instance details

Defined in Cardano.Chain.UTxO.Validation

FromCBOR ApplicationName 
Instance details

Defined in Cardano.Chain.Update.ApplicationName

FromCBOR ApplicationNameError 
Instance details

Defined in Cardano.Chain.Update.ApplicationName

FromCBOR InstallerHash 
Instance details

Defined in Cardano.Chain.Update.InstallerHash

FromCBOR Payload 
Instance details

Defined in Cardano.Chain.Update.Payload

FromCBOR Proposal 
Instance details

Defined in Cardano.Chain.Update.Proposal

FromCBOR ProposalBody 
Instance details

Defined in Cardano.Chain.Update.Proposal

FromCBOR ProtocolParameters 
Instance details

Defined in Cardano.Chain.Update.ProtocolParameters

FromCBOR ProtocolParametersUpdate 
Instance details

Defined in Cardano.Chain.Update.ProtocolParametersUpdate

FromCBOR ProtocolVersion 
Instance details

Defined in Cardano.Chain.Update.ProtocolVersion

FromCBOR SoftforkRule 
Instance details

Defined in Cardano.Chain.Update.SoftforkRule

FromCBOR SoftwareVersion 
Instance details

Defined in Cardano.Chain.Update.SoftwareVersion

FromCBOR SoftwareVersionError 
Instance details

Defined in Cardano.Chain.Update.SoftwareVersion

FromCBOR SystemTag 
Instance details

Defined in Cardano.Chain.Update.SystemTag

FromCBOR SystemTagError 
Instance details

Defined in Cardano.Chain.Update.SystemTag

FromCBOR CandidateProtocolUpdate 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

FromCBOR Endorsement 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

FromCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

FromCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Interface

FromCBOR State 
Instance details

Defined in Cardano.Chain.Update.Validation.Interface

FromCBOR Adopted 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

FromCBOR ApplicationVersion 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

FromCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

FromCBOR ProtocolUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

FromCBOR SoftwareUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

FromCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Voting

FromCBOR Vote 
Instance details

Defined in Cardano.Chain.Update.Vote

FromCBOR ConwayGenesis

Genesis are always encoded with the version of era they are defined in.

Instance details

Defined in Cardano.Ledger.Conway.Genesis

FromCBOR DefaultVote 
Instance details

Defined in Cardano.Ledger.Conway.Governance

FromCBOR ActiveSlotCoeff 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR CertIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR PositiveUnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR TxIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

FromCBOR Ptr 
Instance details

Defined in Cardano.Ledger.Credential

FromCBOR SlotNo32 
Instance details

Defined in Cardano.Ledger.Credential

FromCBOR ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

FromCBOR PlutusWithContext 
Instance details

Defined in Cardano.Ledger.Plutus.Evaluate

FromCBOR Language 
Instance details

Defined in Cardano.Ledger.Plutus.Language

FromCBOR PlutusBinary 
Instance details

Defined in Cardano.Ledger.Plutus.Language

FromCBOR ShelleyGenesis 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

FromCBOR FromByronTranslationContext 
Instance details

Defined in Cardano.Ledger.Shelley.Translation

FromCBOR ChainDepState 
Instance details

Defined in Cardano.Protocol.TPraos.API

FromCBOR KESPeriod 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

FromCBOR PrtclState 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Prtcl

FromCBOR TicknState 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Tickn

FromCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

FromCBOR EpochInterval 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

FromCBOR SlotLength 
Instance details

Defined in Cardano.Slotting.Time

FromCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

FromCBOR TermToken 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Term 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR SecurityParam 
Instance details

Defined in Ouroboros.Consensus.Config.SecurityParam

FromCBOR CoreNodeId 
Instance details

Defined in Ouroboros.Consensus.NodeId

FromCBOR NodeId 
Instance details

Defined in Ouroboros.Consensus.NodeId

FromCBOR CompactGenesis 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

FromCBOR NonMyopicMemberRewards 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

FromCBOR StakeSnapshot 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

FromCBOR StakeSnapshots 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

FromCBOR ShelleyHash 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

FromCBOR PraosState 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

FromCBOR TPraosState 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

FromCBOR AccPoolStakeCoded 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Methods

fromCBOR :: Decoder s AccPoolStakeCoded Source #

label :: Proxy AccPoolStakeCoded -> Text Source #

FromCBOR LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

FromCBOR PoolStakeCoded 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Methods

fromCBOR :: Decoder s PoolStakeCoded Source #

label :: Proxy PoolStakeCoded -> Text Source #

FromCBOR WithOriginCoded 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Methods

fromCBOR :: Decoder s WithOriginCoded Source #

label :: Proxy WithOriginCoded -> Text Source #

FromCBOR RelayAccessPointCoded 
Instance details

Defined in Ouroboros.Network.PeerSelection.RelayAccessPoint

FromCBOR Text 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR UTCTime 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Integer 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Natural 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR () 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s () Source #

label :: Proxy () -> Text Source #

FromCBOR Bool 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Double 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Float 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Int 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR Word 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR a => FromCBOR (NonEmpty a) 
Instance details

Defined in Cardano.Binary.FromCBOR

IsShelleyBasedEra era => FromCBOR (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Internal.Certificate

IsShelleyBasedEra era => FromCBOR (Proposal era) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Actions.ProposalProcedure

IsShelleyBasedEra era => FromCBOR (VotingProcedure era) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure

IsShelleyBasedEra era => FromCBOR (VotingProcedures era) Source # 
Instance details

Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure

FromCBOR (Hash ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) Source # 
Instance details

Defined in Cardano.Api.Internal.Query.Types

SerialiseAsRawBytes a => FromCBOR (UsingRawBytes a) Source # 
Instance details

Defined in Cardano.Api.Internal.SerialiseUsing

FromCBOR (SigDSIGN Ed25519Bip32DSIGN) Source # 
Instance details

Defined in Cardano.Api.Crypto.Ed25519Bip32

FromCBOR (SigDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

FromCBOR (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

FromCBOR (SigDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

FromCBOR (SigDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

FromCBOR (SigDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

FromCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) Source # 
Instance details

Defined in Cardano.Api.Crypto.Ed25519Bip32

FromCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

FromCBOR (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

FromCBOR (SignKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

FromCBOR (SignKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

FromCBOR (SignKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

(TypeError ('Text "CBOR decoding would violate mlocking guarantees") :: Constraint) => FromCBOR (SignKeyDSIGNM Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

FromCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) Source # 
Instance details

Defined in Cardano.Api.Crypto.Ed25519Bip32

FromCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

FromCBOR (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

FromCBOR (VerKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

FromCBOR (VerKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

FromCBOR (VerKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

(DSIGNMAlgorithm d, KnownNat (SizeSigKES (CompactSingleKES d))) => FromCBOR (SigKES (CompactSingleKES d)) 
Instance details

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)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t => FromCBOR (SigKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => FromCBOR (SigKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNMAlgorithm d => FromCBOR (SigKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => FromCBOR (SigKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

fromCBOR :: Decoder s (SigKES (SumKES h d)) Source #

label :: Proxy (SigKES (SumKES h d)) -> Text Source #

(UnsoundDSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => FromCBOR (UnsoundPureSignKeyKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(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)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t => FromCBOR (UnsoundPureSignKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

UnsoundDSIGNMAlgorithm d => FromCBOR (UnsoundPureSignKeyKES (SingleKES d)) 
Instance details

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)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

(DSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => FromCBOR (VerKeyKES (CompactSingleKES d)) 
Instance details

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)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t => FromCBOR (VerKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => FromCBOR (VerKeyKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

DSIGNMAlgorithm d => FromCBOR (VerKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => FromCBOR (VerKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

FromCBOR (CertVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

FromCBOR (CertVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

FromCBOR (CertVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

FromCBOR (CertVRF PraosBatchCompatVRF) 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Typeable v => FromCBOR (OutputVRF v) 
Instance details

Defined in Cardano.Crypto.VRF.Class

FromCBOR (SignKeyVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

FromCBOR (SignKeyVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

FromCBOR (SignKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

FromCBOR (SignKeyVRF PraosBatchCompatVRF) 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

FromCBOR (VerKeyVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

FromCBOR (VerKeyVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

FromCBOR (VerKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

FromCBOR (VerKeyVRF PraosBatchCompatVRF) 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

DecCBOR a => FromCBOR (RedeemSignature a) 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Signature

Typeable a => FromCBOR (Signature a) 
Instance details

Defined in Cardano.Crypto.Signing.Signature

(Era era, Val (Value era)) => FromCBOR (AlonzoTxOut era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxOut

(EraScript era, Val (Value era)) => FromCBOR (BabbageTxOut era) 
Instance details

Defined in Cardano.Ledger.Babbage.TxOut

FromCBOR (ABody ByteSpan) 
Instance details

Defined in Cardano.Chain.Block.Body

FromCBOR (ABlockSignature ByteSpan) 
Instance details

Defined in Cardano.Chain.Block.Header

FromCBOR (Attributes AddrAttributes) 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

FromCBOR (Attributes ()) 
Instance details

Defined in Cardano.Chain.Common.Attributes

DecCBOR a => FromCBOR (MerkleRoot a) 
Instance details

Defined in Cardano.Chain.Common.Merkle

(DecCBOR a, EncCBOR a) => FromCBOR (MerkleTree a) 
Instance details

Defined in Cardano.Chain.Common.Merkle

FromCBOR (ACertificate ByteSpan) 
Instance details

Defined in Cardano.Chain.Delegation.Certificate

FromCBOR (APayload ByteSpan) 
Instance details

Defined in Cardano.Chain.Delegation.Payload

FromCBOR (AMempoolPayload ByteSpan) 
Instance details

Defined in Cardano.Chain.MempoolPayload

FromCBOR (ATxAux ByteSpan) 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

FromCBOR (ATxPayload ByteSpan) 
Instance details

Defined in Cardano.Chain.UTxO.TxPayload

FromCBOR (APayload ByteSpan) 
Instance details

Defined in Cardano.Chain.Update.Payload

FromCBOR (AProposal ByteSpan) 
Instance details

Defined in Cardano.Chain.Update.Proposal

DecCBOR n => FromCBOR (TooLarge n) 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

FromCBOR (AVote ByteSpan) 
Instance details

Defined in Cardano.Chain.Update.Vote

EraPParams era => FromCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

EraPParams era => FromCBOR (PulsingSnapshot era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.DRepPulser

EraPParams era => FromCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Internal

Era era => FromCBOR (Constitution era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

EraPParams era => FromCBOR (ConwayGovPredFailure era) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Gov

(ShelleyEraTxCert era, TxCert era ~ ConwayTxCert era) => FromCBOR (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

(HasZero a, FromCBOR a) => FromCBOR (NonZero a) 
Instance details

Defined in Cardano.Ledger.BaseTypes.NonZero

(Typeable era, FromCBOR (PParamsHKD Identity era)) => FromCBOR (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

fromCBOR :: Decoder s (PParams era) Source #

label :: Proxy (PParams era) -> Text Source #

(Typeable era, FromCBOR (PParamsHKD StrictMaybe era)) => FromCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Typeable kr => FromCBOR (Credential kr) 
Instance details

Defined in Cardano.Ledger.Credential

Era era => FromCBOR (NoGenesis era) 
Instance details

Defined in Cardano.Ledger.Genesis

Typeable r => FromCBOR (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable i => FromCBOR (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable r => FromCBOR (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable kd => FromCBOR (VKey kd) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

fromCBOR :: Decoder s (VKey kd) Source #

label :: Proxy (VKey kd) -> Text Source #

PlutusLanguage l => FromCBOR (SLanguage l) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

(DecCBOR (TxOut era), Era era) => FromCBOR (UTxO era) 
Instance details

Defined in Cardano.Ledger.State.UTxO

Methods

fromCBOR :: Decoder s (UTxO era) Source #

label :: Proxy (UTxO era) -> Text Source #

(Era era, DecCBOR (PredicateFailure (EraRule "LEDGER" era))) => FromCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

(Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) => FromCBOR (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

(EraTxOut era, EraGov era, EraStake era, EraCertState era) => FromCBOR (EpochState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

(EraTxOut era, EraGov era, EraStake era, EraCertState era) => FromCBOR (LedgerState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

(EraTxOut era, EraGov era, EraStake era, EraCertState era, DecCBOR (StashedAVVMAddresses era)) => FromCBOR (NewEpochState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

(EraTxOut era, EraGov era, EraStake era) => FromCBOR (UTxOState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

(Era era, FromCBOR (PParamsUpdate era)) => FromCBOR (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

(ShelleyEraTxCert era, TxCert era ~ ShelleyTxCert era) => FromCBOR (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

(Era era, DecCBOR (CompactForm (Value era))) => FromCBOR (ShelleyTxOut era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxOut

Crypto c => FromCBOR (OCert c) 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

(Serialise t, Typeable t) => FromCBOR (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR a => FromCBOR (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

FromCBOR a => FromCBOR (StrictSeq a) 
Instance details

Defined in Data.Sequence.Strict

FromCBOR a => FromCBOR (Seq a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Seq a) Source #

label :: Proxy (Seq a) -> Text Source #

(Ord a, FromCBOR a) => FromCBOR (Set a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Set a) Source #

label :: Proxy (Set a) -> Text Source #

FromCBOR a => FromCBOR (Vector a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Vector a) Source #

label :: Proxy (Vector a) -> Text Source #

FromCBOR a => FromCBOR (Maybe a) 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR a => FromCBOR [a] 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s [a] Source #

label :: Proxy [a] -> Text Source #

(FromCBOR a, FromCBOR b) => FromCBOR (Either a b) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Either a b) Source #

label :: Proxy (Either a b) -> Text Source #

Typeable a => FromCBOR (Fixed a) 
Instance details

Defined in Cardano.Binary.FromCBOR

(HashAlgorithm h, Typeable a) => FromCBOR (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromCBOR :: Decoder s (Hash h a) Source #

label :: Proxy (Hash h a) -> Text Source #

(VRFAlgorithm v, Typeable a) => FromCBOR (CertifiedVRF v a) 
Instance details

Defined in Cardano.Crypto.VRF.Class

(Typeable algo, Typeable a, HashAlgorithm algo) => FromCBOR (AbstractHash algo a) 
Instance details

Defined in Cardano.Crypto.Hashing

Methods

fromCBOR :: Decoder s (AbstractHash algo a) Source #

label :: Proxy (AbstractHash algo a) -> Text Source #

Era era => FromCBOR (AlonzoPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Era era => FromCBOR (AlonzoPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Era era => FromCBOR (BabbagePParams Identity era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Era era => FromCBOR (BabbagePParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Era era => FromCBOR (ConwayPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Era era => FromCBOR (ConwayPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

(FromCBOR a, Bounded (BoundedRatio b a), Bounded a, Integral a, Typeable b, Show a) => FromCBOR (BoundedRatio b a) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s (BoundedRatio b a) Source #

label :: Proxy (BoundedRatio b a) -> Text Source #

(KnownSymbol rule, Era era) => FromCBOR (VoidEraRule rule era) 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

fromCBOR :: Decoder s (VoidEraRule rule era) Source #

label :: Proxy (VoidEraRule rule era) -> Text Source #

Era era => FromCBOR (ShelleyPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Era era => FromCBOR (ShelleyPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

(Ord k, FromCBOR k, FromCBOR v) => FromCBOR (Map k v) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Map k v) Source #

label :: Proxy (Map k v) -> Text Source #

(FromCBOR a, FromCBOR b) => FromCBOR (a, b) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b) Source #

label :: Proxy (a, b) -> Text Source #

(Typeable s, FromCBOR a) => FromCBOR (Tagged s a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s0 (Tagged s a) Source #

label :: Proxy (Tagged s a) -> Text Source #

(FromCBOR a, FromCBOR b, FromCBOR c) => FromCBOR (a, b, c) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b, c) Source #

label :: Proxy (a, b, c) -> Text Source #

(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d) => FromCBOR (a, b, c, d) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b, c, d) Source #

label :: Proxy (a, b, c, d) -> Text Source #

(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d, FromCBOR e) => FromCBOR (a, b, c, d, e) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b, c, d, e) Source #

label :: Proxy (a, b, c, d, e) -> Text Source #

(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d, FromCBOR e, FromCBOR f) => FromCBOR (a, b, c, d, e, f) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b, c, d, e, f) Source #

label :: Proxy (a, b, c, d, e, f) -> Text Source #

(FromCBOR a, FromCBOR b, FromCBOR c, FromCBOR d, FromCBOR e, FromCBOR f, FromCBOR g) => FromCBOR (a, b, c, d, e, f, g) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b, c, d, e, f, g) Source #

label :: Proxy (a, b, c, d, e, f, g) -> Text Source #

(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) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b, c, d, e, f, g, h) Source #

label :: Proxy (a, b, c, d, e, f, g, h) -> Text Source #

class Typeable a => ToCBOR a Source #

Minimal complete definition

toCBOR

Instances

Instances details
ToCBOR Void 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Void -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Void -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Void] -> Size Source #

ToCBOR Int32 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Int32 -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Int32 -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Int32] -> Size Source #

ToCBOR Int64 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Int64 -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Int64 -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Int64] -> Size Source #

ToCBOR Word16 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word16 -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Word16 -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Word16] -> Size Source #

ToCBOR Word32 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word32 -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Word32 -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Word32] -> Size Source #

ToCBOR Word64 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word64 -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Word64 -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Word64] -> Size Source #

ToCBOR Word8 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word8 -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Word8 -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Word8] -> Size Source #

ToCBOR ByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

ToCBOR ByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

ToCBOR ShortByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

ToCBOR OperationalCertificate Source # 
Instance details

Defined in Cardano.Api.Internal.OperationalCertificate

ToCBOR OperationalCertificateIssueCounter Source # 
Instance details

Defined in Cardano.Api.Internal.OperationalCertificate

ToCBOR CostModel Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

Methods

toCBOR :: CostModel -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CostModel -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CostModel] -> Size Source #

ToCBOR ExecutionUnitPrices Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

ToCBOR PraosNonce Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

ToCBOR ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

ToCBOR UpdateProposal Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

ToCBOR AnyPlutusScriptVersion Source # 
Instance details

Defined in Cardano.Api.Internal.Script

ToCBOR ExecutionUnits Source # 
Instance details

Defined in Cardano.Api.Internal.Script

ToCBOR ScriptData Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

ToCBOR Point 
Instance details

Defined in Cardano.Crypto.VRF.Simple

Methods

toCBOR :: Point -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Point -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Point] -> Size Source #

ToCBOR Proof 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: Proof -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Proof -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Proof] -> Size Source #

ToCBOR SignKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: SignKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SignKey -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKey] -> Size Source #

ToCBOR VerKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: VerKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy VerKey -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKey] -> Size Source #

ToCBOR Proof 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

toCBOR :: Proof -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Proof -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Proof] -> Size Source #

ToCBOR SignKey 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

toCBOR :: SignKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SignKey -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKey] -> Size Source #

ToCBOR VerKey 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Methods

toCBOR :: VerKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy VerKey -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKey] -> Size Source #

ToCBOR ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

ToCBOR RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

ToCBOR Raw 
Instance details

Defined in Cardano.Crypto.Raw

Methods

toCBOR :: Raw -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Raw -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Raw] -> Size Source #

ToCBOR CompactRedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Compact

ToCBOR RedeemSigningKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.SigningKey

ToCBOR RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

ToCBOR SigningKey 
Instance details

Defined in Cardano.Crypto.Signing.SigningKey

ToCBOR VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

ToCBOR AlonzoGenesis 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

ToCBOR IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

toCBOR :: IsValid -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy IsValid -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [IsValid] -> Size Source #

ToCBOR Version 
Instance details

Defined in Cardano.Ledger.Binary.Version

Methods

toCBOR :: Version -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Version -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Version] -> Size Source #

ToCBOR Body 
Instance details

Defined in Cardano.Chain.Block.Body

Methods

toCBOR :: Body -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Body -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Body] -> Size Source #

ToCBOR BlockSignature 
Instance details

Defined in Cardano.Chain.Block.Header

ToCBOR ToSign 
Instance details

Defined in Cardano.Chain.Block.Header

Methods

toCBOR :: ToSign -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ToSign -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ToSign] -> Size Source #

ToCBOR Proof 
Instance details

Defined in Cardano.Chain.Block.Proof

Methods

toCBOR :: Proof -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Proof -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Proof] -> Size Source #

ToCBOR ChainValidationState 
Instance details

Defined in Cardano.Chain.Block.Validation

ToCBOR ApplyMempoolPayloadErr 
Instance details

Defined in Cardano.Chain.Byron.API.Mempool

ToCBOR HDAddressPayload 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

ToCBOR AddrSpendingData 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

ToCBOR AddrType 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Methods

toCBOR :: AddrType -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy AddrType -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AddrType] -> Size Source #

ToCBOR Address 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

toCBOR :: Address -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Address -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Address] -> Size Source #

ToCBOR Address' 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

toCBOR :: Address' -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Address' -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Address'] -> Size Source #

ToCBOR BlockCount 
Instance details

Defined in Cardano.Chain.Common.BlockCount

ToCBOR ChainDifficulty 
Instance details

Defined in Cardano.Chain.Common.ChainDifficulty

ToCBOR CompactAddress 
Instance details

Defined in Cardano.Chain.Common.Compact

ToCBOR Lovelace 
Instance details

Defined in Cardano.Chain.Common.Lovelace

Methods

toCBOR :: Lovelace -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Lovelace -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Lovelace] -> Size Source #

ToCBOR LovelaceError 
Instance details

Defined in Cardano.Chain.Common.Lovelace

ToCBOR LovelacePortion 
Instance details

Defined in Cardano.Chain.Common.LovelacePortion

ToCBOR NetworkMagic 
Instance details

Defined in Cardano.Chain.Common.NetworkMagic

ToCBOR TxFeePolicy 
Instance details

Defined in Cardano.Chain.Common.TxFeePolicy

ToCBOR TxSizeLinear 
Instance details

Defined in Cardano.Chain.Common.TxSizeLinear

ToCBOR Certificate 
Instance details

Defined in Cardano.Chain.Delegation.Certificate

ToCBOR Map 
Instance details

Defined in Cardano.Chain.Delegation.Map

Methods

toCBOR :: Map -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Map -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Map] -> Size Source #

ToCBOR Payload 
Instance details

Defined in Cardano.Chain.Delegation.Payload

Methods

toCBOR :: Payload -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Payload -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Payload] -> Size Source #

ToCBOR State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Activation

Methods

toCBOR :: State -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy State -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [State] -> Size Source #

ToCBOR State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Interface

Methods

toCBOR :: State -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy State -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [State] -> Size Source #

ToCBOR Error 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

Methods

toCBOR :: Error -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Error -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Error] -> Size Source #

ToCBOR ScheduledDelegation 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

ToCBOR State 
Instance details

Defined in Cardano.Chain.Delegation.Validation.Scheduling

Methods

toCBOR :: State -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy State -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [State] -> Size Source #

ToCBOR GenesisAvvmBalances 
Instance details

Defined in Cardano.Chain.Genesis.AvvmBalances

ToCBOR Config 
Instance details

Defined in Cardano.Chain.Genesis.Config

Methods

toCBOR :: Config -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Config -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Config] -> Size Source #

ToCBOR GenesisData 
Instance details

Defined in Cardano.Chain.Genesis.Data

ToCBOR GenesisDelegation 
Instance details

Defined in Cardano.Chain.Genesis.Delegation

ToCBOR GenesisKeyHashes 
Instance details

Defined in Cardano.Chain.Genesis.KeyHashes

ToCBOR GenesisNonAvvmBalances 
Instance details

Defined in Cardano.Chain.Genesis.NonAvvmBalances

ToCBOR MempoolPayload 
Instance details

Defined in Cardano.Chain.MempoolPayload

ToCBOR EpochAndSlotCount 
Instance details

Defined in Cardano.Chain.Slotting.EpochAndSlotCount

ToCBOR EpochNumber 
Instance details

Defined in Cardano.Chain.Slotting.EpochNumber

ToCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

ToCBOR SlotCount 
Instance details

Defined in Cardano.Chain.Slotting.SlotCount

Methods

toCBOR :: SlotCount -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotCount -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SlotCount] -> Size Source #

ToCBOR SlotNumber 
Instance details

Defined in Cardano.Chain.Slotting.SlotNumber

ToCBOR SscPayload 
Instance details

Defined in Cardano.Chain.Ssc

ToCBOR SscProof 
Instance details

Defined in Cardano.Chain.Ssc

Methods

toCBOR :: SscProof -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SscProof -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SscProof] -> Size Source #

ToCBOR CompactTxId 
Instance details

Defined in Cardano.Chain.UTxO.Compact

ToCBOR CompactTxIn 
Instance details

Defined in Cardano.Chain.UTxO.Compact

ToCBOR CompactTxOut 
Instance details

Defined in Cardano.Chain.UTxO.Compact

ToCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toCBOR :: Tx -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Tx -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Tx] -> Size Source #

ToCBOR TxIn 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toCBOR :: TxIn -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIn -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIn] -> Size Source #

ToCBOR TxOut 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toCBOR :: TxOut -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxOut -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxOut] -> Size Source #

ToCBOR TxAux 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

Methods

toCBOR :: TxAux -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxAux -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxAux] -> Size Source #

ToCBOR TxPayload 
Instance details

Defined in Cardano.Chain.UTxO.TxPayload

Methods

toCBOR :: TxPayload -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxPayload -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxPayload] -> Size Source #

ToCBOR TxProof 
Instance details

Defined in Cardano.Chain.UTxO.TxProof

Methods

toCBOR :: TxProof -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxProof -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxProof] -> Size Source #

ToCBOR TxInWitness 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

ToCBOR TxSigData 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Methods

toCBOR :: TxSigData -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxSigData -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxSigData] -> Size Source #

ToCBOR UTxO 
Instance details

Defined in Cardano.Chain.UTxO.UTxO

Methods

toCBOR :: UTxO -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy UTxO -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTxO] -> Size Source #

ToCBOR UTxOError 
Instance details

Defined in Cardano.Chain.UTxO.UTxO

Methods

toCBOR :: UTxOError -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy UTxOError -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTxOError] -> Size Source #

ToCBOR UTxOConfiguration 
Instance details

Defined in Cardano.Chain.UTxO.UTxOConfiguration

ToCBOR TxValidationError 
Instance details

Defined in Cardano.Chain.UTxO.Validation

ToCBOR UTxOValidationError 
Instance details

Defined in Cardano.Chain.UTxO.Validation

ToCBOR ApplicationName 
Instance details

Defined in Cardano.Chain.Update.ApplicationName

ToCBOR ApplicationNameError 
Instance details

Defined in Cardano.Chain.Update.ApplicationName

ToCBOR InstallerHash 
Instance details

Defined in Cardano.Chain.Update.InstallerHash

ToCBOR Payload 
Instance details

Defined in Cardano.Chain.Update.Payload

Methods

toCBOR :: Payload -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Payload -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Payload] -> Size Source #

ToCBOR Proposal 
Instance details

Defined in Cardano.Chain.Update.Proposal

Methods

toCBOR :: Proposal -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Proposal -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Proposal] -> Size Source #

ToCBOR ProposalBody 
Instance details

Defined in Cardano.Chain.Update.Proposal

ToCBOR ProtocolParameters 
Instance details

Defined in Cardano.Chain.Update.ProtocolParameters

ToCBOR ProtocolParametersUpdate 
Instance details

Defined in Cardano.Chain.Update.ProtocolParametersUpdate

ToCBOR ProtocolVersion 
Instance details

Defined in Cardano.Chain.Update.ProtocolVersion

ToCBOR SoftforkRule 
Instance details

Defined in Cardano.Chain.Update.SoftforkRule

ToCBOR SoftwareVersion 
Instance details

Defined in Cardano.Chain.Update.SoftwareVersion

ToCBOR SoftwareVersionError 
Instance details

Defined in Cardano.Chain.Update.SoftwareVersion

ToCBOR SystemTag 
Instance details

Defined in Cardano.Chain.Update.SystemTag

Methods

toCBOR :: SystemTag -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SystemTag -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SystemTag] -> Size Source #

ToCBOR SystemTagError 
Instance details

Defined in Cardano.Chain.Update.SystemTag

ToCBOR CandidateProtocolUpdate 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

ToCBOR Endorsement 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

ToCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Endorsement

Methods

toCBOR :: Error -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Error -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Error] -> Size Source #

ToCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Interface

Methods

toCBOR :: Error -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Error -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Error] -> Size Source #

ToCBOR State 
Instance details

Defined in Cardano.Chain.Update.Validation.Interface

Methods

toCBOR :: State -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy State -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [State] -> Size Source #

ToCBOR Adopted 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: Adopted -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Adopted -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Adopted] -> Size Source #

ToCBOR ApplicationVersion 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

ToCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: Error -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Error -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Error] -> Size Source #

ToCBOR ProtocolUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

ToCBOR SoftwareUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

ToCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Voting

Methods

toCBOR :: Error -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Error -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Error] -> Size Source #

ToCBOR Vote 
Instance details

Defined in Cardano.Chain.Update.Vote

Methods

toCBOR :: Vote -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Vote -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Vote] -> Size Source #

ToCBOR ConwayGenesis 
Instance details

Defined in Cardano.Ledger.Conway.Genesis

ToCBOR DefaultVote 
Instance details

Defined in Cardano.Ledger.Conway.Governance

ToCBOR ActiveSlotCoeff 
Instance details

Defined in Cardano.Ledger.BaseTypes

ToCBOR CertIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: CertIx -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CertIx -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertIx] -> Size Source #

ToCBOR Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: Network -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Network -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Network] -> Size Source #

ToCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: Nonce -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Nonce -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Nonce] -> Size Source #

ToCBOR PositiveUnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

ToCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: ProtVer -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size Source #

ToCBOR TxIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: TxIx -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy TxIx -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxIx] -> Size Source #

ToCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: Coin -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Coin -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Coin] -> Size Source #

ToCBOR DeltaCoin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: DeltaCoin -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy DeltaCoin -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [DeltaCoin] -> Size Source #

ToCBOR Ptr 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toCBOR :: Ptr -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Ptr -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Ptr] -> Size Source #

ToCBOR SlotNo32 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toCBOR :: SlotNo32 -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotNo32 -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SlotNo32] -> Size Source #

ToCBOR ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

ToCBOR BootstrapWitness 
Instance details

Defined in Cardano.Ledger.Keys.Bootstrap

ToCBOR PlutusWithContext 
Instance details

Defined in Cardano.Ledger.Plutus.Evaluate

ToCBOR Language 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

toCBOR :: Language -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Language -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Language] -> Size Source #

ToCBOR PlutusBinary 
Instance details

Defined in Cardano.Ledger.Plutus.Language

ToCBOR ShelleyGenesis 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

ToCBOR FromByronTranslationContext 
Instance details

Defined in Cardano.Ledger.Shelley.Translation

ToCBOR ChainDepState 
Instance details

Defined in Cardano.Protocol.TPraos.API

ToCBOR KESPeriod 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Methods

toCBOR :: KESPeriod -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy KESPeriod -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [KESPeriod] -> Size Source #

ToCBOR PrtclState 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Prtcl

ToCBOR TicknState 
Instance details

Defined in Cardano.Protocol.TPraos.Rules.Tickn

ToCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toCBOR :: BlockNo -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockNo -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BlockNo] -> Size Source #

ToCBOR EpochInterval 
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: EpochNo -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochNo -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochNo] -> Size Source #

ToCBOR EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: EpochSize -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochSize -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochSize] -> Size Source #

ToCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: SlotNo -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy SlotNo -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SlotNo] -> Size Source #

ToCBOR RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

ToCBOR SlotLength 
Instance details

Defined in Cardano.Slotting.Time

ToCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

ToCBOR Encoding 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Encoding -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Encoding -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Encoding] -> Size Source #

ToCBOR Term 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Term -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Term -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Term] -> Size Source #

ToCBOR SecurityParam 
Instance details

Defined in Ouroboros.Consensus.Config.SecurityParam

ToCBOR CoreNodeId 
Instance details

Defined in Ouroboros.Consensus.NodeId

ToCBOR NodeId 
Instance details

Defined in Ouroboros.Consensus.NodeId

Methods

toCBOR :: NodeId -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy NodeId -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NodeId] -> Size Source #

ToCBOR CompactGenesis 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

ToCBOR NonMyopicMemberRewards 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

ToCBOR StakeSnapshot 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

ToCBOR StakeSnapshots 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

ToCBOR ShelleyHash 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

ToCBOR PraosState 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

ToCBOR InputVRF 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.VRF

Methods

toCBOR :: InputVRF -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy InputVRF -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [InputVRF] -> Size Source #

ToCBOR TPraosState 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

ToCBOR AccPoolStakeCoded 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Methods

toCBOR :: AccPoolStakeCoded -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy AccPoolStakeCoded -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AccPoolStakeCoded] -> Size Source #

ToCBOR LedgerPeerSnapshot 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

ToCBOR PoolStakeCoded 
Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Methods

toCBOR :: PoolStakeCoded -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy PoolStakeCoded -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PoolStakeCoded] -> Size Source #

ToCBOR WithOriginCoded

Hand cranked CBOR instances to facilitate CDDL spec

Instance details

Defined in Ouroboros.Network.PeerSelection.LedgerPeers.Type

Methods

toCBOR :: WithOriginCoded -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy WithOriginCoded -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [WithOriginCoded] -> Size Source #

ToCBOR RelayAccessPointCoded

These instances are used to serialize LedgerPeerSnapshot consensus LocalStateQuery server which uses these instances for all its query responses. It appears they provide some improved debugging diagnostics over Serialize instances.

Instance details

Defined in Ouroboros.Network.PeerSelection.RelayAccessPoint

ToCBOR Text 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Text -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Text -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Text] -> Size Source #

ToCBOR UTCTime 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: UTCTime -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy UTCTime -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTCTime] -> Size Source #

ToCBOR Integer 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Integer -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Integer -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Integer] -> Size Source #

ToCBOR Natural 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Natural -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Natural -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Natural] -> Size Source #

ToCBOR () 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: () -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy () -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [()] -> Size Source #

ToCBOR Bool 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Bool -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Bool -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Bool] -> Size Source #

ToCBOR Double 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Double -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Double -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Double] -> Size Source #

ToCBOR Float 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Float -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Float -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Float] -> Size Source #

ToCBOR Int 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Int -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Int -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Int] -> Size Source #

ToCBOR Word 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Word -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Word] -> Size Source #

ToCBOR a => ToCBOR (NonEmpty a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: NonEmpty a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NonEmpty a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NonEmpty a] -> Size Source #

ToCBOR a => ToCBOR (Ratio a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Ratio a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Ratio a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Ratio a] -> Size Source #

IsShelleyBasedEra era => ToCBOR (Certificate era) Source # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.Governance.Actions.ProposalProcedure

Methods

toCBOR :: Proposal era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Proposal era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Proposal era] -> Size Source #

IsShelleyBasedEra era => ToCBOR (VotingProcedure era) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Methods

toCBOR :: Hash ByronKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash ByronKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash ByronKey] -> Size Source #

ToCBOR (Hash ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (Hash KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Methods

toCBOR :: Hash KesKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash KesKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash KesKey] -> Size Source #

ToCBOR (Hash VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Methods

toCBOR :: Hash VrfKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash VrfKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash VrfKey] -> Size Source #

ToCBOR (Hash CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toCBOR :: Hash DRepKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash DRepKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash DRepKey] -> Size Source #

ToCBOR (Hash GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (Hash StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Methods

toCBOR :: Hash StakeKey -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash StakeKey) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash StakeKey] -> Size Source #

ToCBOR (Hash StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes a => ToCBOR (UsingRawBytes a) Source # 
Instance details

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) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: LengthOf xs -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LengthOf xs) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LengthOf xs] -> Size Source #

ToCBOR (SigDSIGN Ed25519Bip32DSIGN) Source # 
Instance details

Defined in Cardano.Api.Crypto.Ed25519Bip32

ToCBOR (SigDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

ToCBOR (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

ToCBOR (SigDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

ToCBOR (SigDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

ToCBOR (SigDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

ToCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) Source # 
Instance details

Defined in Cardano.Api.Crypto.Ed25519Bip32

ToCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

ToCBOR (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

ToCBOR (SignKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

ToCBOR (SignKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

ToCBOR (SignKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

(TypeError ('Text "CBOR encoding would violate mlocking guarantees") :: Constraint) => ToCBOR (SignKeyDSIGNM Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

ToCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) Source # 
Instance details

Defined in Cardano.Api.Crypto.Ed25519Bip32

ToCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

ToCBOR (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

ToCBOR (VerKeyDSIGN Ed448DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed448

ToCBOR (VerKeyDSIGN MockDSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Mock

ToCBOR (VerKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

(DSIGNMAlgorithm d, KnownNat (SizeSigKES (CompactSingleKES d))) => ToCBOR (SigKES (CompactSingleKES d)) 
Instance details

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)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

Methods

toCBOR :: SigKES (CompactSumKES h d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigKES (CompactSumKES h d)) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigKES (CompactSumKES h d)] -> Size Source #

KnownNat t => ToCBOR (SigKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

toCBOR :: SigKES (MockKES t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SigKES (MockKES t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SigKES (MockKES t)] -> Size Source #

(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => ToCBOR (SigKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

toCBOR :: SigKES (SimpleKES d t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (SigKES (SimpleKES d t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [SigKES (SimpleKES d t)] -> Size Source #

DSIGNMAlgorithm d => ToCBOR (SigKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

toCBOR :: SigKES (SingleKES d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigKES (SingleKES d)) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigKES (SingleKES d)] -> Size Source #

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => ToCBOR (SigKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

toCBOR :: SigKES (SumKES h d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigKES (SumKES h d)) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigKES (SumKES h d)] -> Size Source #

(UnsoundDSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => ToCBOR (UnsoundPureSignKeyKES (CompactSingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSingle

(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)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t => ToCBOR (UnsoundPureSignKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

UnsoundDSIGNMAlgorithm d => ToCBOR (UnsoundPureSignKeyKES (SingleKES d)) 
Instance details

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))) => ToCBOR (UnsoundPureSignKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

(DSIGNMAlgorithm d, KnownNat (SizeSigDSIGN d + SizeVerKeyDSIGN d)) => ToCBOR (VerKeyKES (CompactSingleKES d)) 
Instance details

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 (VerKeyKES (CompactSumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.CompactSum

KnownNat t => ToCBOR (VerKeyKES (MockKES t)) 
Instance details

Defined in Cardano.Crypto.KES.Mock

Methods

toCBOR :: VerKeyKES (MockKES t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (VerKeyKES (MockKES t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [VerKeyKES (MockKES t)] -> Size Source #

(DSIGNMAlgorithm d, KnownNat t, KnownNat (SeedSizeDSIGN d * t), KnownNat (SizeVerKeyDSIGN d * t), KnownNat (SizeSignKeyDSIGN d * t)) => ToCBOR (VerKeyKES (SimpleKES d t)) 
Instance details

Defined in Cardano.Crypto.KES.Simple

Methods

toCBOR :: VerKeyKES (SimpleKES d t) -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (VerKeyKES (SimpleKES d t)) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [VerKeyKES (SimpleKES d t)] -> Size Source #

DSIGNMAlgorithm d => ToCBOR (VerKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

toCBOR :: VerKeyKES (SingleKES d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyKES (SingleKES d)) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyKES (SingleKES d)] -> Size Source #

(KESAlgorithm (SumKES h d), SodiumHashAlgorithm h, SizeHash h ~ SeedSizeKES d) => ToCBOR (VerKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

toCBOR :: VerKeyKES (SumKES h d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyKES (SumKES h d)) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyKES (SumKES h d)] -> Size Source #

ToCBOR (CertVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

ToCBOR (CertVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

ToCBOR (CertVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

ToCBOR (CertVRF PraosBatchCompatVRF) 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

Typeable v => ToCBOR (OutputVRF v) 
Instance details

Defined in Cardano.Crypto.VRF.Class

Methods

toCBOR :: OutputVRF v -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (OutputVRF v) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [OutputVRF v] -> Size Source #

ToCBOR (SignKeyVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

ToCBOR (SignKeyVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

ToCBOR (SignKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

ToCBOR (SignKeyVRF PraosBatchCompatVRF) 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

ToCBOR (VerKeyVRF MockVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Mock

ToCBOR (VerKeyVRF SimpleVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Simple

ToCBOR (VerKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

ToCBOR (VerKeyVRF PraosBatchCompatVRF) 
Instance details

Defined in Cardano.Crypto.VRF.PraosBatchCompat

EncCBOR a => ToCBOR (RedeemSignature a) 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.Signature

Typeable a => ToCBOR (Signature a) 
Instance details

Defined in Cardano.Crypto.Signing.Signature

Methods

toCBOR :: Signature a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Signature a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Signature a] -> Size Source #

Typeable era => ToCBOR (AllegraTxAuxData era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

toCBOR :: AlonzoTx era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTx era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoTx era] -> Size Source #

Typeable era => ToCBOR (AlonzoTxAuxData era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWits

Methods

toCBOR :: Redeemers era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Redeemers era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Redeemers era] -> Size Source #

Typeable era => ToCBOR (TxDats era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWits

Methods

toCBOR :: TxDats era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (TxDats era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TxDats era] -> Size Source #

Typeable era => ToCBOR (BabbageTxBody era) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

ToCBOR (Attributes ()) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Chain.MempoolPayload

EncCBOR n => ToCBOR (TooLarge n) 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: TooLarge n -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (TooLarge n) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [TooLarge n] -> Size Source #

(EraPParams era, EraStake era) => ToCBOR (ConwayGovState era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Gov

Typeable era => ToCBOR (ConwayTxBody era) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.BaseTypes.NonZero

Methods

toCBOR :: NonZero a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NonZero a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NonZero a] -> Size Source #

Era era => ToCBOR (CommitteeState era) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Coin

(Typeable era, ToCBOR (PParamsHKD Identity era)) => ToCBOR (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toCBOR :: PParams era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PParams era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PParams era] -> Size Source #

(Typeable era, ToCBOR (PParamsHKD StrictMaybe era)) => ToCBOR (PParamsUpdate era) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Genesis

Methods

toCBOR :: NoGenesis era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NoGenesis era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NoGenesis era] -> Size Source #

Typeable r => ToCBOR (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBOR :: KeyHash r -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (KeyHash r) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [KeyHash r] -> Size Source #

Typeable i => ToCBOR (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBOR :: SafeHash i -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SafeHash i) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SafeHash i] -> Size Source #

Typeable r => ToCBOR (VRFVerKeyHash r) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toCBOR :: VKey kd -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VKey kd) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VKey kd] -> Size Source #

Typeable kr => ToCBOR (WitVKey kr) 
Instance details

Defined in Cardano.Ledger.Keys.WitVKey

Methods

toCBOR :: WitVKey kr -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (WitVKey kr) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [WitVKey kr] -> Size Source #

Typeable t => ToCBOR (MemoBytes t) 
Instance details

Defined in Cardano.Ledger.MemoBytes.Internal

Methods

toCBOR :: MemoBytes t -> Encoding Source #

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (MemoBytes t) -> Size Source #

encodedListSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy [MemoBytes t] -> Size Source #

Typeable era => ToCBOR (Data era) 
Instance details

Defined in Cardano.Ledger.Plutus.Data

Methods

toCBOR :: Data era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Data era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Data era] -> Size Source #

PlutusLanguage l => ToCBOR (SLanguage l) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

toCBOR :: SLanguage l -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SLanguage l) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SLanguage l] -> Size Source #

(EncCBOR (TxOut era), Era era) => ToCBOR (UTxO era) 
Instance details

Defined in Cardano.Ledger.State.UTxO

Methods

toCBOR :: UTxO era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UTxO era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTxO era] -> Size Source #

Typeable era => ToCBOR (MaryTxBody era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toCBOR :: UTxOState era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UTxOState era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [UTxOState era] -> Size Source #

(Era era, ToCBOR (PParamsUpdate era)) => ToCBOR (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Typeable era => ToCBOR (MultiSig era) 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

Methods

toCBOR :: MultiSig era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (MultiSig era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [MultiSig era] -> Size Source #

Typeable era => ToCBOR (ShelleyTx era) 
Instance details

Defined in Cardano.Ledger.Shelley.Tx.Internal

Methods

toCBOR :: ShelleyTx era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTx era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTx era] -> Size Source #

Typeable era => ToCBOR (ShelleyTxAuxData era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Protocol.TPraos.BHeader

Methods

toCBOR :: BHeader c -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BHeader c) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BHeader c] -> Size Source #

Crypto c => ToCBOR (OCert c) 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Methods

toCBOR :: OCert c -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (OCert c) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [OCert c] -> Size Source #

(Serialise t, Typeable t) => ToCBOR (WithOrigin t) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Data.Sequence.Strict

Methods

toCBOR :: StrictSeq a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StrictSeq a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StrictSeq a] -> Size Source #

ToCBOR a => ToCBOR (Seq a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Seq a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Seq a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Seq a] -> Size Source #

(Ord a, ToCBOR a) => ToCBOR (Set a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Set a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Set a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Set a] -> Size Source #

Crypto c => ToCBOR (Header c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Header

Methods

toCBOR :: Header c -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Header c) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Header c] -> Size Source #

ToCBOR a => ToCBOR (Vector a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Vector a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Vector a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Vector a] -> Size Source #

ToCBOR a => ToCBOR (Maybe a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Maybe a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Maybe a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Maybe a] -> Size Source #

ToCBOR a => ToCBOR [a] 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: [a] -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [[a]] -> Size Source #

(ToCBOR a, ToCBOR b) => ToCBOR (Either a b) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Either a b -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Either a b) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Either a b] -> Size Source #

Typeable a => ToCBOR (Fixed a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Fixed a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Fixed a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Fixed a] -> Size Source #

(HashAlgorithm h, Typeable a) => ToCBOR (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

toCBOR :: Hash h a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash h a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash h a] -> Size Source #

(VRFAlgorithm v, Typeable a) => ToCBOR (CertifiedVRF v a) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Allegra.Scripts

Methods

toCBOR :: Timelock era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Timelock era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Timelock era] -> Size Source #

Era era => ToCBOR (AlonzoPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Era era => ToCBOR (AlonzoPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Era era => ToCBOR (BabbagePParams Identity era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Era era => ToCBOR (BabbagePParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Era era => ToCBOR (ConwayPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Era era => ToCBOR (ConwayPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

(ToCBOR a, Integral a, Bounded a, Typeable b) => ToCBOR (BoundedRatio b a) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: BoundedRatio b a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BoundedRatio b a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BoundedRatio b a] -> Size Source #

(EraTx era, Typeable h) => ToCBOR (Block h era) 
Instance details

Defined in Cardano.Ledger.Block

Methods

toCBOR :: Block h era -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Block h era) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Block h era] -> Size Source #

(KnownSymbol rule, Era era) => ToCBOR (VoidEraRule rule era) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Era era => ToCBOR (ShelleyPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

(Ord k, ToCBOR k, ToCBOR v) => ToCBOR (Map k v) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Map k v -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Map k v) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Map k v] -> Size Source #

(ToCBOR a, ToCBOR b) => ToCBOR (a, b) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (a, b) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [(a, b)] -> Size Source #

ToCBOR (Tokens -> Tokens) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (Tokens -> Tokens) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Tokens -> Tokens) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Tokens -> Tokens] -> Size Source #

(Typeable s, ToCBOR a) => ToCBOR (Tagged s a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Tagged s a -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Tagged s a) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Tagged s a] -> Size Source #

(ToCBOR a, ToCBOR b, ToCBOR c) => ToCBOR (a, b, c) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b, c) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (a, b, c) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [(a, b, c)] -> Size Source #

(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d) => ToCBOR (a, b, c, d) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b, c, d) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (a, b, c, d) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [(a, b, c, d)] -> Size Source #

(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d, ToCBOR e) => ToCBOR (a, b, c, d, e) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b, c, d, e) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (a, b, c, d, e) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [(a, b, c, d, e)] -> Size Source #

(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d, ToCBOR e, ToCBOR f) => ToCBOR (a, b, c, d, e, f) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b, c, d, e, f) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (a, b, c, d, e, f) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [(a, b, c, d, e, f)] -> Size Source #

(ToCBOR a, ToCBOR b, ToCBOR c, ToCBOR d, ToCBOR e, ToCBOR f, ToCBOR g) => ToCBOR (a, b, c, d, e, f, g) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b, c, d, e, f, g) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (a, b, c, d, e, f, g) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [(a, b, c, d, e, f, g)] -> Size Source #

(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) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b, c, d, e, f, g, h) -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (a, b, c, d, e, f, g, h) -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [(a, b, c, d, e, f, g, h)] -> Size Source #

castHash :: CastHash roleA roleB => Hash roleA -> Hash roleB Source #

data family VerificationKey keyrole Source #

The type of cryptographic verification key, for each key role.

Instances

Instances details
IsString (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

IsString (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

IsString (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

IsString (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

IsString (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Show (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Show (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Show (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Show (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTypeProxy a => HasTypeProxy (VerificationKey a) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Class

Associated Types

data AsType (VerificationKey a) 
Instance details

Defined in Cardano.Api.Internal.Keys.Class

SerialiseAsCBOR (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsCBOR (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsCBOR (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsCBOR (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsBech32 (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsRawBytes (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsRawBytes (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

HasTextEnvelope (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

HasTextEnvelope (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

HasTextEnvelope (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Eq (VerificationKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Eq (VerificationKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Eq (VerificationKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Eq (VerificationKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Eq (VerificationKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey ByronKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

newtype VerificationKey ByronKeyLegacy Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

newtype VerificationKey KesKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

newtype VerificationKey VrfKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

newtype VerificationKey CommitteeColdExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey CommitteeColdKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey CommitteeHotExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey CommitteeHotKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey DRepExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey DRepKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey GenesisDelegateExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey GenesisDelegateKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey GenesisExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey GenesisKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey GenesisUTxOKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey PaymentExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey PaymentKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey StakeExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey StakeKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey StakePoolExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype VerificationKey StakePoolKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

data AsType (VerificationKey a) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Class

data family SigningKey keyrole Source #

The type of cryptographic signing key, for each key role.

Instances

Instances details
IsString (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

IsString (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

IsString (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

IsString (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

IsString (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

IsString (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Show (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

Show (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Show (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

Show (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

Show (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTypeProxy a => HasTypeProxy (SigningKey a) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Class

Associated Types

data AsType (SigningKey a) 
Instance details

Defined in Cardano.Api.Internal.Keys.Class

SerialiseAsCBOR (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsCBOR (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsCBOR (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsCBOR (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsCBOR (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsBech32 (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsBech32 (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsRawBytes (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

SerialiseAsRawBytes (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsRawBytes (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

HasTextEnvelope (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

HasTextEnvelope (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

HasTextEnvelope (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

HasTextEnvelope (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

HasTextEnvelope (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

FromCBOR (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

FromCBOR (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

FromCBOR (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey ByronKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (SigningKey ByronKeyLegacy) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

ToCBOR (SigningKey KesKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (SigningKey VrfKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

ToCBOR (SigningKey CommitteeColdExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey CommitteeColdKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey CommitteeHotExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey CommitteeHotKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey DRepExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey DRepKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisDelegateExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisDelegateKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey GenesisUTxOKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey PaymentExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey PaymentKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakeExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakeKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakePoolExtendedKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

ToCBOR (SigningKey StakePoolKey) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey ByronKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

newtype SigningKey ByronKeyLegacy Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Byron

newtype SigningKey KesKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

newtype SigningKey VrfKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Praos

newtype SigningKey CommitteeColdExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey CommitteeColdKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey CommitteeHotExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey CommitteeHotKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey DRepExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey DRepKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey GenesisDelegateExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey GenesisDelegateKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey GenesisExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey GenesisKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey GenesisUTxOKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey PaymentExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey PaymentKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey StakeExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey StakeKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey StakePoolExtendedKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

newtype SigningKey StakePoolKey Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Shelley

data AsType (SigningKey a) Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Class

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.

Instances

Instances details
Eon CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Methods

inEonForEra :: a -> (CardanoEra era -> a) -> CardanoEra era -> a Source #

ToCardanoEra CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

TestEquality CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Methods

testEquality :: CardanoEra a -> CardanoEra b -> Maybe (a :~: b) Source #

Convert AllegraEraOnwards CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards

Convert AlonzoEraOnwards CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards

Convert BabbageEraOnwards CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards

Convert ByronToAlonzoEra CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra

Convert ConwayEraOnwards CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards

Convert MaryEraOnwards CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.MaryEraOnwards

Convert ShelleyBasedEra CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra

Convert ShelleyEraOnly CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly

Convert ShelleyToAllegraEra CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra

Convert ShelleyToAlonzoEra CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra

Convert ShelleyToBabbageEra CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra

Convert ShelleyToMaryEra CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra

Convert Era CardanoEra Source # 
Instance details

Defined in Cardano.Api.Internal.Experimental.Eras

Methods

convert :: Era era -> CardanoEra era Source #

ToJSON (CardanoEra era) Source # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Eq (CardanoEra era) Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Methods

(==) :: CardanoEra era -> CardanoEra era -> Bool Source #

(/=) :: CardanoEra era -> CardanoEra era -> Bool Source #

Ord (CardanoEra era) Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Pretty (CardanoEra era) Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Methods

pretty :: CardanoEra era -> Doc ann #

prettyList :: [CardanoEra era] -> Doc ann #

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

Instances details
Show (Script lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Methods

showsPrec :: Int -> Script lang -> ShowS Source #

show :: Script lang -> String Source #

showList :: [Script lang] -> ShowS Source #

HasTypeProxy lang => HasTypeProxy (Script lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Associated Types

data AsType (Script lang) 
Instance details

Defined in Cardano.Api.Internal.Script

data AsType (Script lang) = AsScript (AsType lang)

Methods

proxyToAsType :: Proxy (Script lang) -> AsType (Script lang) Source #

IsScriptLanguage lang => SerialiseAsCBOR (Script lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

IsScriptLanguage lang => HasTextEnvelope (Script lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Eq (Script lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Methods

(==) :: Script lang -> Script lang -> Bool Source #

(/=) :: Script lang -> Script lang -> Bool Source #

data AsType (Script lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

data AsType (Script lang) = AsScript (AsType lang)

data Value Source #

Instances

Instances details
FromJSON Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

Methods

parseJSON :: Value -> Parser Value

parseJSONList :: Value -> Parser [Value]

omittedField :: Maybe Value

ToJSON Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

Methods

toJSON :: Value -> Value

toEncoding :: Value -> Encoding

toJSONList :: [Value] -> Value

toEncodingList :: [Value] -> Encoding

omitField :: Value -> Bool

Monoid Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

Semigroup Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

IsList Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

Associated Types

type Item Value 
Instance details

Defined in Cardano.Api.Internal.Value

Show Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

Eq Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

Methods

(==) :: Value -> Value -> Bool Source #

(/=) :: Value -> Value -> Bool Source #

type Item Value Source # 
Instance details

Defined in Cardano.Api.Internal.Value

data ByronEra Source #

A type used as a tag to distinguish the Byron era.

Instances

Instances details
IsCardanoEra ByronEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

HasTypeProxy ByronEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Associated Types

data AsType ByronEra 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

data AsType ByronEra Source # 
Instance details

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

Instances details
FromJSON ScriptHash Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Methods

parseJSON :: Value -> Parser ScriptHash

parseJSONList :: Value -> Parser [ScriptHash]

omittedField :: Maybe ScriptHash

ToJSON ScriptHash Source # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.Script

Show ScriptHash Source # 
Instance details

Defined in Cardano.Api.Internal.Script

HasTypeProxy ScriptHash Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Associated Types

data AsType ScriptHash 
Instance details

Defined in Cardano.Api.Internal.Script

SerialiseAsRawBytes ScriptHash Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Eq ScriptHash Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Ord ScriptHash Source # 
Instance details

Defined in Cardano.Api.Internal.Script

data AsType ScriptHash Source # 
Instance details

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 

Instances

Instances details
Show (Witness witctx era) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Methods

showsPrec :: Int -> Witness witctx era -> ShowS Source #

show :: Witness witctx era -> String Source #

showList :: [Witness witctx era] -> ShowS Source #

Eq (Witness witctx era) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Methods

(==) :: Witness witctx era -> Witness witctx era -> Bool Source #

(/=) :: Witness witctx era -> Witness witctx era -> Bool Source #

data MIRPot Source #

Constructors

ReservesMIR 
TreasuryMIR 

Instances

Instances details
ToJSON MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: MIRPot -> Value

toEncoding :: MIRPot -> Encoding

toJSONList :: [MIRPot] -> Value

toEncodingList :: [MIRPot] -> Encoding

omitField :: MIRPot -> Bool

Bounded MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Enum MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep MIRPot 
Instance details

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))
Show MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

DecCBOR MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

EncCBOR MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBOR :: MIRPot -> Encoding Source #

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy MIRPot -> Size Source #

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MIRPot] -> Size Source #

NFData MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: MIRPot -> () Source #

Eq MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Ord MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

NoThunks MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> MIRPot -> IO (Maybe ThunkInfo) #

wNoThunks :: Context -> MIRPot -> IO (Maybe ThunkInfo) #

showTypeOf :: Proxy MIRPot -> String #

type Rep MIRPot 
Instance details

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))

data MIRTarget Source #

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.

Instances

Instances details
ToJSON MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: MIRTarget -> Value

toEncoding :: MIRTarget -> Encoding

toJSONList :: [MIRTarget] -> Value

toEncodingList :: [MIRTarget] -> Encoding

omitField :: MIRTarget -> Bool

Generic MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep MIRTarget 
Instance details

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)))
Show MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

DecCBOR MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

EncCBOR MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

NFData MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: MIRTarget -> () Source #

Eq MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Ord MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

NoThunks MIRTarget 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> MIRTarget -> IO (Maybe ThunkInfo) #

wNoThunks :: Context -> MIRTarget -> IO (Maybe ThunkInfo) #

showTypeOf :: Proxy MIRTarget -> String #

type Rep MIRTarget 
Instance details

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)))

newtype CostModel Source #

Constructors

CostModel [Int64] 

Instances

Instances details
Data CostModel Source # 
Instance details

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 # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

FromCBOR CostModel Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

ToCBOR CostModel Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

Methods

toCBOR :: CostModel -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy CostModel -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CostModel] -> Size Source #

Eq CostModel Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

data AlonzoEra Source #

A type used as a tag to distinguish the Alonzo era.

data PlutusScript lang Source #

Plutus scripts.

Note that Plutus scripts have a binary serialisation but no JSON serialisation.

Instances

Instances details
Show (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

HasTypeProxy lang => HasTypeProxy (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Associated Types

data AsType (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Internal.Script

HasTypeProxy lang => SerialiseAsCBOR (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

HasTypeProxy lang => SerialiseAsRawBytes (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

IsPlutusScriptLanguage lang => HasTextEnvelope (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Eq (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

Methods

(==) :: PlutusScript lang -> PlutusScript lang -> Bool Source #

(/=) :: PlutusScript lang -> PlutusScript lang -> Bool Source #

Ord (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

data AsType (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Internal.Script

data BabbageEra Source #

A type used as a tag to distinguish the Babbage era.

Instances

Instances details
IsAllegraBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards

IsAlonzoBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards

IsBabbageBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards

IsMaryBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.MaryEraOnwards

IsShelleyBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra

IsCardanoEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

HasTypeProxy BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Associated Types

data AsType BabbageEra 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

HasScriptLanguageInEra PlutusScriptV1 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

HasScriptLanguageInEra PlutusScriptV2 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

ToAlonzoScript PlutusScriptV1 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

ToAlonzoScript PlutusScriptV2 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

data AsType BabbageEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

data ConwayEra Source #

A type used as a tag to distinguish the Conway era.

Instances

Instances details
IsAllegraBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards

IsAlonzoBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards

IsBabbageBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards

IsConwayBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards

IsMaryBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.MaryEraOnwards

IsShelleyBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra

IsCardanoEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

IsEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Experimental.Eras

HasTypeProxy ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

Associated Types

data AsType ConwayEra 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

HasScriptLanguageInEra PlutusScriptV1 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

HasScriptLanguageInEra PlutusScriptV2 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

HasScriptLanguageInEra PlutusScriptV3 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

ToAlonzoScript PlutusScriptV1 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

ToAlonzoScript PlutusScriptV2 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

ToAlonzoScript PlutusScriptV3 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Script

data AsType ConwayEra Source # 
Instance details

Defined in Cardano.Api.Internal.Eras.Core

newtype TxIx Source #

Constructors

TxIx Word 

Instances

Instances details
FromJSON TxIx Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

parseJSON :: Value -> Parser TxIx

parseJSONList :: Value -> Parser [TxIx]

omittedField :: Maybe TxIx

ToJSON TxIx Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

toJSON :: TxIx -> Value

toEncoding :: TxIx -> Encoding

toJSONList :: [TxIx] -> Value

toEncodingList :: [TxIx] -> Encoding

omitField :: TxIx -> Bool

Enum TxIx Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Show TxIx Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Eq TxIx Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

Methods

(==) :: TxIx -> TxIx -> Bool Source #

(/=) :: TxIx -> TxIx -> Bool Source #

Ord TxIx Source # 
Instance details

Defined in Cardano.Api.Internal.TxIn

data ShelleyEra Source #

A type used as a tag to distinguish the Shelley era.

data CommitteeMembersState Source #

Constructors

CommitteeMembersState 

Fields

Instances

Instances details
ToJSON CommitteeMembersState 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Generic CommitteeMembersState 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Associated Types

type Rep CommitteeMembersState 
Instance details

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))))
Show CommitteeMembersState 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

DecCBOR CommitteeMembersState 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

EncCBOR CommitteeMembersState 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Eq CommitteeMembersState 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Ord CommitteeMembersState 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

type Rep CommitteeMembersState 
Instance details

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

Instances details
ToJSON MemberStatus 
Instance details

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 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Enum MemberStatus 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Generic MemberStatus 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Associated Types

type Rep MemberStatus 
Instance details

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)))
Show MemberStatus 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

DecCBOR MemberStatus 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

EncCBOR MemberStatus 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Eq MemberStatus 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

Ord MemberStatus 
Instance details

Defined in Cardano.Ledger.Api.State.Query.CommitteeMembersState

type Rep MemberStatus 
Instance details

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)))

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.

queryDRepState 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))) 

type Ann = AnsiStyle 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

Instances details
Data EpochSlots 
Instance details

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 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Associated Types

type Rep EpochSlots 
Instance details

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)))
Read EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Show EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

FromCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

ToCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

DecCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

EncCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Buildable EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

build :: EpochSlots -> Builder

Eq EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Ord EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

NoThunks EpochSlots 
Instance details

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 
Instance details

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)))

class Error e where Source #

Methods

prettyError :: e -> Doc ann Source #

Instances

Instances details
Error IOException Source # 
Instance details

Defined in Cardano.Api.Internal.Error

Error AnchorDataFromCertificateError Source # 
Instance details

Defined in Cardano.Api.Internal.Certificate

Error InputDecodeError Source # 
Instance details

Defined in Cardano.Api.Internal.DeserialiseAnyOf

Error ErrorAsException Source # 
Instance details

Defined in Cardano.Api.Internal.Error

Error ScriptExecutionError Source # 
Instance details

Defined in Cardano.Api.Internal.Fees

Error MnemonicToSigningKeyError Source # 
Instance details

Defined in Cardano.Api.Internal.Keys.Mnemonics

Error FoldBlocksError Source # 
Instance details

Defined in Cardano.Api.Internal.LedgerState

Error GenesisConfigError Source # 
Instance details

Defined in Cardano.Api.Internal.LedgerState

Error InitialLedgerStateError Source # 
Instance details

Defined in Cardano.Api.Internal.LedgerState

Error LeadershipError Source # 
Instance details

Defined in Cardano.Api.Internal.LedgerState

Error LedgerStateError Source # 
Instance details

Defined in Cardano.Api.Internal.LedgerState

Error OperationalCertIssueError Source # 
Instance details

Defined in Cardano.Api.Internal.OperationalCertificate

Error ProtocolParametersConversionError Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

Error ProtocolParametersError Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

Error ScriptDataJsonBytesError Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Error ScriptDataJsonError Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Error ScriptDataJsonSchemaError Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Error ScriptDataRangeError Source # 
Instance details

Defined in Cardano.Api.Internal.ScriptData

Error Bech32DecodeError Source # 
Instance details

Defined in Cardano.Api.Internal.SerialiseBech32

Error JsonDecodeError Source # 
Instance details

Defined in Cardano.Api.Internal.SerialiseJSON

Error TextEnvelopeCddlError Source # 
Instance details

Defined in Cardano.Api.Internal.SerialiseLedgerCddl

Error RawBytesHexError Source # 
Instance details

Defined in Cardano.Api.Internal.SerialiseRaw

Error TextEnvelopeError Source # 
Instance details

Defined in Cardano.Api.Internal.SerialiseTextEnvelope

Error StakePoolMetadataValidationError Source # 
Instance details

Defined in Cardano.Api.Internal.StakePoolMetadata

Error TxBodyError Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Body

Error TxOutputError Source # 
Instance details

Defined in Cardano.Api.Internal.Tx.Output

Error TxMetadataJsonError Source # 
Instance details

Defined in Cardano.Api.Internal.TxMetadata

Error TxMetadataJsonSchemaError Source # 
Instance details

Defined in Cardano.Api.Internal.TxMetadata

Error TxMetadataRangeError Source # 
Instance details

Defined in Cardano.Api.Internal.TxMetadata

Error () Source # 
Instance details

Defined in Cardano.Api.Internal.Error

Methods

prettyError :: () -> Doc ann Source #

Error e => Error (FileError e) Source # 
Instance details

Defined in Cardano.Api.Internal.Error

Methods

prettyError :: FileError e -> Doc ann Source #

Error (AutoBalanceError era) Source # 
Instance details

Defined in Cardano.Api.Internal.Fees

Methods

prettyError :: AutoBalanceError era -> Doc ann Source #

Error (TransactionValidityError era) Source # 
Instance details

Defined in Cardano.Api.Internal.Fees

Error (TxBodyErrorAutoBalance era) Source # 
Instance details

Defined in Cardano.Api.Internal.Fees

Error (TxFeeEstimationError era) Source # 
Instance details

Defined in Cardano.Api.Internal.Fees

data ProtocolParametersUpdate Source #

The representation of a change in the ProtocolParameters.

Constructors

ProtocolParametersUpdate 

Fields

Instances

Instances details
Monoid ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

Semigroup ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

Show ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

FromCBOR ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

ToCBOR ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

Eq ProtocolParametersUpdate Source # 
Instance details

Defined in Cardano.Api.Internal.ProtocolParameters

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 applyBlock.

QuickValidation

Only check that the previous hash from the block matches the head hash of the ledger state.

data NetworkId Source #

Constructors

Mainnet 
Testnet !NetworkMagic 

Instances

Instances details
Show NetworkId Source # 
Instance details

Defined in Cardano.Api.Internal.NetworkId

Eq NetworkId Source # 
Instance details

Defined in Cardano.Api.Internal.NetworkId

newtype BlockNo Source #

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.

Constructors

BlockNo 

Fields

Instances

Instances details
FromJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

parseJSON :: Value -> Parser BlockNo

parseJSONList :: Value -> Parser [BlockNo]

omittedField :: Maybe BlockNo

ToJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toJSON :: BlockNo -> Value

toEncoding :: BlockNo -> Encoding

toJSONList :: [BlockNo] -> Value

toEncodingList :: [BlockNo] -> Encoding

omitField :: BlockNo -> Bool

Bounded BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Enum BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Generic BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Associated Types

type Rep BlockNo 
Instance details

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)))
Num BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Show BlockNo 
Instance details

Defined in Cardano.Slotting.Block

FromCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

ToCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toCBOR :: BlockNo -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy BlockNo -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BlockNo] -> Size Source #

DecCBOR BlockNo 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

EncCBOR BlockNo 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: BlockNo -> Encoding Source #

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy BlockNo -> Size Source #

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [BlockNo] -> Size Source #

NFData BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

rnf :: BlockNo -> () Source #

Eq BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Ord BlockNo 
Instance details

Defined in Cardano.Slotting.Block

NoThunks BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

noThunks :: Context -> BlockNo -> IO (Maybe ThunkInfo) #

wNoThunks :: Context -> BlockNo -> IO (Maybe ThunkInfo) #

showTypeOf :: Proxy BlockNo -> String #

ChainOrder BlockNo 
Instance details

Defined in Ouroboros.Consensus.Protocol.Abstract

Condense BlockNo 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Serialise BlockNo 
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo 
Instance details

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 
Instance details

Defined in Ouroboros.Consensus.Protocol.Abstract

newtype EpochNo Source #

An epoch, i.e. the number of the epoch.

Constructors

EpochNo 

Fields

Instances

Instances details
FromJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser EpochNo

parseJSONList :: Value -> Parser [EpochNo]

omittedField :: Maybe EpochNo

ToJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: EpochNo -> Value

toEncoding :: EpochNo -> Encoding

toJSONList :: [EpochNo] -> Value

toEncodingList :: [EpochNo] -> Encoding

omitField :: EpochNo -> Bool

Enum EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Generic EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep EpochNo = D1 ('MetaData "EpochNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-1062762da5e24b3256026b7bf7ed7ea570deea61ae8ec963e4334bb658f0121b" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
Show EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: EpochNo -> Encoding Source #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochNo -> Size Source #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochNo] -> Size Source #

DecCBOR EpochNo 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

EncCBOR EpochNo 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: EpochNo -> Encoding Source #

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy EpochNo -> Size Source #

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [EpochNo] -> Size Source #

NFData EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnf :: EpochNo -> () Source #

Eq EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Ord EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

noThunks :: Context -> EpochNo -> IO (Maybe ThunkInfo) #

wNoThunks :: Context -> EpochNo -> IO (Maybe ThunkInfo) #

showTypeOf :: Proxy EpochNo -> String #

Condense EpochNo 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Serialise